base-4.8.1.0: Basic libraries

Copyright(c) The FFI task force 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerffi@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Foreign.Marshal.Utils

Contents

Description

Utilities for primitive marshaling

Synopsis

General marshalling utilities

Combined allocation and marshalling

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

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 sizeOf method from the instance of Storable for the appropriate type.

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

Marshalling of Boolean values (non-zero corresponds to True)

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

Convert a Haskell Bool to its numeric representation

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

Convert a Boolean in numeric representation to a Haskell value

Marshalling of Maybe values

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

Allocate storage and marshal a storable value wrapped into a Maybe

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

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) -> res Source

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

Filling up memory area with required values

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

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

Since: 4.8.0.0