binrep-0.3.1: Encode precise binary representations directly in types
Safe HaskellNone
LanguageHaskell2010

Binrep.Type.LenPfx

Synopsis

Documentation

data LenPfx (size :: ISize) (end :: Endianness) a Source #

Holy shit - no need to do a smart constructor, it's simply impossible to instantiate invalid values of this type!

Constructors

forall n.(KnownNat n, n <= IMax 'U size) => LenPfx 

Fields

Instances

Instances details
Generic (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Associated Types

type Rep (LenPfx size end a) :: Type -> Type #

Methods

from :: LenPfx size end a -> Rep (LenPfx size end a) x #

to :: Rep (LenPfx size end a) x -> LenPfx size end a #

Show a => Show (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

showsPrec :: Int -> LenPfx size end a -> ShowS #

show :: LenPfx size end a -> String #

showList :: [LenPfx size end a] -> ShowS #

(BLen a, itype ~ I 'U size end, KnownNat (CBLen itype)) => BLen (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Associated Types

type CBLen (LenPfx size end a) :: Natural Source #

Methods

blen :: LenPfx size end a -> BLenT Source #

(itype ~ I 'U size end, irep ~ IRep 'U size, Get itype, Integral irep, Get a, KnownNat (MaxBound irep)) => Get (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

get :: Getter (LenPfx size end a) Source #

(itype ~ I 'U size end, irep ~ IRep 'U size, Put a, Put itype, Num irep) => Put (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

put :: LenPfx size end a -> Builder Source #

Eq a => Eq (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

(==) :: LenPfx size end a -> LenPfx size end a -> Bool #

(/=) :: LenPfx size end a -> LenPfx size end a -> Bool #

(KnownNat (MaxBound (IRep 'U size)), Show a, Typeable a, Typeable size, Typeable end) => Strengthen (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

strengthen :: Weak (LenPfx size end a) -> Validation (NonEmpty StrengthenFail) (LenPfx size end a) #

Weaken (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Associated Types

type Weak (LenPfx size end a) #

Methods

weaken :: LenPfx size end a -> Weak (LenPfx size end a) #

type Rep (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

type Rep (LenPfx size end a) = Rec0 (LenPfx size end a)
type CBLen (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

type CBLen (LenPfx size end a) = TypeError ('Text "No CBLen associated family instance defined for " :<>: 'ShowType (LenPfx size end a)) :: Natural
type Weak (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

type Weak (LenPfx size end a) = [a]

vsEq :: forall a n m. (Eq a, KnownNat n, KnownNat m) => Vector n a -> Vector m a -> Bool Source #

asLenPfx :: forall size end n a irep. (irep ~ IRep 'U size, KnownNat n, KnownNat (MaxBound irep)) => Vector n a -> Maybe (LenPfx size end a) Source #

lenPfxFromList :: forall size end a irep. (irep ~ IRep 'U size, KnownNat (MaxBound irep)) => [a] -> Maybe (LenPfx size end a) Source #

lenPfxSize :: Num (IRep 'U size) => LenPfx size end a -> I 'U size end Source #

getLenPfx :: forall size end a itype irep. (itype ~ I 'U size end, irep ~ IRep 'U size, Get itype, Integral irep, KnownNat (MaxBound irep)) => Getter a -> Getter (LenPfx size end a) Source #