c-storable-0.3: CStorable class

Safe HaskellNone
LanguageHaskell2010

ForeignC

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

Documentation

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 # 
Instance details

Defined in ForeignC

CStorable Int16 Source # 
Instance details

Defined in ForeignC

CStorable Int32 Source # 
Instance details

Defined in ForeignC

CStorable Int64 Source # 
Instance details

Defined in ForeignC

CStorable Word8 Source # 
Instance details

Defined in ForeignC

CStorable Word16 Source # 
Instance details

Defined in ForeignC

CStorable Word32 Source # 
Instance details

Defined in ForeignC

CStorable Word64 Source # 
Instance details

Defined in ForeignC

CStorable CChar Source # 
Instance details

Defined in ForeignC

CStorable CUChar Source # 
Instance details

Defined in ForeignC

CStorable CInt Source # 
Instance details

Defined in ForeignC

CStorable CFloat Source # 
Instance details

Defined in ForeignC

CStorable CDouble Source # 
Instance details

Defined in ForeignC

CStorable (StablePtr a) Source # 
Instance details

Defined in ForeignC

CStorable (Ptr a) Source # 
Instance details

Defined in ForeignC

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 # 
Instance details

Defined in ForeignC

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 #

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

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 #

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

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

module Data.Int

module Data.Word

module Foreign.C

free :: Ptr a -> IO () #

Free a block of memory that was allocated with malloc, mallocBytes, realloc, reallocBytes, new or any of the newX functions in Foreign.Marshal.Array or Foreign.C.String.

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

Resize a memory area that was allocated with malloc or mallocBytes to the given size. The returned pointer may refer to an entirely different memory area, but will be sufficiently aligned for any of the basic foreign types that fits into a memory block of the given size. The contents of the referenced memory area will be the same as of the original pointer up to the minimum of the original size and the given size.

If the pointer argument to reallocBytes is nullPtr, reallocBytes behaves like malloc. If the requested size is 0, reallocBytes behaves like free.

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

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

allocaBytes n f executes the computation f, passing as argument a pointer to a temporarily allocated block of memory of n bytes. The block of memory is sufficiently aligned for any of the basic foreign types that fits into a memory block of the allocated size.

The memory is freed when f terminates (either normally or via an exception), so the pointer passed to f must not be used after this.

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

Allocate a block of memory of the given number of bytes. The block of memory is sufficiently aligned for any of the basic foreign types that fits into a memory block of the allocated size.

The memory may be deallocated using free or finalizerFree when no longer required.

finalizerFree :: FinalizerPtr a #

A pointer to a foreign function equivalent to free, which may be used as a finalizer (cf ForeignPtr) for storage allocated with malloc, mallocBytes, realloc or reallocBytes.

fillBytes :: Ptr a -> Word8 -> Int -> IO () #

Fill a given number of bytes in memory area with a byte value.

Since: base-4.8.0.0

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

Copies the given number of bytes from the second area (source) into the first (destination); the copied areas may overlap

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

Copies the given number of bytes from the second area (source) into the first (destination); the copied areas may not overlap

withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res #

Replicates a withXXX combinator over a list of objects, yielding a list of marshalled objects

maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b) #

Convert a peek combinator into a one returning Nothing if applied to a nullPtr

maybeWith :: (a -> (Ptr b -> IO c) -> IO c) -> Maybe a -> (Ptr b -> IO c) -> IO c #

Converts a withXXX combinator into one marshalling a value wrapped into a Maybe, using nullPtr to represent Nothing.

maybeNew :: (a -> IO (Ptr b)) -> Maybe a -> IO (Ptr b) #

Allocate storage and marshal a storable value wrapped into a Maybe

toBool :: (Eq a, Num a) => a -> Bool #

Convert a Boolean in numeric representation to a Haskell value

fromBool :: Num a => Bool -> a #

Convert a Haskell Bool to its numeric representation