Copyright | (c) Alexis Williams 2019 |
---|---|
License | MPL-2.0 |
Maintainer | alexis@typedr.at |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Foreign.Marshal.ContT
Description
This library wraps the standard base
bracketed allocation primitives (along
with those from ByteString
) in a ContT
-based interface to ease the
chaining of complex marshalling operations.
Synopsis
- alloca :: Storable a => ContT r IO (Ptr a)
- allocaWith :: Storable a => a -> ContT r IO (Ptr a)
- allocaBytes :: Int -> ContT r IO (Ptr a)
- allocaBytesAligned :: Int -> Int -> ContT r IO (Ptr a)
- calloc :: forall r a. Storable a => ContT r IO (Ptr a)
- callocBytes :: Int -> ContT r IO (Ptr a)
- allocaArray :: Storable a => Int -> ContT r IO (Ptr a)
- allocaArrayWith :: (Foldable f, Storable a) => f a -> ContT r IO (Ptr a)
- allocaArrayWithOf :: Storable a => Fold s a -> s -> ContT r IO (Ptr a)
- allocaArray0 :: Storable a => Int -> ContT r IO (Ptr a)
- allocaArrayWith0 :: (Foldable f, Storable a) => f a -> a -> ContT r IO (Ptr a)
- allocaArrayWith0Of :: Storable a => Fold s a -> s -> ContT r IO (Ptr a)
- callocArray :: Storable a => Int -> ContT r IO (Ptr a)
- callocArray0 :: Storable a => Int -> ContT r IO (Ptr a)
- withForeignPtr :: ForeignPtr a -> ContT r IO (Ptr a)
- class ToCString a where
- withCString :: a -> ContT r IO CString
- withCStringLen :: a -> ContT r IO CStringLen
- type AnIndexedFold i s a = forall m p. Indexable i p => p a (Const m a) -> s -> Const m s
- allocaArrayWith' :: (Foldable f, Storable b) => (a -> ContT r IO b) -> f a -> ContT r IO (Ptr b)
- allocaArrayWithOf' :: Storable b => Fold s a -> (a -> ContT r IO b) -> s -> ContT r IO (Ptr b)
- iallocaArrayWith' :: (FoldableWithIndex i f, Storable b) => (i -> a -> ContT r IO b) -> f a -> ContT r IO (Ptr b)
- iallocaArrayWithOf' :: Storable b => AnIndexedFold i s a -> (i -> a -> ContT r IO b) -> s -> ContT r IO (Ptr b)
- allocaArrayWith0' :: (Foldable f, Storable b) => (a -> ContT r IO b) -> f a -> b -> ContT r IO (Ptr b)
- allocaArrayWith0Of' :: Storable b => Fold s a -> (a -> ContT r IO b) -> s -> b -> ContT r IO (Ptr b)
- iallocaArrayWith0' :: (FoldableWithIndex i f, Storable b) => (i -> a -> ContT r IO b) -> f a -> b -> ContT r IO (Ptr b)
- iallocaArrayWith0Of' :: Storable b => AnIndexedFold i s a -> (i -> a -> ContT r IO b) -> s -> b -> ContT r IO (Ptr b)
alloca
alloca :: Storable a => ContT r IO (Ptr a) Source #
alloca
is a continuation that provides access to a pointer into a
temporary block of memory sufficient to hold values of type a
.
allocaWith :: Storable a => a -> ContT r IO (Ptr a) Source #
allocaWith
a
is a continuation that provides access to a pointer into
a temporary block of memory containing a
.
allocaBytes :: Int -> ContT r IO (Ptr a) Source #
allocaBytes
n
is a continuation that provides access to a pointer into
a temporary block of memory sufficient to hold n
bytes, with
machine-standard alignment.
allocaBytesAligned :: Int -> Int -> ContT r IO (Ptr a) Source #
allocaBytesAligned
n
a
is a continuation that provides access to a
pointer into a temporary block of memory sufficient to hold n
bytes,
with a
-byte alignment.
calloc
calloc :: forall r a. Storable a => ContT r IO (Ptr a) Source #
calloc
is a continuation that provides access to a pointer into a
temporary block of zeroed memory sufficient to hold values of type a
.
callocBytes :: Int -> ContT r IO (Ptr a) Source #
callocBytes
n
is a continuation that provides access to a pointer into
a temporary block of zeroed memory sufficient to hold n
bytes, with
machine-standard alignment.
allocaArray
allocaArray :: Storable a => Int -> ContT r IO (Ptr a) Source #
allocaArray
@a
n
is a continuation that provides access to a
pointer into a temporary block of memory sufficient to hold n
values of
type a
.
allocaArrayWith :: (Foldable f, Storable a) => f a -> ContT r IO (Ptr a) Source #
allocaArrayWith
xs
is a continuation that provides access to a
pointer into a temporary block of memory containing the values of xs
.
allocaArrayWithOf :: Storable a => Fold s a -> s -> ContT r IO (Ptr a) Source #
allocaArrayWithOf
f
works in the same way as allocaArrayWith
, but
using the Fold
f
rather than any Foldable
instance.
allocaArray0 :: Storable a => Int -> ContT r IO (Ptr a) Source #
allocaArray0
@a
n
is a continuation that provides access to a
pointer into a temporary block of memory sufficient to hold n
values of
type a
, along with a final terminal element.
allocaArrayWith0 :: (Foldable f, Storable a) => f a -> a -> ContT r IO (Ptr a) Source #
allocaArrayWith0
xs
end
is a continuation that provides access to a
pointer into a temporary block of memory containing the values of xs
,
terminated with end
.
allocaArrayWith0Of :: Storable a => Fold s a -> s -> ContT r IO (Ptr a) Source #
allocaArrayWith0Of
t
works in the same way as allocaArrayWith0
, but
using the Fold
t
rather than any Foldable
instance.
callocArray
callocArray :: Storable a => Int -> ContT r IO (Ptr a) Source #
callocArray0
@a
n
is a continuation that provides access to a
pointer into a temporary block of zeroed memory sufficient to hold n
values of type a
.
callocArray0 :: Storable a => Int -> ContT r IO (Ptr a) Source #
callocArray0
@a
n
is a continuation that provides access to a
pointer into a temporary block of zeroed memory sufficient to hold n
values of type a
, along with a final terminal element.
withForeignPtr
withForeignPtr :: ForeignPtr a -> ContT r IO (Ptr a) Source #
withForeignPtr
ptr
is a continuation that provides safe access to the
backing pointer of ptr
.
ToCString
class ToCString a where Source #
Methods
withCString :: a -> ContT r IO CString Source #
withCString
a
is a continuation that provides access to a
as a
CString
.
withCStringLen :: a -> ContT r IO CStringLen Source #
withCStringLen
a
is a continuation that provides access to a
as a
CStringLen
.
Instances
ToCString String Source # | |
Defined in Foreign.Marshal.ContT Methods withCString :: String -> ContT r IO CString Source # withCStringLen :: String -> ContT r IO CStringLen Source # | |
ToCString ShortByteString Source # | |
Defined in Foreign.Marshal.ContT Methods withCString :: ShortByteString -> ContT r IO CString Source # withCStringLen :: ShortByteString -> ContT r IO CStringLen Source # | |
ToCString ByteString Source # | |
Defined in Foreign.Marshal.ContT Methods withCString :: ByteString -> ContT r IO CString Source # withCStringLen :: ByteString -> ContT r IO CStringLen Source # |
Projected variants
These variants work in the same way as their corresponding functions
without the terminal prime, but with a function argument that projects
the results of the (possibly implicit) Fold
into a Storable
value.
As in the lens
library, the variants beginning with an i
use
IndexedFold
s rather than Fold
s, and no versions without terminal
primes exist because there is no generic enough use for indexes to
give a sensible default.
type AnIndexedFold i s a = forall m p. Indexable i p => p a (Const m a) -> s -> Const m s Source #
A generic IndexedFold
or equivalent, taking an IndexedGetter
,
IndexedFold
(obviously), IndexedTraversal
, or IndexedLens
.
allocaArrayWith' :: (Foldable f, Storable b) => (a -> ContT r IO b) -> f a -> ContT r IO (Ptr b) Source #
allocaArrayWithOf' :: Storable b => Fold s a -> (a -> ContT r IO b) -> s -> ContT r IO (Ptr b) Source #
iallocaArrayWith' :: (FoldableWithIndex i f, Storable b) => (i -> a -> ContT r IO b) -> f a -> ContT r IO (Ptr b) Source #
iallocaArrayWithOf' :: Storable b => AnIndexedFold i s a -> (i -> a -> ContT r IO b) -> s -> ContT r IO (Ptr b) Source #
allocaArrayWith0' :: (Foldable f, Storable b) => (a -> ContT r IO b) -> f a -> b -> ContT r IO (Ptr b) Source #
allocaArrayWith0Of' :: Storable b => Fold s a -> (a -> ContT r IO b) -> s -> b -> ContT r IO (Ptr b) Source #
iallocaArrayWith0' :: (FoldableWithIndex i f, Storable b) => (i -> a -> ContT r IO b) -> f a -> b -> ContT r IO (Ptr b) Source #
iallocaArrayWith0Of' :: Storable b => AnIndexedFold i s a -> (i -> a -> ContT r IO b) -> s -> b -> ContT r IO (Ptr b) Source #