Safe Haskell | None |
---|---|
Language | GHC2021 |
Binrep.BLen
Description
Byte length as a simple pure function, no bells or whistles.
Non-reallocating serializers like store, bytezap or ptr-poker request the expected total byte length when serializing. Thus, they need some way to measure byte length *before* serializing. This is that.
It should be very efficient to calculate serialized byte length for most binrep-compatible Haskell types. If it isn't, consider whether the representation is appropriate for binrep.
Note that you _may_ encode this inside the serializer type (whatever the Put
class stores). I went back and forth on this a couple times. But some binrep
code seems to make more sense when byte length is standalone. And I don't mind
the extra explicitness. So it's here to stay :)
Synopsis
- class BLen a where
- blenGenericNonSum :: (Generic a, GFoldMapNonSum BLen (Rep a), GAssertNotVoid a, GAssertNotSum a) => a -> Int
- blenGenericSum :: forall {k} (sumtag :: k) a. (Generic a, GFoldMapSum BLen sumtag (Rep a), GAssertNotVoid a, GAssertSum a) => ParseCstrTo sumtag Int -> a -> Int
- blenGenericSumRaw :: (Generic a, GFoldMapSum BLen Raw (Rep a), GAssertNotVoid a, GAssertSum a) => (String -> Int) -> a -> Int
- newtype ViaCBLen a = ViaCBLen {
- unViaCBLen :: a
- cblen :: forall {k} (a :: k). KnownNat (CBLen a) => Int
Documentation
Class for types with easily-calculated length in bytes.
If it appears hard to calculate byte length for a given type (e.g. without first serializing it, then measuring serialized byte length), consider whether this type is a good fit for binrep.
Instances
(TypeError ENoEmpty :: Constraint) => BLen Void Source # | |
BLen Int16 Source # | |
BLen Int32 Source # | |
BLen Int64 Source # | |
BLen Int8 Source # | |
BLen Word16 Source # | |
BLen Word32 Source # | |
BLen Word64 Source # | |
BLen Word8 Source # | |
BLen ByteString Source # | _O(1)_ |
Defined in Binrep.BLen Methods blen :: ByteString -> Int Source # | |
BLen () Source # | _O(1)_ Unit type has length 0. |
Defined in Binrep.BLen | |
KnownNat (CBLen a) => BLen (ViaCBLen a) Source # | |
(Generic a, GFoldMapNonSum BLen (Rep a), GAssertNotVoid a, GAssertNotSum a) => BLen (GenericallyNonSum a) Source # | |
Defined in Binrep.BLen Methods blen :: GenericallyNonSum a -> Int Source # | |
BLen a => BLen (NullTerminated a) Source # | |
Defined in Binrep.Type.NullTerminated Methods blen :: NullTerminated a -> Int Source # | |
BLen a => BLen (Thin a) Source # | |
BLen a => BLen [a] Source # | _O(n)_ Sum the length of each element of a list. |
Defined in Binrep.BLen | |
(TypeError ENoSum :: Constraint) => BLen (Either a b) Source # | |
KnownNat (Length (MagicBytes a)) => BLen (Magic a) Source # | |
KnownNat n => BLen (NullPadded n a) Source # | |
Defined in Binrep.Type.NullPadded Methods blen :: NullPadded n a -> Int Source # | |
(LenNat pfx, BLen a, BLen pfx) => BLen (SizePrefixed pfx a) Source # | |
Defined in Binrep.Type.Prefix.Size Methods blen :: SizePrefixed pfx a -> Int Source # | |
KnownNat n => BLen (Sized n a) Source # | |
KnownNat (CBLen a) => BLen (ByteOrdered end a) Source # | Explicitness does not alter length. |
Defined in Binrep.BLen Methods blen :: ByteOrdered end a -> Int Source # | |
(BLen l, BLen r) => BLen (l, r) Source # | _O(1)_ Sum tuples. |
Defined in Binrep.BLen | |
(HasBaseOps a, KnownNat base) => BLen (Refined (AsciiNat base) a) Source # | The bytelength of an |
BLen (Refined pr (Refined pl a)) => BLen (Refined (And pl pr) a) Source # | |
(LenNat pfx, Foldable f, BLen pfx, BLen (f a)) => BLen (CountPrefixed pfx f a) Source # | The byte length of a count-prefixed type is the length of the prefix type (holding the length of the type) plus the length of the type. Bit confusing. How to explain this? TODO |
Defined in Binrep.Type.Prefix.Count Methods blen :: CountPrefixed pfx f a -> Int Source # |
blenGenericNonSum :: (Generic a, GFoldMapNonSum BLen (Rep a), GAssertNotVoid a, GAssertNotSum a) => a -> Int Source #
Measure the byte length of a term of the non-sum type a
via its Generic
instance.
blenGenericSum :: forall {k} (sumtag :: k) a. (Generic a, GFoldMapSum BLen sumtag (Rep a), GAssertNotVoid a, GAssertSum a) => ParseCstrTo sumtag Int -> a -> Int Source #
Measure the byte length of a term of the sum type a
via its Generic
instance.
blenGenericSumRaw :: (Generic a, GFoldMapSum BLen Raw (Rep a), GAssertNotVoid a, GAssertSum a) => (String -> Int) -> a -> Int Source #
Measure the byte length of a term of the sum type a
via its Generic
instance.
DerivingVia wrapper for types which may derive a BLen
instance through
an existing IsCBLen
instance (i.e. it is known at compile time)
Examples of such types include machine integers, and explicitly-sized types (e.g. Binrep.Type.Sized).
Constructors
ViaCBLen | |
Fields
|