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

Binrep.BLen

Synopsis

Documentation

newtype WithCBLen a Source #

Newtype wrapper for defining BLen instances which are allowed to assume the existence of a valid CBLen family instance.

Constructors

WithCBLen 

Fields

Instances

Instances details
KnownNat (CBLen a + CBLen b) => BLen (WithCBLen (a, b)) Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen (WithCBLen (a, b)) :: Natural Source #

Methods

blen :: WithCBLen (a, b) -> BLenT Source #

KnownNat (CBLen a) => BLen (WithCBLen [a]) Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen (WithCBLen [a]) :: Natural Source #

Methods

blen :: WithCBLen [a] -> BLenT Source #

type CBLen (WithCBLen (a, b)) Source # 
Instance details

Defined in Binrep.BLen

type CBLen (WithCBLen (a, b)) = CBLen a + CBLen b
type CBLen (WithCBLen [a]) Source # 
Instance details

Defined in Binrep.BLen

type CBLen (WithCBLen [a]) = TypeError ('Text "No CBLen associated family instance defined for " :<>: 'ShowType (WithCBLen [a])) :: Natural

class BLen a where Source #

The length in bytes of a value of the given type can be known on the cheap e.g. by reading a length field, or using compile time information.

Some binary representation building blocks require the notion of length in bytes in order to handle, e.g. null padding. One may always obtain this by serializing the value, then reading out the length of the output bytestring. But in most cases, we can be much more efficient.

  • Certain primitives have a size known at compile time, irrelevant of the value. A Word64 is always 8 bytes; some data null-padded to n bytes is exactly n bytes long.
  • For simple ADTs, it's often possible to calculate length in bytes via pattern matching and some numeric operations. Very little actual work.

This type class enables each type to implement its own efficient method of byte length calculation. Aim to write something that plainly feels more efficient than full serialization. If that doesn't feel possible, you might be working with a type ill-suited for binary representation.

A thought: Some instances could be improved by reifying CBLen. But it would mess up all the deriving, and it feels like too minor an improvement to be worthwhile supporting, writing a bunch of newtype wrappers, etc.

Minimal complete definition

Nothing

Associated Types

type CBLen a :: Natural Source #

The length in bytes of any value of the given type is constant.

Many binary representation primitives are constant, or may be designed to "store" their size in their type. This is a stronger statement about their length than just blen.

This is now an associated type family of the BLen type class in hopes of simplifying the binrep framework.

type CBLen a = TypeError ('Text "No CBLen associated family instance defined for " :<>: 'ShowType a)

Methods

blen :: a -> BLenT Source #

The length in bytes of the serialized value.

The default implementation reifies the constant length for the type. If a type-wide constant length is not defined, it will fail at compile time.

default blen :: KnownNat (CBLen a) => a -> BLenT Source #

Instances

Instances details
BLen Void Source #

Impossible to put a byte length to Void.

Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Void :: Natural Source #

Methods

blen :: Void -> BLenT Source #

BLen Int16 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Int16 :: Natural Source #

Methods

blen :: Int16 -> BLenT Source #

BLen Int32 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Int32 :: Natural Source #

Methods

blen :: Int32 -> BLenT Source #

BLen Int64 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Int64 :: Natural Source #

Methods

blen :: Int64 -> BLenT Source #

BLen Int8 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Int8 :: Natural Source #

Methods

blen :: Int8 -> BLenT Source #

BLen Word16 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Word16 :: Natural Source #

Methods

blen :: Word16 -> BLenT Source #

BLen Word32 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Word32 :: Natural Source #

Methods

blen :: Word32 -> BLenT Source #

BLen Word64 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Word64 :: Natural Source #

Methods

blen :: Word64 -> BLenT Source #

BLen Word8 Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen Word8 :: Natural Source #

Methods

blen :: Word8 -> BLenT Source #

BLen DCS Source # 
Instance details

Defined in Binrep.Example

Associated Types

type CBLen DCS :: Natural Source #

Methods

blen :: DCS -> BLenT Source #

BLen DSS Source # 
Instance details

Defined in Binrep.Example

Associated Types

type CBLen DSS :: Natural Source #

Methods

blen :: DSS -> BLenT Source #

BLen DU Source # 
Instance details

Defined in Binrep.Example

Associated Types

type CBLen DU :: Natural Source #

Methods

blen :: DU -> BLenT Source #

BLen DX Source # 
Instance details

Defined in Binrep.Example

Associated Types

type CBLen DX :: Natural Source #

Methods

blen :: DX -> BLenT Source #

