module LibffiTypes where import Foreign import Foreign.C data Ffi_type = Ffi_type { ffi_type'size :: CSize, ffi_type'alignment, ffi_type'type :: CUShort, ffi_type'elements :: Ptr (Ptr Ffi_type) } instance Storable Ffi_type where sizeOf _ = fromIntegral size_of_ffi_type alignment = sizeOf peek p = with 0 $ \p1 -> with 0 $ \p2 -> with 0 $ \p3 -> with nullPtr $ \p4 -> c2hs_ffi_type p p1 p2 p3 p4 >> peek p1 >>= \v1 -> peek p2 >>= \v2 -> peek p3 >>= \v3 -> peek p4 >>= \v4 -> return $ Ffi_type v1 v2 v3 v4 poke p (Ffi_type v1 v2 v3 v4) = hs2c_ffi_type p v1 v2 v3 v4 type Ffi_status = CInt type Ffi_abi = CInt data Ffi_cif = Ffi_cif instance Storable Ffi_cif where sizeOf _ = fromIntegral size_of_ffi_cif alignment = sizeOf peek p = return Ffi_cif poke p v = return () data Ffi_closure foreign import ccall "size_of_ffi_type" size_of_ffi_type :: CInt foreign import ccall "hs2c_ffi_type" hs2c_ffi_type :: Ptr Ffi_type -> CSize -> CUShort -> CUShort -> Ptr (Ptr Ffi_type) -> IO () foreign import ccall "c2hs_ffi_type" c2hs_ffi_type :: Ptr Ffi_type -> Ptr CSize -> Ptr CUShort -> Ptr CUShort -> Ptr (Ptr (Ptr Ffi_type)) -> IO () foreign import ccall "size_of_ffi_cif" size_of_ffi_cif :: CInt