binrep
Safe HaskellNone
LanguageGHC2021

Binrep.Type.Prefix.Count

Documentation

data CountPrefix pfx Source #

Instances

Instances details
(KnownPredicateName (CountPrefix pfx), KnownNat (LenNatMax pfx), Foldable f) => Refine1 (CountPrefix pfx :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

validate1 :: Proxy# (CountPrefix pfx) -> f a -> Maybe RefineFailure #

Predicate (CountPrefix pfx :: Type) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

(KnownPredicateName (CountPrefix pfx), KnownNat (LenNatMax pfx), Foldable f) => Refine (CountPrefix pfx :: Type) (f a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

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

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 :: Type) 
Instance details

Defined in Binrep.Type.Prefix.Count

type CBLen (CountPrefixed pfx f a :: Type) = CBLen pfx + CBLen (f a)
(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

Instance details

Defined in Binrep.Type.Prefix.Count

Methods

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

(LenNat 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 #

(LenNat 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 PredicateName d (CountPrefix pfx :: Type) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

type PredicateName d (CountPrefix pfx :: Type) = ShowParen (d > 9) ("CountPrefix " ++ LenNatName pfx)
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)

type CountPrefixed pfx = Refined1 (CountPrefix pfx) :: (k1 -> Type) -> k1 -> Type Source #

class GetCount (f :: Type -> Type) where Source #

Methods

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

Instances

Instances details
GetCount [] Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

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