zydiskell-0.2.0.0: Haskell language binding for the Zydis library, a x86/x86-64 disassembler.
Safe HaskellNone
LanguageHaskell2010

Zydis.Util

Description

This handy module extend Storable typeclasse with default instances for C-like enums/fixed arrays (FFI).

Using StorableExt, we are now able to use deriving via clause on sum types.

data X
  = A
  | B
  | C
  deriving stock Enum
  deriving Storable via StorableExt X

This type will be stored as a word32 (C enum FFI).

Synopsis

Documentation

newtype StorableExt a Source #

Wrapper to extend storable default instances.

Constructors

StorableExt 

Fields

Instances

Instances details
Eq a => Eq (StorableExt a) Source # 
Instance details

Defined in Zydis.Util

Show a => Show (StorableExt a) Source # 
Instance details

Defined in Zydis.Util

Enum a => Storable (StorableExt a) Source # 
Instance details

Defined in Zydis.Util

class Storable a #

The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.

Memory addresses are represented as values of type Ptr a, for some a which is an instance of class Storable. The type argument to Ptr helps provide some valuable type safety in FFI code (you can't mix pointers of different types without an explicit cast), while helping the Haskell type system figure out which marshalling method is needed for a given pointer.

All marshalling between Haskell and a foreign language ultimately boils down to translating Haskell data structures into the binary representation of a corresponding data structure of the foreign language and vice versa. To code this marshalling in Haskell, it is necessary to manipulate primitive data types stored in unstructured memory blocks. The class Storable facilitates this manipulation on all types for which it is instantiated, which are the standard basic types of Haskell, the fixed size Int types (Int8, Int16, Int32, Int64), the fixed size Word types (Word8, Word16, Word32, Word64), StablePtr, all types from Foreign.C.Types, as well as Ptr.

Minimal complete definition

sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)

Instances

Instances details
Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable ()

Since: base-4.9.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: () -> Int #

alignment :: () -> Int #

peekElemOff :: Ptr () -> Int -> IO () #

pokeElemOff :: Ptr () -> Int -> () -> IO () #

peekByteOff :: Ptr b -> Int -> IO () #

pokeByteOff :: Ptr b -> Int -> () -> IO () #

peek :: Ptr () -> IO () #

poke :: Ptr () -> () -> IO () #

Storable WordPtr 
Instance details

Defined in Foreign.Ptr

Storable IntPtr 
Instance details

Defined in Foreign.Ptr

Storable Fingerprint

Since: base-4.4.0.0

Instance details

Defined in Foreign.Storable

Storable SwizzleMode Source # 
Instance details

Defined in Zydis.SwizzleMode

Storable RoundingMode Source # 
Instance details

Defined in Zydis.RoundingMode

Storable Register Source # 
Instance details

Defined in Zydis.Register

Storable PrefixType Source # 
Instance details

Defined in Zydis.PrefixType

Storable OperandVisibility Source # 
Instance details

Defined in Zydis.OperandVisibility

Storable OperandType Source # 
Instance details

Defined in Zydis.OperandType

Storable OperandMemoryType Source # 
Instance details

Defined in Zydis.OperandMemoryType

Storable OperandEncoding Source # 
Instance details

Defined in Zydis.OperandEncoding

Storable OpcodeMap Source # 
Instance details

Defined in Zydis.OpcodeMap

Storable Mnemonic Source # 
Instance details

Defined in Zydis.Mnemonic

Storable MaskMode Source # 
Instance details

Defined in Zydis.MaskMode

Storable MachineMode Source # 
Instance details

Defined in Zydis.MachineMode

Storable InstructionEncoding Source # 
Instance details

Defined in Zydis.InstructionEncoding

Storable InstructionCategory Source # 
Instance details

Defined in Zydis.InstructionCategory

Storable ISASet Source # 
Instance details

Defined in Zydis.ISASet

Storable ISAExt Source # 
Instance details

Defined in Zydis.ISAExt

Storable ExceptionClass Source # 
Instance details

Defined in Zydis.ExceptionClass

Storable ElementType Source # 
Instance details

Defined in Zydis.ElementType

Storable Operand Source # 
Instance details

Defined in Zydis.Operand

