| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Haskus.Binary.Storable
Description
Storable class
Synopsis
- class StaticStorable a where- type SizeOf a :: Nat
- type Alignment a :: Nat
- staticPeekIO :: Ptr a -> IO a
- staticPokeIO :: Ptr a -> a -> IO ()
 
- staticPeek :: (StaticStorable a, MonadIO m) => Ptr a -> m a
- staticPoke :: (StaticStorable a, MonadIO m) => Ptr a -> a -> m ()
- staticSizeOf :: forall a. KnownNat (SizeOf a) => a -> Word
- staticAlignment :: forall a. KnownNat (Alignment a) => a -> Word
- wordBytes :: forall a. (Storable a, KnownNat (SizeOf a)) => a -> [Word8]
- class Storable a where
- peek :: (Storable a, MonadIO m) => Ptr a -> m a
- poke :: (Storable a, MonadIO m) => Ptr a -> a -> m ()
- sizeOf' :: (Integral b, Storable a) => a -> b
- sizeOfT :: forall a. Storable a => Word
- sizeOfT' :: forall a b. (Storable a, Integral b) => b
- alignment' :: (Integral b, Storable a) => a -> b
- alignmentT :: forall a. Storable a => Word
- alignmentT' :: forall a b. (Storable a, Integral b) => b
- peekByteOff :: (MonadIO m, Storable a) => Ptr a -> Int -> m a
- pokeByteOff :: (MonadIO m, Storable a) => Ptr a -> Int -> a -> m ()
- peekElemOff :: forall a m. (MonadIO m, Storable a) => Ptr a -> Int -> m a
- pokeElemOff :: (MonadIO m, Storable a) => Ptr a -> Int -> a -> m ()
- alloca :: forall a b m. (MonadInIO m, Storable a) => (Ptr a -> m b) -> m b
- allocaBytes :: MonadInIO m => Word -> (Ptr a -> m b) -> m b
- allocaBytesAligned :: MonadInIO m => Word -> Word -> (Ptr a -> m b) -> m b
- malloc :: forall a m. (MonadIO m, Storable a) => m (Ptr a)
- with :: (MonadInIO m, Storable a) => a -> (Ptr a -> m b) -> m b
- withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
- allocaArray :: forall a b m. (MonadInIO m, Storable a) => Word -> (Ptr a -> m b) -> m b
- mallocArray :: forall a m. (MonadIO m, Storable a) => Word -> m (Ptr a)
- withArray :: (MonadInIO m, Storable a) => [a] -> (Ptr a -> m b) -> m b
- withArrayLen :: (MonadInIO m, Storable a) => [a] -> (Word -> Ptr a -> m b) -> m b
- peekArray :: (MonadIO m, Storable a) => Word -> Ptr a -> m [a]
- pokeArray :: (MonadIO m, Storable a) => Ptr a -> [a] -> m ()
- type family RequiredPadding a b where ...
- type family Padding (sz :: Nat) b where ...
- type family PaddingEx (m :: Nat) (a :: Nat) where ...
Documentation
class StaticStorable a where Source #
A storable data in constant space whose size is known at compile time
Associated Types
Size of the stored data (in bytes)
type Alignment a :: Nat Source #
Alignment requirement (in bytes)
Methods
staticPeekIO :: Ptr a -> IO a Source #
Peek (read) a value from a memory address
staticPokeIO :: Ptr a -> a -> IO () Source #
Poke (write) a value at the given memory address
Instances
staticPeek :: (StaticStorable a, MonadIO m) => Ptr a -> m a Source #
Peek (read) a value from a memory address
staticPoke :: (StaticStorable a, MonadIO m) => Ptr a -> a -> m () Source #
Poke (write) a value at the given memory address
staticAlignment :: forall a. KnownNat (Alignment a) => a -> Word Source #
Get statically known alignment
wordBytes :: forall a. (Storable a, KnownNat (SizeOf a)) => a -> [Word8] Source #
Get bytes in host-endianness order
Storable
class Storable a where Source #
Storable data-types
Currently we cannot automatically derive a Storable class with type-level naturals for "alignment" and "sizeOf". Instead we define a Storable class isomorphic to the Foreign.Storable's one but with default methods using DefaultSignatures (i.e., the Storable instance can be automatically derived from a Generic instance).
Minimal complete definition
Nothing
Methods
peekIO :: Ptr a -> IO a Source #
peekIO :: (Generic a, GStorable (Rep a)) => Ptr a -> IO a Source #
pokeIO :: Ptr a -> a -> IO () Source #
pokeIO :: (Generic a, GStorable (Rep a)) => Ptr a -> a -> IO () Source #
alignment :: a -> Word Source #
alignment :: (Generic a, GStorable (Rep a)) => a -> Word Source #
sizeOf :: (Generic a, GStorable (Rep a)) => a -> Word Source #
Instances
alignmentT :: forall a. Storable a => Word Source #
Alignment (for type-application)
alignmentT' :: forall a b. (Storable a, Integral b) => b Source #
Alignment' (for type-application)
peekElemOff :: forall a m. (MonadIO m, Storable a) => Ptr a -> Int -> m a Source #
Peek with element size offset
pokeElemOff :: (MonadIO m, Storable a) => Ptr a -> Int -> a -> m () Source #
Poke with element size offset
alloca :: forall a b m. (MonadInIO m, Storable a) => (Ptr a -> m b) -> m b Source #
alloca ff, passing as argument
 a pointer to a temporarily allocated block of memory sufficient to
 hold values of type a.
The memory is freed when f terminates (either normally or via an
 exception), so the pointer passed to f must not be used after this.
allocaBytesAligned :: MonadInIO m => Word -> Word -> (Ptr a -> m b) -> m b Source #
Allocate some aligned bytes
with :: (MonadInIO m, Storable a) => a -> (Ptr a -> m b) -> m b Source #
with val ff, passing as argument
 a 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), so the pointer passed to f must not be used after this.
withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res Source #
Replicates a withXXX combinator over a list of objects, yielding a list of
 marshalled objects
allocaArray :: forall a b m. (MonadInIO m, Storable a) => Word -> (Ptr a -> m b) -> m b Source #
Temporarily allocate space for the given number of elements
 (like alloca, but for multiple elements).
mallocArray :: forall a m. (MonadIO m, Storable a) => Word -> m (Ptr a) Source #
Allocate space for the given number of elements
 (like malloc, but for multiple elements).
withArray :: (MonadInIO m, Storable a) => [a] -> (Ptr a -> m b) -> m b Source #
Temporarily store a list of storable values in memory
 (like with, but for multiple elements).
withArrayLen :: (MonadInIO m, Storable a) => [a] -> (Word -> Ptr a -> m b) -> m b Source #
Like withArray, but the action gets the number of values
 as an additional parameter
peekArray :: (MonadIO m, Storable a) => Word -> Ptr a -> m [a] Source #
Convert an array of given length into a Haskell list. The implementation is tail-recursive and so uses constant stack space.
pokeArray :: (MonadIO m, Storable a) => Ptr a -> [a] -> m () Source #
Write the list elements consecutive into memory
Padding
type family RequiredPadding a b where ... Source #
Compute the required padding between a and b to respect b's alignment
Equations
| RequiredPadding a b = Padding (SizeOf a) b |