binrep-0.5.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 # 
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 # 
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 -> Poke 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 [] Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

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