Haskell bindings

These Haskell bindings make large use of c2hs to generate much of the code, so
Unicorn's const_generator is not used.

The emulator is based on the Either monad transformer. The IO monad is used to
run the underlying Unicorn library, while the Either monad is used to handle
errors.

Instructions on how to build the bindings are located in
bindings/haskell/README.TXT. The same samples found in samples/ can be found
in bindings/haskell/samples. They should produce the same output, with slight
differences in their error handling and messaging.
This commit is contained in:
Adrian Herrera
2016-04-06 09:21:36 +10:00
parent affe94d5fe
commit 74aaf3b321
28 changed files with 2994 additions and 1 deletions

View File

@ -0,0 +1,29 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module : Unicorn.CPU.Arm
Description : Definitions for the ARM architecture.
Copyright : (c) Adrian Herrera, 2016
License : GPL-2
Definitions for the ARM architecture.
-}
module Unicorn.CPU.Arm (
Register(..),
) where
import Unicorn.Internal.Core (Reg)
{# context lib="unicorn" #}
#include <unicorn/arm.h>
-- | ARM registers.
{# enum uc_arm_reg as Register
{underscoreToCase}
omit (UC_ARM_REG_INVALID,
UC_ARM_REG_ENDING)
with prefix="UC_ARM_REG_"
deriving (Show, Eq) #}
instance Reg Register

View File

@ -0,0 +1,29 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module : Unicorn.CPU.Arm64
Description : Definitions for the ARM64 (ARMv8) architecture.
Copyright : (c) Adrian Herrera, 2016
License : GPL-2
Definitions for the ARM64 (ARMv8) architecture.
-}
module Unicorn.CPU.Arm64 (
Register(..),
) where
import Unicorn.Internal.Core (Reg)
{# context lib="unicorn" #}
#include <unicorn/arm64.h>
-- | ARM64 registers.
{# enum uc_arm64_reg as Register
{underscoreToCase}
omit (UC_ARM64_REG_INVALID,
UC_ARM64_REG_ENDING)
with prefix="UC_ARM64_REG_"
deriving (Show, Eq) #}
instance Reg Register

View File

@ -0,0 +1,29 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module : Unicorn.CPU.Mk68k
Description : Definitions for the MK68K architecture.
Copyright : (c) Adrian Herrera, 2016
License : GPL-2
Definitions for the MK68K architecture.
-}
module Unicorn.CPU.M68k (
Register(..),
) where
import Unicorn.Internal.Core (Reg)
{# context lib="unicorn" #}
#include <unicorn/m68k.h>
-- | M68K registers.
{# enum uc_m68k_reg as Register
{underscoreToCase}
omit (UC_M68K_REG_INVALID,
UC_M68K_REG_ENDING)
with prefix="UC_M68K_REG_"
deriving (Show, Eq) #}
instance Reg Register

View File

@ -0,0 +1,61 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module : Unicorn.CPU.Mips
Description : Definitions for the MIPS architecture.
Copyright : (c) Adrian Herrera, 2016
License : GPL-2
Definitions for the MIPS architecture.
-}
module Unicorn.CPU.Mips (
Register(..),
) where
import Unicorn.Internal.Core (Reg)
{# context lib="unicorn" #}
#include <unicorn/mips.h>
-- | MIPS registers.
{# enum UC_MIPS_REG as Register
{underscoreToCase,
UC_MIPS_REG_0 as Reg0,
UC_MIPS_REG_1 as Reg1,
UC_MIPS_REG_2 as Reg2,
UC_MIPS_REG_3 as Reg3,
UC_MIPS_REG_4 as Reg4,
UC_MIPS_REG_5 as Reg5,
UC_MIPS_REG_6 as Reg6,
UC_MIPS_REG_7 as Reg7,
UC_MIPS_REG_8 as Reg8,
UC_MIPS_REG_9 as Reg9,
UC_MIPS_REG_10 as Reg10,
UC_MIPS_REG_11 as Reg11,
UC_MIPS_REG_12 as Reg12,
UC_MIPS_REG_13 as Reg13,
UC_MIPS_REG_14 as Reg14,
UC_MIPS_REG_15 as Reg15,
UC_MIPS_REG_16 as Reg16,
UC_MIPS_REG_17 as Reg17,
UC_MIPS_REG_18 as Reg18,
UC_MIPS_REG_19 as Reg19,
UC_MIPS_REG_20 as Reg20,
UC_MIPS_REG_21 as Reg21,
UC_MIPS_REG_22 as Reg22,
UC_MIPS_REG_23 as Reg23,
UC_MIPS_REG_24 as Reg24,
UC_MIPS_REG_25 as Reg25,
UC_MIPS_REG_26 as Reg26,
UC_MIPS_REG_27 as Reg27,
UC_MIPS_REG_28 as Reg28,
UC_MIPS_REG_29 as Reg29,
UC_MIPS_REG_30 as Reg30,
UC_MIPS_REG_31 as Reg31}
omit (UC_MIPS_REG_INVALID,
UC_MIPS_REG_ENDING)
with prefix="UC_MIPS_REG_"
deriving (Show, Eq) #}
instance Reg Register

View File

@ -0,0 +1,29 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module : Unicorn.CPU.Sparc
Description : Definitions for the SPARC architecture.
Copyright : (c) Adrian Herrera, 2016
License : GPL-2
Definitions for the SPARC architecture.
-}
module Unicorn.CPU.Sparc (
Register(..),
) where
import Unicorn.Internal.Core (Reg)
{# context lib="unicorn" #}
#include <unicorn/sparc.h>
-- | SPARC registers.
{# enum uc_sparc_reg as Register
{underscoreToCase}
omit (UC_SPARC_REG_INVALID,
UC_SPARC_REG_ENDING)
with prefix="UC_SPARC_REG_"
deriving (Show, Eq) #}
instance Reg Register

View File

@ -0,0 +1,65 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module : Unicorn.CPU.X86
Description : Definitions for the X86 architecture.
Copyright : (c) Adrian Herrera, 2016
License : GPL-2
Definitions for the X86 architecture.
-}
module Unicorn.CPU.X86 (
Mmr(..),
Register(..),
Instruction(..),
) where
import Control.Applicative
import Data.Word
import Foreign
import Unicorn.Internal.Core (Reg)
{# context lib="unicorn" #}
#include <unicorn/x86.h>
-- | Memory-managemen Register for instructions IDTR, GDTR, LDTR, TR.
-- Borrow from SegmentCache in qemu/target-i386/cpu.h
data Mmr = Mmr {
selector :: Word16, -- ^ Not used by GDTR and IDTR
base :: Word64, -- ^ Handle 32 or 64 bit CPUs
limit :: Word32,
flags :: Word32 -- ^ Not used by GDTR and IDTR
}
instance Storable Mmr where
sizeOf _ = {# sizeof uc_x86_mmr #}
alignment _ = {# alignof uc_x86_mmr #}
peek p = Mmr <$> liftA fromIntegral ({# get uc_x86_mmr->selector #} p)
<*> liftA fromIntegral ({# get uc_x86_mmr->base #} p)
<*> liftA fromIntegral ({# get uc_x86_mmr->limit #} p)
<*> liftA fromIntegral ({# get uc_x86_mmr->flags #} p)
poke p mmr = do
{# set uc_x86_mmr.selector #} p (fromIntegral $ selector mmr)
{# set uc_x86_mmr.base #} p (fromIntegral $ base mmr)
{# set uc_x86_mmr.limit #} p (fromIntegral $ limit mmr)
{# set uc_x86_mmr.flags #} p (fromIntegral $ flags mmr)
-- | X86 registers.
{# enum uc_x86_reg as Register
{underscoreToCase}
omit (UC_X86_REG_INVALID,
UC_X86_REG_ENDING)
with prefix="UC_X86_REG_"
deriving (Show, Eq) #}
instance Reg Register
-- | X86 instructions.
{# enum uc_x86_insn as Instruction
{underscoreToCase}
omit (UC_X86_INS_INVALID,
UC_X86_INS_ENDING)
with prefix="UC_X86_INS_"
deriving (Show, Eq) #}