libffi-dynamic-0.0.0.2: LibFFI interface with dynamic bidirectional type-driven binding generation

Safe HaskellNone
LanguageHaskell98

Foreign.LibFFI.Dynamic.CIF

Documentation

newtype ABI Source #

Constructors

ABI CInt 
Instances
Eq ABI Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

(==) :: ABI -> ABI -> Bool #

(/=) :: ABI -> ABI -> Bool #

Ord ABI Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

compare :: ABI -> ABI -> Ordering #

(<) :: ABI -> ABI -> Bool #

(<=) :: ABI -> ABI -> Bool #

(>) :: ABI -> ABI -> Bool #

(>=) :: ABI -> ABI -> Bool #

max :: ABI -> ABI -> ABI #

min :: ABI -> ABI -> ABI #

Show ABI Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

showsPrec :: Int -> ABI -> ShowS #

show :: ABI -> String #

showList :: [ABI] -> ShowS #

Storable ABI Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

sizeOf :: ABI -> Int #

alignment :: ABI -> Int #

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

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

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

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

peek :: Ptr ABI -> IO ABI #

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

Hashable ABI Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

hashWithSalt :: Int -> ABI -> Int #

hash :: ABI -> Int #

newtype SomeCIF Source #

Constructors

SomeCIF (Ptr SomeCIF) 
Instances
Eq SomeCIF Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

(==) :: SomeCIF -> SomeCIF -> Bool #

(/=) :: SomeCIF -> SomeCIF -> Bool #

Ord SomeCIF Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Show SomeCIF Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Interned SomeCIF Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Associated Types

data Description SomeCIF :: Type #

type Uninterned SomeCIF :: Type #

Eq (Description SomeCIF) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Show (Description SomeCIF) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Hashable (Description SomeCIF) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

type Uninterned SomeCIF Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

data Description SomeCIF Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

newtype CIF a Source #

Constructors

CIF SomeCIF 
Instances
Eq (CIF a) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

(==) :: CIF a -> CIF a -> Bool #

(/=) :: CIF a -> CIF a -> Bool #

Ord (CIF a) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

compare :: CIF a -> CIF a -> Ordering #

(<) :: CIF a -> CIF a -> Bool #

(<=) :: CIF a -> CIF a -> Bool #

(>) :: CIF a -> CIF a -> Bool #

(>=) :: CIF a -> CIF a -> Bool #

max :: CIF a -> CIF a -> CIF a #

min :: CIF a -> CIF a -> CIF a #

Show (CIF a) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Methods

showsPrec :: Int -> CIF a -> ShowS #

show :: CIF a -> String #

showList :: [CIF a] -> ShowS #

cif :: SigType t => CIF t Source #

class SigType t Source #

Minimal complete definition

retTypeOf', argTypesOf'

Instances
FFIType t => SigType (IO t) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Associated Types

type SigReturn (IO t) :: Type Source #

Methods

retTypeOf' :: p (IO t) -> SomeType

argTypesOf' :: p (IO t) -> [SomeType]

(FFIType a, SigType b) => SigType (a -> b) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

Associated Types

type SigReturn (a -> b) :: Type Source #

Methods

retTypeOf' :: p (a -> b) -> SomeType

argTypesOf' :: p (a -> b) -> [SomeType]

type family SigReturn t Source #

Instances
type SigReturn (IO t) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

type SigReturn (IO t) = t
type SigReturn (a -> b) Source # 
Instance details

Defined in Foreign.LibFFI.Dynamic.CIF

type SigReturn (a -> b) = SigReturn b

call :: SigType t => FunPtr t -> Ptr (SigReturn t) -> Ptr (Ptr ()) -> IO () Source #

callWithABI :: SigType t => ABI -> FunPtr t -> Ptr (SigReturn t) -> Ptr (Ptr ()) -> IO () Source #

callWithCIF :: CIF a -> FunPtr a -> Ptr (SigReturn a) -> Ptr (Ptr ()) -> IO () Source #