Copyright | (c) Alexis Williams 2019 |
---|---|
License | MPL-2.0 |
Maintainer | alexis@typedr.at |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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 :: (Traversable t, Storable a) => t a -> ContT r IO (Ptr a)
- allocaArray0 :: Storable a => Int -> ContT r IO (Ptr a)
- allocaArrayWith0 :: (Traversable t, Storable a) => t a -> a -> 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
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 :: (Traversable t, Storable a) => t 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
.
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 :: (Traversable t, Storable a) => t a -> a -> ContT r IO (Ptr a) Source #
allocaArrayWith
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
.
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 #
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 withCString :: String -> ContT r IO CString Source # withCStringLen :: String -> ContT r IO CStringLen Source # | |
ToCString ShortByteString Source # | |
Defined in Foreign.Marshal.ContT withCString :: ShortByteString -> ContT r IO CString Source # withCStringLen :: ShortByteString -> ContT r IO CStringLen Source # | |
ToCString ByteString Source # | |
Defined in Foreign.Marshal.ContT withCString :: ByteString -> ContT r IO CString Source # withCStringLen :: ByteString -> ContT r IO CStringLen Source # |