BLen Tar Source # 
Instance details

Defined in Binrep.Example.Tar

Associated Types

type CBLen Tar :: Natural Source #

Methods

blen :: Tar -> BLenT Source #

BLen Tiff Source # 
Instance details

Defined in Binrep.Example.Tiff

Associated Types

type CBLen Tiff :: Natural Source #

Methods

blen :: Tiff -> BLenT Source #

BLen WavHeader Source # 
Instance details

Defined in Binrep.Example.Wav

Associated Types

type CBLen WavHeader :: Natural Source #

Methods

blen :: WavHeader -> BLenT Source #

BLen ByteString Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen ByteString :: Natural Source #

KnownNat (CBLen a + CBLen b) => BLen (WithCBLen (a, b)) Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen (WithCBLen (a, b)) :: Natural Source #

Methods

blen :: WithCBLen (a, b) -> BLenT Source #

KnownNat (CBLen a) => BLen (WithCBLen [a]) Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen (WithCBLen [a]) :: Natural Source #

Methods

blen :: WithCBLen [a] -> BLenT Source #

(bs ~ MagicBytes (TiffMagic end), KnownNat (Length bs)) => BLen (TiffBody end) Source # 
Instance details

Defined in Binrep.Example.Tiff

Associated Types

type CBLen (TiffBody end) :: Natural Source #

Methods

blen :: TiffBody end -> BLenT Source #

KnownNat base => BLen (AsciiNat base) Source #

The bytelength of an AsciiNat is the number of digits in the number in the given base. We can calculate this generically with great efficiency using GHC primitives.

Instance details

Defined in Binrep.Type.AsciiNat

Associated Types

type CBLen (AsciiNat base) :: Natural Source #

Methods

blen :: AsciiNat base -> BLenT Source #

BLen (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

Associated Types

type CBLen (AsByteString 'C) :: Natural Source #

(itype ~ I 'U size end, irep ~ IRep 'U size, KnownNat (CBLen irep)) => BLen (AsByteString ('Pascal size end)) Source # 
Instance details

Defined in Binrep.Type.ByteString

Associated Types

type CBLen (AsByteString ('Pascal size end)) :: Natural Source #

Methods

blen :: AsByteString ('Pascal size end) -> BLenT Source #

KnownSymbol str => BLen (MagicUTF8 str) Source # 
Instance details

Defined in Binrep.Type.Magic.UTF8

Associated Types

type CBLen (MagicUTF8 str) :: Natural Source #

Methods

blen :: MagicUTF8 str -> BLenT Source #

BLen a => BLen [a] Source #
O(n)
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen [a] :: Natural Source #

Methods

blen :: [a] -> BLenT Source #

KnownNat n => BLen (TarNat n) Source # 
Instance details

Defined in Binrep.Example.Tar

Associated Types

type CBLen (TarNat n) :: Natural Source #

Methods

blen :: TarNat n -> BLenT Source #

KnownNat (Length (MagicBytes a)) => BLen (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Associated Types

type CBLen (Magic a) :: Natural Source #

Methods

blen :: Magic a -> BLenT Source #

KnownNat n => BLen (NullPadded n a) Source # 
Instance details

Defined in Binrep.Type.NullPadded

Associated Types

type CBLen (NullPadded n a) :: Natural Source #

Methods

blen :: NullPadded n a -> BLenT Source #

KnownNat n => BLen (Sized n a) Source # 
Instance details

Defined in Binrep.Type.Sized

Associated Types

type CBLen (Sized n a) :: Natural Source #

Methods

blen :: Sized n a -> BLenT Source #

BLen a => BLen (Vector n a) Source # 
Instance details

Defined in Binrep.Type.Vector

Associated Types

type CBLen (Vector n a) :: Natural Source #

Methods

blen :: Vector n a -> BLenT Source #

(BLen a, BLen b) => BLen (a, b) Source # 
Instance details

Defined in Binrep.BLen

Associated Types

type CBLen (a, b) :: Natural Source #

Methods

blen :: (a, b) -> BLenT Source #

KnownNat (CBLen (I sign size end)) => BLen (I sign size end) Source # 
Instance details

Defined in Binrep.Type.Int

Associated Types

type CBLen (I sign size end) :: Natural Source #

Methods

blen :: I sign size end -> BLenT Source #

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

type BLenT = Int Source #

typeNatToBLen :: forall n. KnownNat n => BLenT Source #

cblen :: forall a n. (n ~ CBLen a, KnownNat n) => BLenT Source #

Reify a type's constant byte length to the term level.