base-4.1.0.0: Basic librariesSource codeContentsIndex
Foreign.Marshal.Utils
Portabilityportable
Stabilityprovisional
Maintainerffi@haskell.org
Contents
General marshalling utilities
Combined allocation and marshalling
Marshalling of Boolean values (non-zero corresponds to True)
Marshalling of Maybe values
Marshalling lists of storable objects
Haskellish interface to memcpy and memmove
Description
Utilities for primitive marshaling
Synopsis
with :: Storable a => a -> (Ptr a -> IO b) -> IO b
new :: Storable a => a -> IO (Ptr a)
fromBool :: Num a => Bool -> a
toBool :: Num a => a -> Bool
maybeNew :: (a -> IO (Ptr a)) -> Maybe a -> IO (Ptr a)
maybeWith :: (a -> (Ptr b -> IO c) -> IO c) -> Maybe a -> (Ptr b -> IO c) -> IO c
maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
copyBytes :: Ptr a -> Ptr a -> Int -> IO ()
moveBytes :: Ptr a -> Ptr a -> Int -> IO ()
General marshalling utilities
Combined allocation and marshalling
with :: Storable a => a -> (Ptr a -> IO b) -> IO bSource

with val f executes the computation f, passing as argument a pointer to a temporarily allocated block of memory into which val has been marshalled (the combination of alloca and poke).

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.

new :: Storable a => a -> IO (Ptr a)Source

Allocate a block of memory and marshal a value into it (the combination of malloc and poke). The size of the area allocated is determined by the Foreign.Storable.sizeOf method from the instance of Storable for the appropriate type.

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

Marshalling of Boolean values (non-zero corresponds to True)
fromBool :: Num a => Bool -> aSource
Convert a Haskell Bool to its numeric representation
toBool :: Num a => a -> BoolSource
Convert a Boolean in numeric representation to a Haskell value
Marshalling of Maybe values
maybeNew :: (a -> IO (Ptr a)) -> Maybe a -> IO (Ptr a)Source

Allocate storage and marshall a storable value wrapped into a Maybe

maybeWith :: (a -> (Ptr b -> IO c) -> IO c) -> Maybe a -> (Ptr b -> IO c) -> IO cSource
Converts a withXXX combinator into one marshalling a value wrapped into a Maybe, using nullPtr to represent Nothing.
maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)Source
Convert a peek combinator into a one returning Nothing if applied to a nullPtr
Marshalling lists of storable objects
withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> resSource
Replicates a withXXX combinator over a list of objects, yielding a list of marshalled objects
Haskellish interface to memcpy and memmove
(argument order: destination, source)
copyBytes :: Ptr a -> Ptr a -> Int -> IO ()Source
Copies the given number of bytes from the second area (source) into the first (destination); the copied areas may not overlap
moveBytes :: Ptr a -> Ptr a -> Int -> IO ()Source
Copies the given number of bytes from the second area (source) into the first (destination); the copied areas may overlap
Produced by Haddock version 2.4.2