isobmff-0.13.0.0: A parser and generator for the ISO-14496-12/14 base media file format

Safe HaskellNone
LanguageHaskell2010

Data.Type.BitRecords.Builder.LazyByteStringBuilder

Contents

Synopsis

Documentation

bitBuilderBox :: forall (record :: BitRecord). BitStringBuilderHoley (Proxy record) BuilderBox => Proxy record -> ToBitStringBuilder (Proxy record) BuilderBox Source #

Create a Builder from a BitRecord and store it in a BuilderBox

wrapBitBuilderBox :: forall (record :: BitRecord) wrapped. BitStringBuilderHoley (Proxy record) wrapped => (BuilderBox -> wrapped) -> Proxy record -> ToBitStringBuilder (Proxy record) wrapped Source #

Like bitBuilderBox, but toFunction the result and accept as an additional parameter a wrapper function to wrap the final result (the BuilderBox) and toFunction the whole machiner.

bitBuilderBoxHoley :: forall (record :: BitRecord) r. BitStringBuilderHoley (Proxy record) r => Proxy record -> FunctionBuilder BuilderBox r (ToBitStringBuilder (Proxy record) r) Source #

Create a Builder from a BitRecord and store it in a BuilderBox; return a FunctionBuilder monoid that does that on toFunction

Low-level interface to building BitRecords and other things

flushBitStringBuilder :: BitStringBuilderState -> BitStringBuilderState Source #

Write the partial buffer contents using any number of word8 The unwritten parts of the bittr buffer are at the top. If the

    63  ...  (63-off-1)(63-off)  ...  0
    ^^^^^^^^^^^^^^^^^^^
Relevant bits start to the top!

appendBitString :: BitString -> BitStringBuilder Source #

Write all the bits, in chunks, filling and writing the BitString in the BitStringBuilderState as often as necessary.

appendStrictByteString :: ByteString -> BitStringBuilder Source #

Write all the b*y*tes, into the BitStringBuilderState this allows general purposes non-byte aligned builders.

BitString construction from BitRecords

class BitStringBuilderHoley a r where Source #

Associated Types

type ToBitStringBuilder a r Source #

Instances
BitStringBuilderHoley BitString r Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder BitString r :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldFlag)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldFlag)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldI8)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldI8)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldI16)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldI16)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldI32)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldI32)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldI64)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldI64)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldU8)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldU8)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldU16)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldU16)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldU32)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldU32)) a :: Type Source #

BitStringBuilderHoley (Proxy (MkField MkFieldU64)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldU64)) a :: Type Source #

(KnownNat v, BitStringBuilderHoley (Proxy f) a, ToBitStringBuilder (Proxy f) a ~ (rt -> a), Num rt) => BitStringBuilderHoley (Proxy (f := v)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (f := v)) a :: Type Source #

(KnownNat v, BitStringBuilderHoley (Proxy f) a, ToBitStringBuilder (Proxy f) a ~ (x -> a), Num x) => BitStringBuilderHoley (Proxy (f := NegativeNat v)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (f := NegativeNat v)) a :: Type Source #

(KnownNat v, BitStringBuilderHoley (Proxy f) a, ToBitStringBuilder (Proxy f) a ~ (x -> a), Num x) => BitStringBuilderHoley (Proxy (f := PositiveNat v)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (f := PositiveNat v)) a :: Type Source #

BitRecordFieldSize f ~ 1 => BitStringBuilderHoley (Proxy (f := False)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (f := False)) a :: Type Source #

BitRecordFieldSize f ~ 1 => BitStringBuilderHoley (Proxy (f := True)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (f := True)) a :: Type Source #

BitStringBuilderHoley (Proxy nested) a => BitStringBuilderHoley (Proxy (LabelF l nested)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (LabelF l nested)) a :: Type Source #

KnownChunkSize s => BitStringBuilderHoley (Proxy (MkField (MkFieldBits :: BitField (B s) Nat s))) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldBits)) a :: Type Source #

KnownChunkSize size => BitStringBuilderHoley (Proxy (MkField (MkFieldCustom :: BitField (EnumValue e) e size))) r Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

Associated Types

type ToBitStringBuilder (Proxy (MkField MkFieldCustom)) r :: Type Source #

(KnownNat (FromEnum e v), KnownChunkSize size) => BitStringBuilderHoley (Proxy (f := v)) r Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

Associated Types

type ToBitStringBuilder (Proxy (f := v)) r :: Type Source #

BitStringBuilderHoley (Proxy (Eval r)) a => BitStringBuilderHoley (Proxy r) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy r) a :: Type Source #

BitStringBuilderHoley (Proxy EmptyBitRecord) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy EmptyBitRecord) a :: Type Source #

BitStringBuilderHoley (Proxy f) a => BitStringBuilderHoley (Proxy (BitRecordMember f)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (BitRecordMember f)) a :: Type Source #

(BitStringBuilderHoley (Proxy l) (ToBitStringBuilder (Proxy r) a), BitStringBuilderHoley (Proxy r) a) => BitStringBuilderHoley (Proxy (BitRecordAppend l r)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToBitStringBuilder (Proxy (BitRecordAppend l r)) a :: Type Source #

BitRecordField instances

Labbeled Fields

Bool

Bits

Naturals

Signed

BitRecord instances

BitRecordMember

AppendedBitRecords

EmptyBitRecord and '...Pretty'

Tracing/Debug Printing

printBuilder :: Builder -> String Source #

Print a Builder to a space seperated series of hexa-decimal bytes.