Copyright | (c) Alexis Williams 2019 |
---|---|
License | MPL-2.0 |
Maintainer | alexis@typedr.at |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Foreign.Marshal.Codensity
Contents
Description
This library wraps the standard base
bracketed allocation primitives (along
with those from Data.ByteString and Data.ByteString.Short) in a
Codensity
-based interface to ease the chaining of complex marshalling
operations.
Synopsis
- alloca :: Storable a => Codensity IO (Ptr a)
- allocaWith :: Storable a => a -> Codensity IO (Ptr a)
- allocaBytes :: Int -> Codensity IO (Ptr a)
- allocaBytesAligned :: Int -> Int -> Codensity IO (Ptr a)
- calloc :: forall a. Storable a => Codensity IO (Ptr a)
- callocBytes :: Int -> Codensity IO (Ptr a)
- allocaArray :: Storable a => Int -> Codensity IO (Ptr a)
- allocaArrayWith :: (Foldable f, Storable a) => f a -> Codensity IO (Ptr a)
- allocaArrayWithOf :: Storable a => Fold s a -> s -> Codensity IO (Ptr a)
- allocaArray0 :: Storable a => Int -> Codensity IO (Ptr a)
- allocaArrayWith0 :: (Foldable f, Storable a) => f a -> a -> Codensity IO (Ptr a)
- allocaArrayWith0Of :: Storable a => Fold s a -> s -> a -> Codensity IO (Ptr a)
- callocArray :: forall a. Storable a => Int -> Codensity IO (Ptr a)
- callocArray0 :: forall a. Storable a => Int -> Codensity IO (Ptr a)
- withForeignPtr :: ForeignPtr a -> Codensity IO (Ptr a)
- bracketCodensity :: (a -> IO b) -> (a -> IO c) -> Codensity IO a -> Codensity IO a
- class ToCString a where
- withCString :: a -> Codensity IO CString
- withCStringLen :: a -> Codensity IO CStringLen
- type CString = Ptr CChar
- type CStringLen = (Ptr CChar, Int)
- data Ptr a
- nullPtr :: Ptr a
- newtype Codensity (m :: k -> TYPE rep) a :: forall k (rep :: RuntimeRep). (k -> TYPE rep) -> Type -> Type = Codensity {
- runCodensity :: forall (b :: k). (a -> m b) -> m b
- lowerCodensity :: Applicative f => Codensity f a -> f a
- 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 -> Codensity IO b) -> f a -> Codensity IO (Ptr b)
- allocaArrayWithOf' :: Storable b => Fold s a -> (a -> Codensity IO b) -> s -> Codensity IO (Ptr b)
- iallocaArrayWith' :: (FoldableWithIndex i f, Storable b) => (i -> a -> Codensity IO b) -> f a -> Codensity IO (Ptr b)
- iallocaArrayWithOf' :: Storable b => AnIndexedFold i s a -> (i -> a -> Codensity IO b) -> s -> Codensity IO (Ptr b)
- allocaArrayWith0' :: (Foldable f, Storable b) => (a -> Codensity IO b) -> f a -> b -> Codensity IO (Ptr b)
- allocaArrayWith0Of' :: Storable b => Fold s a -> (a -> Codensity IO b) -> s -> b -> Codensity IO (Ptr b)
- iallocaArrayWith0' :: (FoldableWithIndex i f, Storable b) => (i -> a -> Codensity IO b) -> f a -> b -> Codensity IO (Ptr b)
- iallocaArrayWith0Of' :: Storable b => AnIndexedFold i s a -> (i -> a -> Codensity IO b) -> s -> b -> Codensity IO (Ptr b)
alloca
alloca :: Storable a => Codensity IO (Ptr a) Source #
alloca
@a
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 -> Codensity 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 -> Codensity 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 -> Codensity 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 a. Storable a => Codensity IO (Ptr a) Source #
calloc
@a
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 -> Codensity 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 -> Codensity 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 -> Codensity 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 -> Codensity 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 -> Codensity 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 -> Codensity 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 -> a -> Codensity 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 :: forall a. Storable a => Int -> Codensity IO (Ptr a) Source #
callocArray
@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 :: forall a. Storable a => Int -> Codensity 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
(and alternatives)
withForeignPtr :: ForeignPtr a -> Codensity IO (Ptr a) Source #
withForeignPtr
ptr
is a continuation that provides safe access to the
backing pointer of ptr
.
bracketCodensity :: (a -> IO b) -> (a -> IO c) -> Codensity IO a -> Codensity IO a Source #
bracketCodensity
allows one to add initialization and finalization hooks to
an existing Codensity
that will be executed even in cases where an exception
occurs.
This provides an alternative to ForeignPtr
s when the pointer will only
be used in code that is written with this library in mind.
ToCString
class ToCString a where Source #
Methods
withCString :: a -> Codensity IO CString Source #
withCString
a
is a continuation that provides access to a
as a
CString
.
withCStringLen :: a -> Codensity IO CStringLen Source #
withCStringLen
a
is a continuation that provides access to a
as a
CStringLen
.
Instances
ToCString String Source # | |
Defined in Foreign.Marshal.Codensity Methods withCString :: String -> Codensity IO CString Source # withCStringLen :: String -> Codensity IO CStringLen Source # | |
ToCString ShortByteString Source # | |
Defined in Foreign.Marshal.Codensity Methods withCString :: ShortByteString -> Codensity IO CString Source # withCStringLen :: ShortByteString -> Codensity IO CStringLen Source # | |
ToCString ByteString Source # | |
Defined in Foreign.Marshal.Codensity Methods withCString :: ByteString -> Codensity IO CString Source # withCStringLen :: ByteString -> Codensity IO CStringLen Source # |
Reexports
type CStringLen = (Ptr CChar, Int) #
A string with explicit length information in bytes instead of a terminating NUL (allowing NUL characters in the middle of the string).
A value of type
represents a pointer to an object, or an
array of objects, which may be marshalled to or from Haskell values
of type Ptr
aa
.
The type a
will often be an instance of class
Storable
which provides the marshalling operations.
However this is not essential, and you can provide your own operations
to access the pointer. For example you might write small foreign
functions to get or set the fields of a C struct
.
Instances
Generic1 (URec (Ptr ()) :: k -> Type) | |
Eq (Ptr a) | Since: base-2.1 |
Ord (Ptr a) | Since: base-2.1 |
Show (Ptr a) | Since: base-2.1 |
Storable (Ptr a) | Since: base-2.1 |
Functor (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
Foldable (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => URec (Ptr ()) m -> m # foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m # foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b # foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b # foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b # foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b # foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a # foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a # toList :: URec (Ptr ()) a -> [a] # null :: URec (Ptr ()) a -> Bool # length :: URec (Ptr ()) a -> Int # elem :: Eq a => a -> URec (Ptr ()) a -> Bool # maximum :: Ord a => URec (Ptr ()) a -> a # minimum :: Ord a => URec (Ptr ()) a -> a # | |
Traversable (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable Methods traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) # | |
Eq (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Ord (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Defined in GHC.Generics Methods compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
Generic (URec (Ptr ()) p) | |
data URec (Ptr ()) (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec (Ptr ()) :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
newtype Codensity (m :: k -> TYPE rep) a :: forall k (rep :: RuntimeRep). (k -> TYPE rep) -> Type -> Type #
is the Monad generated by taking the right Kan extension
of any Codensity
fFunctor
f
along itself (Ran f f
).
This can often be more "efficient" to construct than f
itself using
repeated applications of (>>=)
.
See "Asymptotic Improvement of Computations over Free Monads" by Janis Voigtländer for more information about this type.
https://www.janis-voigtlaender.eu/papers/AsymptoticImprovementOfComputationsOverFreeMonads.pdf
Constructors
Codensity | |
Fields
|
Instances
MonadReader r m => MonadReader r (Codensity m) | |
MonadReader r m => MonadState r (Codensity m) | |
(Functor f, MonadFree f m) => MonadFree f (Codensity m) | |
Defined in Control.Monad.Codensity | |
MonadTrans (Codensity :: (Type -> Type) -> Type -> Type) | |
Defined in Control.Monad.Codensity | |
Monad (Codensity f) | |
Functor (Codensity k) | |
MonadFail f => MonadFail (Codensity f) | |
Defined in Control.Monad.Codensity | |
Applicative (Codensity f) | |
Defined in Control.Monad.Codensity | |
MonadIO m => MonadIO (Codensity m) | |
Defined in Control.Monad.Codensity | |
Alternative v => Alternative (Codensity v) | |
Alternative v => MonadPlus (Codensity v) | |
Apply (Codensity f) | |
Plus v => Plus (Codensity v) | |
Defined in Control.Monad.Codensity | |
Alt v => Alt (Codensity v) | |
lowerCodensity :: Applicative f => Codensity f a -> f a #
This serves as the *left*-inverse (retraction) of lift
.
lowerCodensity
.lift
≡id
In general this is not a full 2-sided inverse, merely a retraction, as
is often considerably "larger" than Codensity
mm
.
e.g.
could support a full complement of Codensity
((->) s)) a ~ forall r. (a -> s -> r) -> s -> r
actions, while MonadState
s(->) s
is limited to
actions.MonadReader
s
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 -> Codensity IO b) -> f a -> Codensity IO (Ptr b) Source #
allocaArrayWithOf' :: Storable b => Fold s a -> (a -> Codensity IO b) -> s -> Codensity IO (Ptr b) Source #
iallocaArrayWith' :: (FoldableWithIndex i f, Storable b) => (i -> a -> Codensity IO b) -> f a -> Codensity IO (Ptr b) Source #
iallocaArrayWithOf' :: Storable b => AnIndexedFold i s a -> (i -> a -> Codensity IO b) -> s -> Codensity IO (Ptr b) Source #
allocaArrayWith0' :: (Foldable f, Storable b) => (a -> Codensity IO b) -> f a -> b -> Codensity IO (Ptr b) Source #
allocaArrayWith0Of' :: Storable b => Fold s a -> (a -> Codensity IO b) -> s -> b -> Codensity IO (Ptr b) Source #
iallocaArrayWith0' :: (FoldableWithIndex i f, Storable b) => (i -> a -> Codensity IO b) -> f a -> b -> Codensity IO (Ptr b) Source #
iallocaArrayWith0Of' :: Storable b => AnIndexedFold i s a -> (i -> a -> Codensity IO b) -> s -> b -> Codensity IO (Ptr b) Source #