haskus-binary-0.6.0.0: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.Storable

Contents

Description

Storable class

Synopsis

Documentation

class StaticStorable a where Source #

A storable data in constant space whose size is known at compile time

Minimal complete definition

staticPeekIO, staticPokeIO

Associated Types

type SizeOf a :: Nat Source #

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

StaticStorable Int8 Source # 

Associated Types

type SizeOf Int8 :: Nat Source #

type Alignment Int8 :: Nat Source #

StaticStorable Int16 Source # 

Associated Types

type SizeOf Int16 :: Nat Source #

type Alignment Int16 :: Nat Source #

StaticStorable Int32 Source # 

Associated Types

type SizeOf Int32 :: Nat Source #

type Alignment Int32 :: Nat Source #

StaticStorable Int64 Source # 

Associated Types

type SizeOf Int64 :: Nat Source #

type Alignment Int64 :: Nat Source #

StaticStorable Word8 Source # 

Associated Types

type SizeOf Word8 :: Nat Source #

type Alignment Word8 :: Nat Source #

StaticStorable Word16 Source # 
StaticStorable Word32 Source # 
StaticStorable Word64 Source # 
((~) Nat s (FullRecordSize fs), KnownNat s) => StaticStorable (Record fs) Source # 

Associated Types

type SizeOf (Record fs) :: Nat Source #

type Alignment (Record fs) :: Nat Source #

Methods

staticPeekIO :: Ptr (Record fs) -> IO (Record fs) Source #

staticPokeIO :: Ptr (Record fs) -> Record fs -> IO () Source #

(KnownNat (Max (MapSizeOf fs)), KnownNat (Max (MapAlignment fs))) => StaticStorable (Union fs) Source # 

Associated Types

type SizeOf (Union fs) :: Nat Source #

type Alignment (Union fs) :: Nat Source #

Methods

staticPeekIO :: Ptr (Union fs) -> IO (Union fs) Source #

staticPokeIO :: Ptr (Union fs) -> Union fs -> IO () Source #

(ByteReversable a, StaticStorable a) => StaticStorable (AsLittleEndian a) Source # 
(ByteReversable a, StaticStorable a) => StaticStorable (AsBigEndian a) Source # 

Associated Types

type SizeOf (AsBigEndian a) :: Nat Source #

type Alignment (AsBigEndian a) :: Nat Source #

(Integral b, StaticStorable b, CEnum a) => StaticStorable (EnumField b a) Source # 

Associated Types

type SizeOf (EnumField b a) :: Nat Source #

type Alignment (EnumField b a) :: Nat Source #

Methods

staticPeekIO :: Ptr (EnumField b a) -> IO (EnumField b a) Source #

staticPokeIO :: Ptr (EnumField b a) -> EnumField b a -> IO () Source #

KnownNat (* (SizeOf a) n) => StaticStorable (Vector n a) Source # 

Associated Types

type SizeOf (Vector n a) :: Nat Source #

type Alignment (Vector n a) :: Nat Source #

Methods

staticPeekIO :: Ptr (Vector n a) -> IO (Vector n a) Source #

staticPokeIO :: Ptr (Vector n a) -> Vector n a -> IO () Source #

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

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 

type family Padding (sz :: Nat) b where ... Source #

Compute the required padding between the size sz and b to respect b's alignment

Equations

Padding sz b = PaddingEx (Modulo sz (Alignment b)) (Alignment b) 

type family PaddingEx (m :: Nat) (a :: Nat) where ... Source #

Equations

PaddingEx 0 a = 0 
PaddingEx m a = a - m 

staticSizeOf :: forall a. KnownNat (SizeOf a) => a -> Word Source #

Get statically known size

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).

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 :: a -> Word Source #

sizeOf :: (Generic a, GStorable (Rep a)) => a -> Word Source #

Instances

Storable Char Source # 
Storable Double Source # 
Storable Float Source # 
Storable Int Source # 
Storable Int8 Source # 
Storable Int16 Source # 
Storable Int32 Source # 
Storable Int64 Source # 
Storable Word Source # 
Storable Word8 Source # 
Storable Word16 Source # 
Storable Word32 Source # 
Storable Word64 Source # 
Storable WordPtr Source # 
Storable CChar Source # 
Storable CShort Source # 
Storable CUShort Source # 
Storable CInt Source # 
Storable CUInt Source # 
Storable CLong Source # 
Storable CULong Source # 
Storable CSize Source # 
Storable (Ptr a) Source # 

Methods

