Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Word8
- data Int8
- data ByteString
- data ShortByteString
- data Vector a
- data Seq a where
- data ByteArray
- class Generic a
- data Proxy (t :: k) = Proxy
- data GetError
- prettyGetError :: GetError -> Text
- data GetIncRequest = GetIncRequest {
- girAbsPos :: !ByteCount
- girBaseOff :: !ByteCount
- girNeedLength :: !ByteCount
- type GetIncCb z m = GetIncRequest -> m (Maybe z)
- runCount :: Put -> ByteCount
- module Dahdit.Binary
- module Dahdit.BinaryRep
- module Dahdit.Fancy
- type Put = PutM ()
- data PutM a
- data Get a
- getWord8 :: Get Word8
- getInt8 :: Get Int8
- getWord16LE :: Get Word16LE
- getInt16LE :: Get Int16LE
- getWord24LE :: Get Word24LE
- getInt24LE :: Get Int24LE
- getWord32LE :: Get Word32LE
- getInt32LE :: Get Int32LE
- getWord64LE :: Get Word64LE
- getInt64LE :: Get Int64LE
- getFloatLE :: Get FloatLE
- getDoubleLE :: Get DoubleLE
- getWord16BE :: Get Word16BE
- getInt16BE :: Get Int16BE
- getWord24BE :: Get Word24BE
- getInt24BE :: Get Int24BE
- getWord32BE :: Get Word32BE
- getInt32BE :: Get Int32BE
- getWord64BE :: Get Word64BE
- getInt64BE :: Get Int64BE
- getFloatBE :: Get FloatBE
- getDoubleBE :: Get DoubleBE
- getText :: ByteCount -> Get Text
- getByteString :: ByteCount -> Get ShortByteString
- getSkip :: ByteCount -> Get ()
- getExact :: ByteCount -> Get a -> Get a
- getWithin :: ByteCount -> Get a -> Get a
- getList :: ElemCount -> Get a -> Get [a]
- getSeq :: ElemCount -> Get a -> Get (Seq a)
- getStaticSeq :: StaticByteSized a => ElemCount -> Get a -> Get (Seq a)
- getStaticArray :: LiftedPrim a => ElemCount -> Get (LiftedPrimArray a)
- getByteArray :: ByteCount -> Get ByteArray
- getLiftedPrimArray :: LiftedPrim a => Proxy a -> ElemCount -> Get (LiftedPrimArray a)
- getLookAhead :: Get a -> Get a
- getRemainingSize :: Get ByteCount
- getRemainingString :: Get ShortByteString
- getRemainingSeq :: Get a -> Get (Seq a)
- getRemainingStaticSeq :: StaticByteSized a => Get a -> Get (Seq a)
- getRemainingStaticArray :: LiftedPrim a => Proxy a -> Get (LiftedPrimArray a)
- getRemainingByteArray :: Get ByteArray
- getRemainingLiftedPrimArray :: LiftedPrim a => Proxy a -> Get (LiftedPrimArray a)
- getExpect :: (Eq a, Show a) => String -> Get a -> a -> Get ()
- getUnfold :: b -> (b -> Get (Either b a)) -> Get a
- putWord8 :: Word8 -> Put
- putInt8 :: Int8 -> Put
- putWord16LE :: Word16LE -> Put
- putInt16LE :: Int16LE -> Put
- putWord24LE :: Word24LE -> Put
- putInt24LE :: Int24LE -> Put
- putWord32LE :: Word32LE -> Put
- putInt32LE :: Int32LE -> Put
- putWord64LE :: Word64LE -> Put
- putInt64LE :: Int64LE -> Put
- putFloatLE :: FloatLE -> Put
- putDoubleLE :: DoubleLE -> Put
- putWord16BE :: Word16BE -> Put
- putInt16BE :: Int16BE -> Put
- putWord24BE :: Word24BE -> Put
- putInt24BE :: Int24BE -> Put
- putWord32BE :: Word32BE -> Put
- putInt32BE :: Int32BE -> Put
- putWord64BE :: Word64BE -> Put
- putInt64BE :: Int64BE -> Put
- putFloatBE :: FloatBE -> Put
- putDoubleBE :: DoubleBE -> Put
- putText :: Text -> Put
- putByteString :: ShortByteString -> Put
- putFixedString :: Word8 -> ByteCount -> ShortByteString -> Put
- putList :: (a -> Put) -> [a] -> Put
- putSeq :: (a -> Put) -> Seq a -> Put
- putStaticSeq :: StaticByteSized a => (a -> Put) -> Seq a -> Put
- putStaticArray :: LiftedPrim a => LiftedPrimArray a -> Put
- putByteArray :: ByteArray -> Put
- putLiftedPrimArray :: LiftedPrimArray a -> Put
- putStaticHint :: StaticByteSized a => (a -> Put) -> a -> Put
- module Dahdit.Generic
- module Dahdit.Iface
- module Dahdit.LiftedPrim
- module Dahdit.LiftedPrimArray
- module Dahdit.Nums
- module Dahdit.Proxy
- module Dahdit.Sizes
Documentation
8-bit unsigned integer type
Instances
8-bit signed integer type
Instances
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
data ShortByteString #
A compact representation of a Word8
vector.
It has a lower memory overhead than a ByteString
and does not
contribute to heap fragmentation. It can be converted to or from a
ByteString
(at the cost of copying the string data). It supports very few
other operations.
It is suitable for use as an internal representation for code that needs
to keep many short strings in memory, but it should not be used as an
interchange type. That is, it should not generally be used in public APIs.
The ByteString
type is usually more suitable for use in interfaces; it is
more flexible and it supports a wide range of operations.
Instances
Storable
-based vectors.
Instances
NFData1 Vector | Since: vector-0.12.1.0 |
Defined in Data.Vector.Storable | |
Storable a => Vector Vector a | |
Defined in Data.Vector.Storable basicUnsafeFreeze :: Mutable Vector s a -> ST s (Vector a) # basicUnsafeThaw :: Vector a -> ST s (Mutable Vector s a) # basicLength :: Vector a -> Int # basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a # basicUnsafeIndexM :: Vector a -> Int -> Box a # basicUnsafeCopy :: Mutable Vector s a -> Vector a -> ST s () # | |
(Data a, Storable a) => Data (Vector a) | |
Defined in Data.Vector.Storable gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
Storable a => Monoid (Vector a) | |
Storable a => Semigroup (Vector a) | |
Storable a => IsList (Vector a) | |
(Read a, Storable a) => Read (Vector a) | |
(Show a, Storable a) => Show (Vector a) | |
NFData (Vector a) | |
Defined in Data.Vector.Storable | |
(Storable a, Eq a) => Eq (Vector a) | |
(Storable a, Ord a) => Ord (Vector a) | |
Defined in Data.Vector.Storable | |
BinaryGetTarget (Vector Word8) IO Source # | |
BinaryPutTarget (Vector Word8) IO Source # | |
Defined in Dahdit.Iface | |
MutableMem (Vector Word8) (IOVector Word8) IO Source # | |
Defined in Dahdit.Mem | |
type Mutable Vector | |
Defined in Data.Vector.Storable | |
type Item (Vector a) | |
Defined in Data.Vector.Storable |
General-purpose finite sequences.
pattern Empty :: Seq a | A bidirectional pattern synonym matching an empty sequence. Since: containers-0.5.8 |
pattern (:<|) :: a -> Seq a -> Seq a infixr 5 | A bidirectional pattern synonym viewing the front of a non-empty sequence. Since: containers-0.5.8 |
pattern (:|>) :: Seq a -> a -> Seq a infixl 5 | A bidirectional pattern synonym viewing the rear of a non-empty sequence. Since: containers-0.5.8 |
Instances
MonadFix Seq | Since: containers-0.5.11 |
Defined in Data.Sequence.Internal | |
MonadZip Seq |
|
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldMap' :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Eq1 Seq | Since: containers-0.5.9 |
Ord1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Read1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Show1 Seq | Since: containers-0.5.9 |
Traversable Seq | |
Alternative Seq | Since: containers-0.5.4 |
Applicative Seq | Since: containers-0.5.4 |
Functor Seq | |
Monad Seq | |
MonadPlus Seq | |
UnzipWith Seq | |
Defined in Data.Sequence.Internal unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
Hashable1 Seq | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
Monoid (Seq a) | |
Semigroup (Seq a) | Since: containers-0.5.7 |
IsList (Seq a) | |
Read a => Read (Seq a) | |
Show a => Show (Seq a) | |
Binary a => Binary (Seq a) Source # | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
Eq a => Eq (Seq a) | |
Ord a => Ord (Seq a) | |
Hashable v => Hashable (Seq v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
type Item (Seq a) | |
Defined in Data.Sequence.Internal |
Boxed wrapper for ByteArray#
.
Since ByteArray#
is an unlifted type and not a member of kind Type
,
things like [ByteArray#]
or IO ByteArray#
are ill-typed. To work around this
inconvenience this module provides a standard boxed wrapper, inhabiting Type
.
Clients are expected to use ByteArray
in higher-level APIs,
but wrap and unwrap ByteArray
internally as they please
and use functions from GHC.Exts.
Instances
Data ByteArray | |
Defined in Data.Array.Byte gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteArray -> c ByteArray # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteArray # toConstr :: ByteArray -> Constr # dataTypeOf :: ByteArray -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteArray) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray) # gmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteArray -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteArray -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray # | |
Monoid ByteArray | |
Semigroup ByteArray | |
IsList ByteArray | |
Show ByteArray | |
NFData ByteArray | |
Defined in Data.Array.Byte | |
Eq ByteArray | |
Ord ByteArray | Non-lexicographic ordering. This compares the lengths of the byte arrays first and uses a lexicographic ordering if the lengths are equal. Subject to change between major versions. |
Defined in Data.Array.Byte | |
Hashable ByteArray | This instance was available since 1.4.1.0 only for GHC-9.4+ Since: hashable-1.4.2.0 |
Defined in Data.Hashable.Class | |
PrimMonad m => BinaryGetTarget ByteArray m Source # | |
PrimMonad m => BinaryPutTarget ByteArray m Source # | |
Defined in Dahdit.Iface | |
PrimMonad m => ReadMem ByteArray m Source # | |
Defined in Dahdit.Mem indexMemInBytes :: LiftedPrim a => ByteArray -> ByteCount -> m a Source # cloneArrayMemInBytes :: ByteArray -> ByteCount -> ByteCount -> m ByteArray Source # | |
Lift ByteArray | |
MonadPrim s m => MutableMem ByteArray (MutableByteArray s) m Source # | |
Defined in Dahdit.Mem unsafeThawMem :: ByteArray -> m (MutableByteArray s) Source # unsafeUseThawedMem :: ByteArray -> (MutableByteArray s -> m a) -> m a Source # unsafeFreezeMem :: MutableByteArray s -> m ByteArray Source # unsafeUseFrozenMem :: MutableByteArray s -> (ByteArray -> m a) -> m a Source # | |
type Item ByteArray | |
Defined in Data.Array.Byte |
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) | |
Foldable (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Generic (Proxy t) | |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |
GetErrorLocalCap !Text !ByteCount !ByteCount | |
GetErrorScopedMismatch !ScopeMode !ByteCount !ByteCount | |
GetErrorFail !Text | |
GetErrorGlobalCap !Text !ByteCount !ByteCount | |
GetErrorRemaining !ByteCount |
Instances
Exception GetError Source # | |
Defined in Dahdit.Run toException :: GetError -> SomeException # fromException :: SomeException -> Maybe GetError # displayException :: GetError -> String # | |
Show GetError Source # | |
Eq GetError Source # | |
prettyGetError :: GetError -> Text Source #
data GetIncRequest Source #
A request for more data. Includes absolute position, offset in the current buffer, and required length.
GetIncRequest | |
|
Instances
Show GetIncRequest Source # | |
Defined in Dahdit.Run showsPrec :: Int -> GetIncRequest -> ShowS # show :: GetIncRequest -> String # showList :: [GetIncRequest] -> ShowS # | |
Eq GetIncRequest Source # | |
Defined in Dahdit.Run (==) :: GetIncRequest -> GetIncRequest -> Bool # (/=) :: GetIncRequest -> GetIncRequest -> Bool # | |
Ord GetIncRequest Source # | |
Defined in Dahdit.Run compare :: GetIncRequest -> GetIncRequest -> Ordering # (<) :: GetIncRequest -> GetIncRequest -> Bool # (<=) :: GetIncRequest -> GetIncRequest -> Bool # (>) :: GetIncRequest -> GetIncRequest -> Bool # (>=) :: GetIncRequest -> GetIncRequest -> Bool # max :: GetIncRequest -> GetIncRequest -> GetIncRequest # min :: GetIncRequest -> GetIncRequest -> GetIncRequest # |
type GetIncCb z m = GetIncRequest -> m (Maybe z) Source #
Return new chunk containing enough data (or nothing).
module Dahdit.Binary
module Dahdit.BinaryRep
module Dahdit.Fancy
getInt16LE :: Get Int16LE Source #
getInt24LE :: Get Int24LE Source #
getInt32LE :: Get Int32LE Source #
getInt64LE :: Get Int64LE Source #
getFloatLE :: Get FloatLE Source #
getInt16BE :: Get Int16BE Source #
getInt24BE :: Get Int24BE Source #
getInt32BE :: Get Int32BE Source #
getInt64BE :: Get Int64BE Source #
getFloatBE :: Get FloatBE Source #
getStaticSeq :: StaticByteSized a => ElemCount -> Get a -> Get (Seq a) Source #
Get Seq of statically-sized elements
getStaticArray :: LiftedPrim a => ElemCount -> Get (LiftedPrimArray a) Source #
Get PrimArray of statically-sized elements
getLiftedPrimArray :: LiftedPrim a => Proxy a -> ElemCount -> Get (LiftedPrimArray a) Source #
getLookAhead :: Get a -> Get a Source #
getRemainingStaticSeq :: StaticByteSized a => Get a -> Get (Seq a) Source #
getRemainingStaticArray :: LiftedPrim a => Proxy a -> Get (LiftedPrimArray a) Source #
getRemainingLiftedPrimArray :: LiftedPrim a => Proxy a -> Get (LiftedPrimArray a) Source #
putWord16LE :: Word16LE -> Put Source #
putInt16LE :: Int16LE -> Put Source #
putWord24LE :: Word24LE -> Put Source #
putInt24LE :: Int24LE -> Put Source #
putWord32LE :: Word32LE -> Put Source #
putInt32LE :: Int32LE -> Put Source #
putWord64LE :: Word64LE -> Put Source #
putInt64LE :: Int64LE -> Put Source #
putFloatLE :: FloatLE -> Put Source #
putDoubleLE :: DoubleLE -> Put Source #
putWord16BE :: Word16BE -> Put Source #
putInt16BE :: Int16BE -> Put Source #
putWord24BE :: Word24BE -> Put Source #
putInt24BE :: Int24BE -> Put Source #
putWord32BE :: Word32BE -> Put Source #
putInt32BE :: Int32BE -> Put Source #
putWord64BE :: Word64BE -> Put Source #
putInt64BE :: Int64BE -> Put Source #
putFloatBE :: FloatBE -> Put Source #
putDoubleBE :: DoubleBE -> Put Source #
putByteString :: ShortByteString -> Put Source #
putFixedString :: Word8 -> ByteCount -> ShortByteString -> Put Source #
putStaticSeq :: StaticByteSized a => (a -> Put) -> Seq a -> Put Source #
Put Seq of statically-sized elements
putStaticArray :: LiftedPrim a => LiftedPrimArray a -> Put Source #
Put Array of statically-sized elements
putByteArray :: ByteArray -> Put Source #
putLiftedPrimArray :: LiftedPrimArray a -> Put Source #
putStaticHint :: StaticByteSized a => (a -> Put) -> a -> Put Source #
module Dahdit.Generic
module Dahdit.Iface
module Dahdit.LiftedPrim
module Dahdit.LiftedPrimArray
module Dahdit.Nums
module Dahdit.Proxy
module Dahdit.Sizes