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

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

Documentation

class BLen a where Source #

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.

Methods

blen :: a -> Int Source #

Calculate the serialized byte length of the given value.

Instances

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

Defined in Binrep.BLen

Methods

blen :: Void -> Int Source #

BLen Int16 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Int16 -> Int Source #

BLen Int32 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Int32 -> Int Source #

BLen Int64 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Int64 -> Int Source #

BLen Int8 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Int8 -> Int Source #

BLen Word16 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Word16 -> Int Source #

BLen Word32 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Word32 -> Int Source #

BLen Word64 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Word64 -> Int Source #

BLen Word8 Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Word8 -> Int Source #

BLen ByteString Source #

_O(1)_ ByteStrings store their own length.

Instance details

Defined in Binrep.BLen

Methods

blen :: ByteString -> Int Source #

BLen () Source #

_O(1)_ Unit type has length 0.

Instance details

Defined in Binrep.BLen

Methods

blen :: () -> Int Source #

KnownNat (CBLen a) => BLen (ViaCBLen a) Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: ViaCBLen a -> Int Source #

BLen a => BLen (NullTerminated a) Source # 
Instance details

Defined in Binrep.Type.NullTerminated

Methods

blen :: NullTerminated a -> Int Source #

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

Defined in Binrep.Type.Thin

Methods

blen :: Thin a -> Int Source #

BLen a => BLen [a] Source #

_O(n)_ Sum the length of each element of a list.

Instance details

Defined in Binrep.BLen

Methods

blen :: [a] -> Int Source #

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

Defined in Binrep.BLen

Methods

blen :: Either a b -> Int Source #

KnownNat (Length (MagicBytes a)) => BLen (Magic a) Source #

The byte length of a magic is obtained via reifying.

Instance details

Defined in Binrep.Type.Magic

Methods

blen :: Magic a -> Int Source #

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

Defined in Binrep.Type.NullPadded

Methods

blen :: NullPadded n a -> Int Source #

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

Defined in Binrep.Type.Prefix.Size

Methods

blen :: SizePrefixed pfx a -> Int Source #

KnownNat n => BLen (Sized n a) Source # 
Instance details

Defined in Binrep.Type.Sized

Methods

blen :: Sized n a -> Int Source #

KnownNat (CBLen a) => BLen (ByteOrdered end a) Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: ByteOrdered end a -> Int Source #

(BLen l, BLen r) => BLen (l, r) Source #

_O(1)_ Sum tuples.

Instance details

Defined in Binrep.BLen

Methods

blen :: (l, r) -> Int Source #

GenericFoldMap BLen Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type GenericFoldMapM BLen #

type GenericFoldMapC BLen a #

BLen (Refined pr (Refined pl a)) => BLen (Refined (And pl pr) a) Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: Refined (And pl pr) a -> Int Source #

(Prefix 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

Instance details

Defined in Binrep.Type.Prefix.Count

Methods

blen :: CountPrefixed pfx f a -> Int Source #

type GenericFoldMapM BLen Source # 
Instance details

Defined in Binrep.BLen

type GenericFoldMapC BLen a Source # 
Instance details

Defined in Binrep.BLen

blenGenericNonSum :: forall a. (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 a. (Generic a, GFoldMapSum BLen (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.

You must provide a function to obtain the byte length for the prefix tag, via inspecting the reified constructor names. This is regrettably inefficient. Alas. Do write your own instance if you want better performance!

newtype ViaCBLen a Source #

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

Instances

Instances details
KnownNat (CBLen a) => BLen (ViaCBLen a) Source # 
Instance details

Defined in Binrep.BLen

Methods

blen :: ViaCBLen a -> Int Source #

cblen :: forall a. KnownNat (CBLen a) => Int Source #

Reify a type's constant byte length to the term level.