binrep-0.5.0: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageGHC2021

Binrep.Put.Bytezap

Description

Serialization using the bytezap library.

bytezap serializers ("pokes") work by writing bytes into a pointer, which is assumed to have _precisely_ the space required. The user must determine the post-serialize length before the fact. For that reason, this module requires that types to be serialized have a BLen instance. In general, we are happy about this, because a binrep type should always have an efficient and preferably simple BLen instance (and if not, it shouldn't be a binrep type).

Synopsis

Documentation

class Put a where Source #

Methods

put :: a -> Poke Source #

Instances

Instances details
(TypeError ENoEmpty :: Constraint) => Put Void Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: Void -> Poke Source #

Put Int8 Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: Int8 -> Poke Source #

Put Word8 Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: Word8 -> Poke Source #

Put Poke Source #

Fairly useless because Poke doesn't have a BLen instance.

Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: Poke -> Poke Source #

Put Write Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: Write -> Poke Source #

Put ByteString Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: ByteString -> Poke Source #

Put () Source #

Unit type serializes to nothing. How zen.

Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: () -> Poke Source #

Put a => Put (NullTerminated a) Source #

Serialization of null-terminated data may be defined generally using the data's underlying serializer.

Instance details

Defined in Binrep.Type.NullTerminated

Methods

put :: NullTerminated a -> Poke Source #

Put a => Put (Thin a) Source # 
Instance details

Defined in Binrep.Type.Thin

Methods

put :: Thin a -> Poke Source #

Put a => Put (Binreply a) Source # 
Instance details

Defined in Binrep.Via

Methods

put :: Binreply a -> Poke Source #

Put a => Put [a] Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: [a] -> Poke Source #

(TypeError ENoSum :: Constraint) => Put (Either a b) Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: Either a b -> Poke Source #

Put (Endian 'BE Int16) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'BE Int16 -> Poke Source #

Put (Endian 'BE Int32) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'BE Int32 -> Poke Source #

Put (Endian 'BE Int64) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'BE Int64 -> Poke Source #

Put (Endian 'BE Word16) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'BE Word16 -> Poke Source #

Put (Endian 'BE Word32) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'BE Word32 -> Poke Source #

Put (Endian 'BE Word64) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'BE Word64 -> Poke Source #

Put (Endian 'LE Int16) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'LE Int16 -> Poke Source #

Put (Endian 'LE Int32) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'LE Int32 -> Poke Source #

Put (Endian 'LE Int64) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'LE Int64 -> Poke Source #

Put (Endian 'LE Word16) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'LE Word16 -> Poke Source #

Put (Endian 'LE Word32) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'LE Word32 -> Poke Source #

Put (Endian 'LE Word64) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: Endian 'LE Word64 -> Poke Source #

(bs ~ MagicBytes a, ReifyBytes bs) => Put (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

put :: Magic a -> Poke Source #

(BLen a, Put a, KnownNat n) => Put (NullPadded n a) Source # 
Instance details

Defined in Binrep.Type.NullPadded

Methods

put :: NullPadded n a -> Poke Source #

(Prefix pfx, BLen a, Put pfx, Put a) => Put (SizePrefixed pfx a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Size

Methods

put :: SizePrefixed pfx a -> Poke Source #

Put a => Put (Sized n a) Source # 
Instance details

Defined in Binrep.Type.Sized

Methods

put :: Sized n a -> Poke Source #

(Put l, Put r) => Put (l, r) Source # 
Instance details

Defined in Binrep.Put.Bytezap

Methods

put :: (l, r) -> Poke Source #

(Prefix pfx, Foldable f, Put pfx, Put (f a)) => Put (CountPrefixed pfx f a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

put :: CountPrefixed pfx f a -> Poke Source #

runPut :: (BLen a, Put a) => a -> ByteString Source #

putGenericNonSum :: forall {cd} {f} {asserts} a. (Generic a, Rep a ~ D1 cd f, GFoldMapNonSum Poke f, asserts ~ '['NoEmpty, 'NoSum], ApplyGCAsserts asserts f) => a -> Poke Source #

Serialize a term of the non-sum type a via its Generic instance.

putGenericSum :: forall {cd} {f} {asserts} a. (Generic a, Rep a ~ D1 cd f, GFoldMapSum 'SumOnly Poke f, asserts ~ '['NoEmpty, 'NeedSum], ApplyGCAsserts asserts f) => (String -> Poke) -> a -> Poke Source #

Serialize a term of the sum type a via its Generic instance.

You must provide a serializer for a's constructors. This is regrettably inefficient due to having to use Strings. Alas. Do write your own instance if you want better performance!

Orphan instances

GenericFoldMap Poke Source # 
Instance details

Associated Types

type GenericFoldMapC Poke a #