regional-pointers-0.6.0.1: Regional memory pointers

MaintainerBas van Dijk <v.dijk.bas@gmail.com>

Foreign.Marshal.Utils.Region

Contents

Description

 

Synopsis

General marshalling utilities

Combined allocation and marshalling

withSource

Arguments

:: (Storable α, MonadControlIO pr) 
=> α 
-> (forall sl. LocalPtr α (LocalRegion sl s) -> RegionT (Local s) pr β) 
-> RegionT s pr β 

with val f executes the computation f, passing as argument a regional 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).

This provides a safer replacement for Foreign.Marshal.Utils.with.

new :: (Storable α, MonadControlIO pr) => α -> RegionT s pr (RegionalPtr α (RegionT s pr))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.

This provides a safer replacement for Foreign.Marshal.Utils.new.

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

fromBool :: Num a => Bool -> a

Convert a Haskell Bool to its numeric representation

toBool :: Num a => a -> Bool

Convert a Boolean in numeric representation to a Haskell value

Marshalling of MaybePointer values

data MaybePointer α pointer β r whereSource

A MaybePointer α corresponds to a Maybe α but additionally introduces some type equalities to the type-checker.

Constructors

NullPointer :: MaybePointer α (NullPtr β RootRegion) β RootRegion 
JustPointer :: α -> MaybePointer α (RegionalPtr β r) β r 

maybeNewSource

Arguments

:: Monad m 
=> (α -> m (RegionalPtr β r)) 
-> MaybePointer α pointer β r -> m pointer 

Allocate storage and marshal a storable value wrapped into a MaybePointer.

The nullPtr is used to represent NullPointer.

Alternative for maybeNew.

maybeWithSource

Arguments

:: (α -> (pointer -> m γ) -> m γ) 
-> MaybePointer α pointer β r -> (pointer -> m γ) -> m γ 

Converts a withXXX combinator into one marshalling a value wrapped into a MaybePointer, using nullPtr to represent NoPointer.

Alternative for maybeWith

class MaybePeek pointer whereSource

Methods

maybePeekSource

Arguments

:: Applicative m 
=> (pointer α r -> m β) 
-> pointer α r -> m (Maybe β) 

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

Alternative for maybePeek.

Marshalling lists of storable objects

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

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)

copyBytesSource

Arguments

:: (AllocatedPointer pointer1, AllocatedPointer pointer2, AncestorRegion pr1 cr, AncestorRegion pr2 cr, MonadIO cr) 
=> pointer1 α pr1

Destination

-> pointer2 α pr2

Source

-> Int

Number of bytes to copy

-> cr () 

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

Wraps: Foreign.Marshal.Utils.copyBytes.

moveBytesSource

Arguments

:: (AllocatedPointer pointer1, AllocatedPointer pointer2, AncestorRegion pr1 cr, AncestorRegion pr2 cr, MonadIO cr) 
=> pointer1 α pr1

Destination

-> pointer2 α pr2

Source

-> Int

Number of bytes to move

-> cr () 

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

Wraps: Foreign.Marshal.Utils.moveBytes.