c-storable-0.2: CStorable class

Safe HaskellNone
LanguageHaskell98

ForeignC

Contents

Description

This is a drop-in replacement for Foreign and Foreign.C. The difference is that it uses a CStorable class instead of Storable, and only C types are in CStorable. Otherwise, it's easy to corrupt memory by accidentally marshalling a haskell type into a C struct.

It tries to export all the same things that Foreign and Foreign.C do, but because I only copied the things I need, it's not complete.

Synopsis

CStorable

class CStorable a where Source #

Minimal complete definition

sizeOf, alignment

Methods

sizeOf :: a -> Int Source #

alignment :: a -> Int Source #

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

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

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

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

peek :: Ptr a -> IO a Source #

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

Instances

CStorable Int8 Source # 
CStorable Int16 Source # 
CStorable Int32 Source # 
CStorable Int64 Source # 
CStorable Word8 Source # 
CStorable Word16 Source # 
CStorable Word32 Source # 
CStorable Word64 Source # 
CStorable CChar Source # 
CStorable CUChar Source # 
CStorable CInt Source # 
CStorable CFloat Source # 
CStorable CDouble Source # 
CStorable (StablePtr a) Source # 
CStorable (Ptr a) Source # 

Methods

sizeOf :: Ptr a -> Int Source #

alignment :: Ptr a -> Int Source #

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

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

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

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

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

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

CStorable (FunPtr a) Source # 

Methods

sizeOf :: FunPtr a -> Int Source #

alignment :: FunPtr a -> Int Source #

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

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

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

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

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

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

basic types

words

ints

ptrs

Foreign.Marshal.Alloc

alloca :: forall a b. CStorable a => (Ptr a -> IO b) -> IO b Source #

Foreign.Marshal.Array

allocaArray :: CStorable a => Int -> (Ptr a -> IO b) -> IO b Source #

pokeArray :: CStorable a => Ptr a -> [a] -> IO () Source #

peekArray :: CStorable a => Int -> Ptr a -> IO [a] Source #

newArray :: CStorable a => [a] -> IO (Ptr a) Source #

withArray :: CStorable a => [a] -> (Ptr a -> IO b) -> IO b Source #

withArrayLen :: CStorable a => [a] -> (Int -> Ptr a -> IO b) -> IO b Source #

withArrayLenNull :: CStorable a => [a] -> (Int -> Ptr a -> IO b) -> IO b Source #

Like withArrayLen, except if the list is null, then pass (0, nullPtr).

copyArray :: CStorable a => Ptr a -> Ptr a -> Int -> IO () Source #

Foreign.Marshal.Utils

with :: CStorable a => a -> (Ptr a -> IO b) -> IO b Source #

module Data.Int

module Data.Word

module Foreign.C