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

Binrep.Type.Prefix.Count

Documentation

data CountPrefix (pfx :: Type) Source #

Instances

Instances details
(KnownNat (Max pfx), Foldable f, Typeable pfx) => Predicate1 (CountPrefix pfx :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

validate1 :: forall (a :: k). Proxy (CountPrefix pfx) -> f a -> Maybe RefineException #

(KnownNat (Max pfx), Foldable f, Typeable pfx) => Predicate (CountPrefix pfx :: Type) (f a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

validate :: Proxy (CountPrefix pfx) -> f a -> Maybe RefineException #

IsCBLen (CountPrefixed pfx f a :: Type) Source #

We can know byte length at compile time _if_ we know it for the prefix and the list-like.

This is extremely unlikely, because then what counting are we even performing for the list-like? But it's a valid instance.

Instance details

Defined in Binrep.Type.Prefix.Count

Associated Types

type CBLen (CountPrefixed pfx f a) :: Natural 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 #

(Prefix pfx, GetCount f, Get pfx, Get a) => Get (CountPrefixed pfx f a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

get :: Getter (CountPrefixed pfx f a) 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 CBLen (CountPrefixed pfx f a :: Type) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

type CBLen (CountPrefixed pfx f a :: Type) = CBLen pfx + CBLen (f a)

class GetCount f where Source #

Methods

getCount :: Get a => Int -> Getter (f a) Source #

Instances

Instances details
GetCount List Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

getCount :: Get a => Int -> Getter [a] Source #