peekIO :: Ptr (Ptr a) -> IO (Ptr a) Source #

pokeIO :: Ptr (Ptr a) -> Ptr a -> IO () Source #

alignment :: Ptr a -> Word Source #

sizeOf :: Ptr a -> Word Source #

(HFoldr' FoldSizeOf Word l Word, HFoldr' FoldAlignment Word l Word) => Storable (Union l) Source # 

Methods

peekIO :: Ptr (Union l) -> IO (Union l) Source #

pokeIO :: Ptr (Union l) -> Union l -> IO () Source #

alignment :: Union l -> Word Source #

sizeOf :: Union l -> Word Source #

(ByteReversable a, Storable a) => Storable (AsLittleEndian a) Source # 
(ByteReversable a, Storable a) => Storable (AsBigEndian a) Source # 
(Storable b, Integral b, CEnum a) => Storable (EnumField b a) Source # 

Methods

peekIO :: Ptr (EnumField b a) -> IO (EnumField b a) Source #

pokeIO :: Ptr (EnumField b a) -> EnumField b a -> IO () Source #

alignment :: EnumField b a -> Word Source #

sizeOf :: EnumField b a -> Word Source #

(KnownNat n, Storable a) => Storable (Vector n a) Source # 

Methods

peekIO :: Ptr (Vector n a) -> IO (Vector n a) Source #

pokeIO :: Ptr (Vector n a) -> Vector n a -> IO () Source #

alignment :: Vector n a -> Word Source #

sizeOf :: Vector n a -> Word Source #

Storable b => Storable (BitSet b a) Source # 

Methods

peekIO :: Ptr (BitSet b a) -> IO (BitSet b a) Source #

pokeIO :: Ptr (BitSet b a) -> BitSet b a -> IO () Source #

alignment :: BitSet b a -> Word Source #

sizeOf :: BitSet b a -> Word Source #

Storable b => Storable (BitFields b f) Source # 

Methods

peekIO :: Ptr (BitFields b f) -> IO (BitFields b f) Source #

pokeIO :: Ptr (BitFields b f) -> BitFields b f -> IO () Source #

alignment :: BitFields b f -> Word Source #

sizeOf :: BitFields b f -> Word Source #

Storable s => Storable (BitField n name s) Source # 

Methods

peekIO :: Ptr (BitField n name s) -> IO (BitField n name s) Source #

pokeIO :: Ptr (BitField n name s) -> BitField n name s -> IO () Source #

alignment :: BitField n name s -> Word Source #

sizeOf :: BitField n name s -> Word Source #

Storable w => Storable (FixedPoint w i f) Source # 

Methods

peekIO :: Ptr (FixedPoint w i f) -> IO (FixedPoint w i f) Source #

pokeIO :: Ptr (FixedPoint w i f) -> FixedPoint w i f -> IO () Source #

alignment :: FixedPoint w i f -> Word Source #

sizeOf :: FixedPoint w i f -> Word Source #

peek :: (Storable a, MonadIO m) => Ptr a -> m a Source #

Peek a value from a pointer

poke :: (Storable a, MonadIO m) => Ptr a -> a -> m () Source #

Poke a value to a pointer

sizeOf' :: (Integral b, Storable a) => a -> b Source #

Generalized sizeOf

sizeOfT :: forall a. Storable a => Word Source #

SizeOf (for type-application)

sizeOfT' :: forall a b. (Storable a, Integral b) => b Source #

SizeOf' (for type-application)

alignment' :: (Integral b, Storable a) => a -> b Source #

Generalized alignment

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)

peekByteOff :: (MonadIO m, Storable a) => Ptr a -> Int -> m a Source #

Peek with byte offset

pokeByteOff :: (MonadIO m, Storable a) => Ptr a -> Int -> a -> m () Source #

Poke with byte offset

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 f executes the computation f, 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.

allocaBytes :: MonadInIO m => Word -> (Ptr a -> m b) -> m b Source #

Allocate some bytes

allocaBytesAligned :: MonadInIO m => Word -> Word -> (Ptr a -> m b) -> m b Source #

Allocate some aligned bytes

malloc :: forall a m. (MonadIO m, Storable a) => m (Ptr a) Source #

Allocate a block of memory that is sufficient to hold values of type a. The size of the area allocated is determined by the sizeOf method from the instance of Storable for the appropriate type.

The memory may be deallocated using free or finalizerFree when no longer required.

with :: (MonadInIO m, Storable a) => a -> (Ptr a -> m b) -> m b Source #

with val f executes the computation f, 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