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

Binrep.BLen.Simple

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.

Synopsis

Documentation

class BLen a where Source #

Methods

blen :: a -> Int Source #

Instances

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

Defined in Binrep.BLen.Simple

Methods

blen :: Void -> Int Source #

BLen Int16 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Int16 -> Int Source #

BLen Int32 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Int32 -> Int Source #

BLen Int64 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Int64 -> Int Source #

BLen Int8 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Int8 -> Int Source #

BLen Word16 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Word16 -> Int Source #

BLen Word32 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Word32 -> Int Source #

BLen Word64 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Word64 -> Int Source #

BLen Word8 Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Word8 -> Int Source #

BLen Write Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: Write -> Int Source #

BLen ByteString Source #

Length of a bytestring is fairly obvious.

Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: ByteString -> Int Source #

BLen () Source #

Unit type has length 0.

Instance details

Defined in Binrep.BLen.Simple

Methods

blen :: () -> Int Source #

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

Defined in Binrep.BLen.Simple

Methods

blen :: CBLenly 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 (Binreply a) Source # 
Instance details

Defined in Binrep.Via

Methods

blen :: Binreply 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.Simple

Methods

blen :: [a] -> Int Source #

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

Defined in Binrep.BLen.Simple

Methods

blen :: Either a b -> Int Source #

BLen a => BLen (Endian end a) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

blen :: Endian end a -> Int Source #

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

Defined in Binrep.Type.Magic

Methods

blen :: Magic 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 #

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

Sum tuples.

Instance details

Defined in Binrep.BLen.Simple

Methods

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

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

Defined in Binrep.Type.Prefix.Count

Methods

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

newtype BLen' a Source #

Constructors

BLen' 

Fields

Instances

Instances details
Num a => Monoid (BLen' a) Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

mempty :: BLen' a #

mappend :: BLen' a -> BLen' a -> BLen' a #

mconcat :: [BLen' a] -> BLen' a #

Num a => Semigroup (BLen' a) Source # 
Instance details

Defined in Binrep.BLen.Simple

Methods

(<>) :: BLen' a -> BLen' a -> BLen' a #

sconcat :: NonEmpty (BLen' a) -> BLen' a #

stimes :: Integral b => b -> BLen' a -> BLen' a #

GenericFoldMap (BLen' Int) Source # 
Instance details

Defined in Binrep.BLen.Simple

Associated Types

type GenericFoldMapC (BLen' Int) a #

type GenericFoldMapC (BLen' Int) a Source # 
Instance details

Defined in Binrep.BLen.Simple

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

Measure the byte length of a term of the non-sum type a via its Generic instance.

blenGenericSum :: forall {cd} {f} {asserts} a. (Generic a, Rep a ~ D1 cd f, GFoldMapSum 'SumOnly (BLen' Int) f, asserts ~ '['NoEmpty, 'NeedSum], ApplyGCAsserts asserts f) => (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 CBLenly a Source #

Deriving via wrapper for types which may derive a BLen instance through an existing IsCBLen instance.

Examples of such types include machine integers, and explicitly-sized types (e.g. Binrep.Type.Sized).

Constructors

CBLenly 

Fields

Instances

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

Defined in Binrep.BLen.Simple

Methods

blen :: CBLenly a -> Int Source #

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

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