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

Binrep.Put

Synopsis

Documentation

class Put a where Source #

Methods

put :: a -> Putter Source #

Instances

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

Defined in Binrep.Put

Methods

put :: Void -> Putter Source #

Put Int8 Source #

8-bit (1-byte) words do not require byte order in order to precisely define their representation.

Instance details

Defined in Binrep.Put

Methods

put :: Int8 -> Putter Source #

Put Word8 Source #

8-bit (1-byte) words do not require byte order in order to precisely define their representation.

Instance details

Defined in Binrep.Put

Methods

put :: Word8 -> Putter Source #

Put Putter Source # 
Instance details

Defined in Binrep.Put

Methods

put :: Putter -> Putter Source #

Put ByteString Source # 
Instance details

Defined in Binrep.Put

Put () Source #

Unit type serializes to nothing. How zen.

Instance details

Defined in Binrep.Put

Methods

put :: () -> Putter Source #

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

Defined in Binrep.Put

Methods

put :: Identity a -> Putter Source #

(Generic a, GFoldMapNonSum Put (Rep a), GAssertNotVoid a, GAssertNotSum a) => Put (GenericallyNonSum a) Source # 
Instance details

Defined in Binrep.Put

Prim' a => Put (ViaPrim a) Source # 
Instance details

Defined in Binrep.Put

Methods

put :: ViaPrim a -> Putter Source #

(PutC a, KnownNat (CBLen a)) => Put (ViaPutC a) Source # 
Instance details

Defined in Binrep.Put

Methods

put :: ViaPutC a -> Putter 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

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

Defined in Binrep.Type.Thin

Methods

put :: Thin a -> Putter Source #

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

Defined in Binrep.Put

Methods

put :: [a] -> Putter Source #

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

Defined in Binrep.Put

Methods

put :: Either a b -> Putter Source #

(bs ~ MagicBytes a, ReifyBytesW64 bs, KnownNat (Length bs)) => Put (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

put :: Magic a -> Putter Source #

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

Defined in Binrep.Type.NullPadded

Methods

put :: NullPadded n a -> Putter 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 -> Putter Source #

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

Defined in Binrep.Type.Sized

Methods

put :: Sized n a -> Putter Source #

(Prim' a, ByteSwap a) => Put (ByteOrdered 'BigEndian a) Source # 
Instance details

Defined in Binrep.Put

(Prim' a, ByteSwap a) => Put (ByteOrdered 'LittleEndian a) Source # 
Instance details

Defined in Binrep.Put

Put (ByteOrdered end Int8) Source #

Byte order is irrelevant for 8-bit (1-byte) words.

Instance details

Defined in Binrep.Put

Methods

put :: ByteOrdered end Int8 -> Putter Source #

Put (ByteOrdered end Word8) Source #

Byte order is irrelevant for 8-bit (1-byte) words.

Instance details

Defined in Binrep.Put

Methods

put :: ByteOrdered end Word8 -> Putter Source #

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

Defined in Binrep.Put

Methods

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

GenericFoldMap Put Source #

Serialize generically using generic foldMap.

Instance details

Defined in Binrep.Put

Associated Types

type GenericFoldMapM Put #

type GenericFoldMapC Put a #

Put (Refined pr (Refined pl a)) => Put (Refined (And pl pr) a) Source #

Put types refined with multiple predicates by wrapping the left predicate with the right. LOL REALLY?

Instance details

Defined in Binrep.Put

Methods

put :: Refined (And pl pr) a -> Putter 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 -> Putter Source #

type GenericFoldMapM Put Source # 
Instance details

Defined in Binrep.Put

type GenericFoldMapC Put a Source # 
Instance details

Defined in Binrep.Put

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

putGenericNonSum :: forall a. (Generic a, GFoldMapNonSum Put (Rep a), GAssertNotVoid a, GAssertNotSum a) => a -> Putter Source #

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

putGenericSum :: forall a. (Generic a, GFoldMapSum Put (Rep a), GAssertNotVoid a, GAssertSum a) => (String -> Putter) -> a -> Putter 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!

newtype ViaPutC a Source #

Constructors

ViaPutC 

Fields

Instances

Instances details
(PutC a, KnownNat (CBLen a)) => Put (ViaPutC a) Source # 
Instance details

Defined in Binrep.Put

Methods

put :: ViaPutC a -> Putter Source #