| Maintainer | Bas van Dijk <v.dijk.bas@gmail.com> |
|---|
Foreign.Marshal.Utils.Region
Contents
Description
- with :: (Storable α, MonadControlIO pr) => α -> (forall sl. LocalPtr α (LocalRegion sl s) -> RegionT (Local s) pr β) -> RegionT s pr β
- new :: (Storable α, MonadControlIO pr) => α -> RegionT s pr (RegionalPtr α (RegionT s pr))
- fromBool :: Num a => Bool -> a
- toBool :: Num a => a -> Bool
- data MaybePointer α pointer β r where
- NullPointer :: MaybePointer α (NullPtr β RootRegion) β RootRegion
- JustPointer :: α -> MaybePointer α (RegionalPtr β r) β r
- maybeNew :: Monad m => (α -> m (RegionalPtr β r)) -> MaybePointer α pointer β r -> m pointer
- maybeWith :: (α -> (pointer -> m γ) -> m γ) -> MaybePointer α pointer β r -> (pointer -> m γ) -> m γ
- class MaybePeek pointer where
- maybePeek :: Applicative m => (pointer α r -> m β) -> pointer α r -> m (Maybe β)
- withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
- copyBytes :: (AllocatedPointer pointer1, AllocatedPointer pointer2, AncestorRegion pr1 cr, AncestorRegion pr2 cr, MonadIO cr) => pointer1 α pr1 -> pointer2 α pr2 -> Int -> cr ()
- moveBytes :: (AllocatedPointer pointer1, AllocatedPointer pointer2, AncestorRegion pr1 cr, AncestorRegion pr2 cr, MonadIO cr) => pointer1 α pr1 -> pointer2 α pr2 -> Int -> cr ()
General marshalling utilities
Combined allocation and marshalling
Arguments
| :: (Storable α, MonadControlIO pr) | |
| => α | |
| -> (forall sl. LocalPtr α (LocalRegion sl s) -> RegionT (Local s) pr β) | |
| -> RegionT s pr β |
executes the computation with val ff, 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
Marshalling of Boolean values (non-zero corresponds to True)
Marshalling of MaybePointer values
data MaybePointer α pointer β r whereSource
A corresponds to a MaybePointer α
but additionally introduces some type equalities to the type-checker.
Maybe α
Constructors
| NullPointer :: MaybePointer α (NullPtr β RootRegion) β RootRegion | |
| JustPointer :: α -> MaybePointer α (RegionalPtr β r) β r |
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.
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
Arguments
| :: Applicative m | |
| => (pointer α r -> m β) | |
| -> pointer α r -> m (Maybe β) |
Instances
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)
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
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