Safe Haskell | None |
---|---|
Language | GHC2021 |
Binrep.Put
Synopsis
- type Putter = Poke RealWorld
- class Put a where
- runPut :: (BLen a, Put a) => a -> ByteString
- putGenericNonSum :: (Generic a, GFoldMapNonSum Put (Rep a), GAssertNotVoid a, GAssertNotSum a) => a -> Putter
- putGenericSum :: forall {k} (sumtag :: k) a. (Generic a, GFoldMapSum Put sumtag (Rep a), GAssertNotVoid a, GAssertSum a) => ParseCstrTo sumtag Putter -> a -> Putter
- putGenericSumRaw :: (Generic a, GFoldMapSum Put Raw (Rep a), GAssertNotVoid a, GAssertSum a) => (String -> Putter) -> a -> Putter
- newtype ViaPutC a = ViaPutC {
- unViaPutC :: a
Documentation
Instances
(TypeError ENoEmpty :: Constraint) => Put Void Source # | |
Put Int8 Source # | 8-bit (1-byte) words do not require byte order in order to precisely define their representation. |
Put Word8 Source # | 8-bit (1-byte) words do not require byte order in order to precisely define their representation. |
Put Putter Source # | |
Put ByteString Source # | |
Defined in Binrep.Put Methods put :: ByteString -> Putter Source # | |
Put () Source # | Unit type serializes to nothing. How zen. |
Defined in Binrep.Put | |
(Generic a, GFoldMapNonSum Put (Rep a), GAssertNotVoid a, GAssertNotSum a) => Put (GenericallyNonSum a) Source # | |
Defined in Binrep.Put Methods put :: GenericallyNonSum a -> Putter Source # | |
Prim' a => Put (ViaPrim a) Source # | |
(PutC a, KnownNat (CBLen a)) => Put (ViaPutC a) Source # | |
Put a => Put (NullTerminated a) Source # | Serialization of null-terminated data may be defined generally using the data's underlying serializer. |
Defined in Binrep.Type.NullTerminated Methods put :: NullTerminated a -> Putter Source # | |
Put a => Put (Thin a) Source # | |
Put a => Put [a] Source # | |
Defined in Binrep.Put | |
(TypeError ENoSum :: Constraint) => Put (Either a b) Source # | |
(bs ~ MagicBytes a, ReifyBytesW64 bs, KnownNat (Length bs)) => Put (Magic a) Source # | |
(BLen a, KnownNat n, Put a) => Put (NullPadded n a) Source # | |
Defined in Binrep.Type.NullPadded Methods put :: NullPadded n a -> Putter Source # | |
(LenNat pfx, BLen a, Put pfx, Put a) => Put (SizePrefixed pfx a) Source # | |
Defined in Binrep.Type.Prefix.Size Methods put :: SizePrefixed pfx a -> Putter Source # | |
Put a => Put (Sized n a) Source # | |
(Prim' a, ByteSwap a) => Put (ByteOrdered 'BigEndian a) Source # | |
Defined in Binrep.Put | |
(Prim' a, ByteSwap a) => Put (ByteOrdered 'LittleEndian a) Source # | |
Defined in Binrep.Put Methods put :: ByteOrdered 'LittleEndian a -> Putter Source # | |
Put (ByteOrdered end Int8) Source # | Byte order is irrelevant for 8-bit (1-byte) words. |
Defined in Binrep.Put | |
Put (ByteOrdered end Word8) Source # | Byte order is irrelevant for 8-bit (1-byte) words. |
Defined in Binrep.Put | |
(Put l, Put r) => Put (l, r) Source # | |
Defined in Binrep.Put | |
Integral a => Put (Refined (AsciiNat 2) a) Source # | Serialize any term of an |
Integral a => Put (Refined (AsciiNat 8) a) Source # | Serialize any term of an |
Integral a => Put (Refined (AsciiNat 10) a) Source # | Serialize any term of an |
Integral a => Put (Refined (AsciiNat 16) a) Source # | Serialize any term of an Uses lower-case ASCII. |
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? |
(LenNat pfx, Foldable f, Put pfx, Put (f a)) => Put (CountPrefixed pfx f a) Source # | |
Defined in Binrep.Type.Prefix.Count Methods put :: CountPrefixed pfx f a -> Putter Source # |
putGenericNonSum :: (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 {k} (sumtag :: k) a. (Generic a, GFoldMapSum Put sumtag (Rep a), GAssertNotVoid a, GAssertSum a) => ParseCstrTo sumtag Putter -> a -> Putter Source #
Serialize a term of the sum type a
via its Generic
instance.
putGenericSumRaw :: (Generic a, GFoldMapSum Put Raw (Rep a), GAssertNotVoid a, GAssertSum a) => (String -> Putter) -> a -> Putter Source #
Serialize a term of the sum type a
via its Generic
instance, without
pre-parsing constructor names.