Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Binrep.CBLen
Synopsis
- class IsCBLen a where
- cblen :: forall a. KnownNat (CBLen a) => Int
- cblen# :: forall a. KnownNat (CBLen a) => Int#
- cblenProxy# :: forall a. KnownNat (CBLen a) => Proxy# a -> Int#
- data CBLenSym a
- type CBLenGenericSum (w :: Type) a = GCBLen w (Rep a)
- type CBLenGenericNonSum a = GTFoldMapCAddition CBLenSym (Rep a)
- type family GCBLen w (gf :: k -> Type) :: Natural where ...
- type family GCBLenSum (gf :: k -> Type) where ...
- type family MaybeEq a b where ...
- type family GCBLenCaseMaybe a where ...
- data JustX a b
- data NothingX
Documentation
Instances
IsCBLen Int16 Source # | |
IsCBLen Int32 Source # | |
IsCBLen Int64 Source # | |
IsCBLen Int8 Source # | |
IsCBLen Word16 Source # | |
IsCBLen Word32 Source # | |
IsCBLen Word64 Source # | |
IsCBLen Word8 Source # | |
IsCBLen DMagic Source # | |
IsCBLen DStruct Source # | |
IsCBLen () Source # | |
Defined in Binrep.CBLen | |
Generic a => IsCBLen (GenericallyNonSum a :: Type) Source # | Deriving via this instance necessitates |
Defined in Binrep.CBLen Associated Types type CBLen (GenericallyNonSum a) :: Natural Source # | |
IsCBLen (Magic a :: Type) Source # | The byte length of a magic is known at compile time. |
IsCBLen (NullPadded n a :: Type) Source # | |
Defined in Binrep.Type.NullPadded Associated Types type CBLen (NullPadded n a) :: Natural Source # | |
IsCBLen (SizePrefixed pfx a :: Type) Source # | |
Defined in Binrep.Type.Prefix.Size Associated Types type CBLen (SizePrefixed pfx a) :: Natural Source # | |
IsCBLen (Sized n a :: Type) Source # | |
IsCBLen a => IsCBLen (ByteOrdered end a :: Type) Source # | |
Defined in Binrep.CBLen Associated Types type CBLen (ByteOrdered end a) :: Natural Source # | |
(IsCBLen l, IsCBLen r) => IsCBLen ((l, r) :: Type) Source # | |
Defined in Binrep.CBLen | |
IsCBLen (Refined pr (Refined pl a)) => IsCBLen (Refined (And pl pr) a :: Type) Source # | |
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. |
Defined in Binrep.Type.Prefix.Count Associated Types type CBLen (CountPrefixed pfx f a) :: Natural Source # |
cblen :: forall a. KnownNat (CBLen a) => Int Source #
Reify a type's constant byte length to the term level.
Generically derive CBLen
type family instances.
A type having a valid CBLen
instance usually indicates one of the following:
- it's a primitive, or extremely simple
- it holds size information in its type
- it's constructed from other constant byte length types
The first two cases must be handled manually. The third case is where Haskell generics excel, and the one this module targets.
You may derive a CBLen
type generically for a non-sum type with
instance IsCBLen a where type CBLen a = CBLenGenericNonSum a
You may attempt to derive a CBLen
type generically for a sum type with
instance IsCBLen a where type CBLen a = CBLenGenericSum w a
As with other generic sum type handlers, you must provide the type used to store
the sum tag for sum types. That sum tag type must have a CBLen
, and every
constructor must have the same CBLen
for a CBLen
to be calculated. Not many types will fit those criteria, and the code is not well-tested.
type CBLenGenericSum (w :: Type) a = GCBLen w (Rep a) Source #
Using this necessitates UndecidableInstances
.
type CBLenGenericNonSum a = GTFoldMapCAddition CBLenSym (Rep a) Source #
Using this necessitates UndecidableInstances
.
type family GCBLenCaseMaybe a where ... Source #
I don't know how to pattern match in types without writing type families.
Equations
GCBLenCaseMaybe (JustX n _) = n | |
GCBLenCaseMaybe NothingX = TypeError ('Text "Two constructors didn't have equal constant size." ':$$: 'Text "Sry dunno how to thread errors thru LOL") |