Storable OperandMemory Source # 
Instance details

Defined in Zydis.Operand

Storable OperandMemoryDisplacement Source # 
Instance details

Defined in Zydis.Operand

Storable OperandPointer Source # 
Instance details

Defined in Zydis.Operand

Storable OperandImmediate Source # 
Instance details

Defined in Zydis.Operand

Storable ConversionMode Source # 
Instance details

Defined in Zydis.ConversionMode

Storable CPUFlagAction Source # 
Instance details

Defined in Zydis.CPUFlagAction

Storable BroadcastMode Source # 
Instance details

Defined in Zydis.BroadcastMode

Storable BranchType Source # 
Instance details

Defined in Zydis.BranchType

Storable AddressWidth Source # 
Instance details

Defined in Zydis.AddressWidth

Storable Decoder Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstruction Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionAvx Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionAvxMask Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionAvxBroadcast Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionMeta Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRaw Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawPrefix Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawRex Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawXop Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawVex Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawEvex Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawMvex Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionModRm Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawSib Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawDisp Source # 
Instance details

Defined in Zydis.Types

Storable DecodedInstructionRawImmediate Source # 
Instance details

Defined in Zydis.Types

(Storable a, Integral a) => Storable (Ratio a)

Since: base-4.8.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

peekElemOff :: Ptr (Ratio a) -> Int -> IO (Ratio a) #

pokeElemOff :: Ptr (Ratio a) -> Int -> Ratio a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ratio a) #

pokeByteOff :: Ptr b -> Int -> Ratio a -> IO () #

peek :: Ptr (Ratio a) -> IO (Ratio a) #

poke :: Ptr (Ratio a) -> Ratio a -> IO () #

Storable (StablePtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: StablePtr a -> Int #

alignment :: StablePtr a -> Int #

peekElemOff :: Ptr (StablePtr a) -> Int -> IO (StablePtr a) #

pokeElemOff :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (StablePtr a) #

pokeByteOff :: Ptr b -> Int -> StablePtr a -> IO () #

peek :: Ptr (StablePtr a) -> IO (StablePtr a) #

poke :: Ptr (StablePtr a) -> StablePtr a -> IO () #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () #

peek :: Ptr (Ptr a) -> IO (Ptr a) #

poke :: Ptr (Ptr a) -> Ptr a -> IO () #

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

Storable a => Storable (Only a) 
Instance details

Defined in Data.Vector.Fixed

Methods

sizeOf :: Only a -> Int #

alignment :: Only a -> Int #

peekElemOff :: Ptr (Only a) -> Int -> IO (Only a) #

pokeElemOff :: Ptr (Only a) -> Int -> Only a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Only a) #

pokeByteOff :: Ptr b -> Int -> Only a -> IO () #

peek :: Ptr (Only a) -> IO (Only a) #

poke :: Ptr (Only a) -> Only a -> IO () #

Enum a => Storable (StorableExt a) Source # 
Instance details

Defined in Zydis.Util

(Arity n, Storable a) => Storable (Vec n a) 
Instance details

Defined in Data.Vector.Fixed.Storable

Methods

sizeOf :: Vec n a -> Int #

alignment :: Vec n a -> Int #

peekElemOff :: Ptr (Vec n a) -> Int -> IO (Vec n a) #

pokeElemOff :: Ptr (Vec n a) -> Int -> Vec n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Vec n a) #

pokeByteOff :: Ptr b -> Int -> Vec n a -> IO () #

peek :: Ptr (Vec n a) -> IO (Vec n a) #

poke :: Ptr (Vec n a) -> Vec n a -> IO () #

(Storable a, Arity n) => Storable (VecList n a) 
Instance details

Defined in Data.Vector.Fixed

Methods

sizeOf :: VecList n a -> Int #

alignment :: VecList n a -> Int #

peekElemOff :: Ptr (VecList n a) -> Int -> IO (VecList n a) #

pokeElemOff :: Ptr (VecList n a) -> Int -> VecList n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (VecList n a) #

pokeByteOff :: Ptr b -> Int -> VecList n a -> IO () #

peek :: Ptr (VecList n a) -> IO (VecList n a) #

poke :: Ptr (VecList n a) -> VecList n a -> IO () #