isobmff-builder-0.10.5.0: A (bytestring-) builder for the ISO-14496-12 base media file format

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Boxes.BoxFields

Contents

Description

Mini EDSL for labelled box fields. The boxfields can be Scalar or ScalarArrays.

Synopsis

Scalar box fields

type U64 label = Scalar Word64 label Source #

type I64 label = Scalar Int64 label Source #

u64 :: Word64 -> U64 label Source #

i64 :: Int64 -> I64 label Source #

type U32 label = Scalar Word32 label Source #

type I32 label = Scalar Int32 label Source #

u32 :: Word32 -> U32 label Source #

i32 :: Int32 -> I32 label Source #

type U16 label = Scalar Word16 label Source #

type I16 label = Scalar Int16 label Source #

u16 :: Word16 -> U16 label Source #

i16 :: Int16 -> I16 label Source #

type U8 label = Scalar Word8 label Source #

type I8 label = Scalar Int8 label Source #

u8 :: Word8 -> U8 label Source #

i8 :: Int8 -> I8 label Source #

newtype Scalar scalartype label Source #

A numeric box field with a type level label. Note that it has a Num instance. Use the type aliases above, e.g. U8,I8,U16,I16,U32,I32,U64,I64 from above. Use either the smart constructors, e.g. u8,i8,u16,i16,u32,i32,u64,i64 or the Num instance, whereas the constructors might give a bit more safety.

Constructors

Scalar 

Fields

Instances

(KnownNat scalar, Num o) => FromTypeLit Nat (Scalar k o label) scalar Source # 

Methods

fromTypeLit :: proxy scalar v -> scalar Source #

Eq scalartype => Eq (Scalar k scalartype label) Source # 

Methods

(==) :: Scalar k scalartype label -> Scalar k scalartype label -> Bool #

(/=) :: Scalar k scalartype label -> Scalar k scalartype label -> Bool #

Num scalartype => Num (Scalar k scalartype label) Source # 

Methods

(+) :: Scalar k scalartype label -> Scalar k scalartype label -> Scalar k scalartype label #

(-) :: Scalar k scalartype label -> Scalar k scalartype label -> Scalar k scalartype label #

(*) :: Scalar k scalartype label -> Scalar k scalartype label -> Scalar k scalartype label #

negate :: Scalar k scalartype label -> Scalar k scalartype label #

abs :: Scalar k scalartype label -> Scalar k scalartype label #

signum :: Scalar k scalartype label -> Scalar k scalartype label #

fromInteger :: Integer -> Scalar k scalartype label #

Ord scalartype => Ord (Scalar k scalartype label) Source # 

Methods

compare :: Scalar k scalartype label -> Scalar k scalartype label -> Ordering #

(<) :: Scalar k scalartype label -> Scalar k scalartype label -> Bool #

(<=) :: Scalar k scalartype label -> Scalar k scalartype label -> Bool #

(>) :: Scalar k scalartype label -> Scalar k scalartype label -> Bool #

(>=) :: Scalar k scalartype label -> Scalar k scalartype label -> Bool #

max :: Scalar k scalartype label -> Scalar k scalartype label -> Scalar k scalartype label #

min :: Scalar k scalartype label -> Scalar k scalartype label -> Scalar k scalartype label #

Read scalartype => Read (Scalar k scalartype label) Source # 

Methods

readsPrec :: Int -> ReadS (Scalar k scalartype label) #

readList :: ReadS [Scalar k scalartype label] #

readPrec :: ReadPrec (Scalar k scalartype label) #

readListPrec :: ReadPrec [Scalar k scalartype label] #

Show scalartype => Show (Scalar k scalartype label) Source # 

Methods

showsPrec :: Int -> Scalar k scalartype label -> ShowS #

show :: Scalar k scalartype label -> String #

showList :: [Scalar k scalartype label] -> ShowS #

Default scalartype => Default (Scalar k scalartype label) Source # 

Methods

def :: Scalar k scalartype label #

IsBoxContent (Scalar k Int64 label) Source # 

Methods

boxSize :: Scalar k Int64 label -> BoxSize Source #

boxBuilder :: Scalar k Int64 label -> Builder Source #

IsBoxContent (Scalar k Int32 label) Source # 

Methods

boxSize :: Scalar k Int32 label -> BoxSize Source #

boxBuilder :: Scalar k Int32 label -> Builder Source #

IsBoxContent (Scalar k Int16 label) Source # 

Methods

boxSize :: Scalar k Int16 label -> BoxSize Source #

boxBuilder :: Scalar k Int16 label -> Builder Source #

IsBoxContent (Scalar k Int8 label) Source # 

Methods

boxSize :: Scalar k Int8 label -> BoxSize Source #

boxBuilder :: Scalar k Int8 label -> Builder Source #

IsBoxContent (Scalar k Word64 label) Source # 
IsBoxContent (Scalar k Word32 label) Source # 
IsBoxContent (Scalar k Word16 label) Source # 
IsBoxContent (Scalar k Word8 label) Source # 

Methods

boxSize :: Scalar k Word8 label -> BoxSize Source #

boxBuilder :: Scalar k Word8 label -> Builder Source #

relabelScalar :: Scalar t l -> Scalar t l' Source #

Relabel a scalar value, e.g. convert a Scalar U32 "foo" to a Scalar U32 "bar".

Array fields

type U64Arr label size = ScalarArray label size Word64 Source #

u64Arr :: (KnownNat size, KnownSymbol label) => [Word64] -> U64Arr label size Source #

type I64Arr label size = ScalarArray label size Int64 Source #

i64Arr :: (KnownNat size, KnownSymbol label) => [Int64] -> I64Arr label size Source #

type U32Arr label size = ScalarArray label size Word32 Source #

u32Arr :: (KnownNat size, KnownSymbol label) => [Word32] -> U32Arr label size Source #

type I32Arr label size = ScalarArray label size Int32 Source #

i32Arr :: (KnownNat size, KnownSymbol label) => [Int32] -> I32Arr label size Source #

type U16Arr label size = ScalarArray label size Word16 Source #

u16Arr :: (KnownNat size, KnownSymbol label) => [Word16] -> U16Arr label size Source #

type I16Arr label size = ScalarArray label size Int16 Source #

i16Arr :: (KnownNat size, KnownSymbol label) => [Int16] -> I16Arr label size Source #

type U8Arr label size = ScalarArray label size Word8 Source #

u8Arr :: (KnownNat size, KnownSymbol label) => [Word8] -> U8Arr label size Source #

type I8Arr label size = ScalarArray label size Int8 Source #

i8Arr :: (KnownNat size, KnownSymbol label) => [Int8] -> I8Arr label size Source #

newtype ScalarArray label len o where Source #

A box field that is an array of Scalars with a type level label. Use the type aliases, e.g. U8Arr,I8Arr,U16Arr,I16Arr,U32Arr,I32Arr,U64Arr,I64Arr from above. Use the smart constructors, e.g. u8Arr,i8Arr,u16Arr,i16Arr,u32Arr,i32Arr,u64Arr,i64Arr .

Constructors

ScalarArray :: Vector n o -> ScalarArray label n o 

Instances

(SingI [Nat] arr, Num o, SingKind [Nat], KnownNat len, (~) Nat len (Length Nat arr)) => FromTypeLit [Nat] (ScalarArray k label len o) arr Source # 

Methods

fromTypeLit :: proxy arr v -> arr Source #

Eq o => Eq (ScalarArray k label len o) Source # 

Methods

(==) :: ScalarArray k label len o -> ScalarArray k label len o -> Bool #

(/=) :: ScalarArray k label len o -> ScalarArray k label len o -> Bool #

Show o => Show (ScalarArray k label len o) Source # 

Methods

showsPrec :: Int -> ScalarArray k label len o -> ShowS #

show :: ScalarArray k label len o -> String #

showList :: [ScalarArray k label len o] -> ShowS #

(Default o, KnownNat len) => Default (ScalarArray k label len o) Source # 

Methods

def :: ScalarArray k label len o #

(Num o, IsBoxContent (Scalar k o label), KnownNat len) => IsBoxContent (ScalarArray k label len o) Source # 

Methods

boxSize :: ScalarArray k label len o -> BoxSize Source #

boxBuilder :: ScalarArray k label len o -> Builder Source #

fromList :: forall label n o. (KnownSymbol label, KnownNat n) => [o] -> ScalarArray label n o Source #

Internal function

Constant fields

data Constant o v where Source #

Wrapper around a field, e.g. a Scalar or ScalarArray, with a type level value. The wrapped content must implement FromTypeLit. To get the value of a Constant use fromTypeLit.

Constructors

Constant :: Constant o v 

Instances

Default (Constant k k1 o v) Source # 

Methods

def :: Constant k k1 o v #

(IsBoxContent o, FromTypeLit k o v) => IsBoxContent (Constant * k o v) Source # 

Template Fields

data Template o v where Source #

Fields with default values that can be overriden with custom value. Like Constant this is a wrapper around a field, e.g. a Scalar or ScalarArray, with a type level default value. The wrapped content must implement FromTypeLit.

Constructors

Template :: Template o v 
Custom :: o -> Template o v 

Instances

Default (Template k o v) Source # 

Methods

def :: Template k o v #

(IsBoxContent o, FromTypeLit k o v) => IsBoxContent (Template k o v) Source # 

templateValue :: FromTypeLit o v => Template o v -> o Source #

Get a value from a Template.

Conversion from type-level numbers and lists to values

class FromTypeLit o v where Source #

Types that can be constructed from type level value representations.

Minimal complete definition

fromTypeLit

Methods

fromTypeLit :: proxy o v -> o Source #

Instances

KnownSymbol str => FromTypeLit Symbol Text str Source # 

Methods

fromTypeLit :: proxy str v -> str Source #

KnownSymbol str => FromTypeLit Symbol (U32Text label) str Source # 

Methods

fromTypeLit :: proxy str v -> str Source #

(KnownNat scalar, Num o) => FromTypeLit Nat (Scalar k o label) scalar Source # 

Methods

fromTypeLit :: proxy scalar v -> scalar Source #

(SingI [Nat] arr, Num o, SingKind [Nat], KnownNat len, (~) Nat len (Length Nat arr)) => FromTypeLit [Nat] (ScalarArray k label len o) arr Source # 

Methods

fromTypeLit :: proxy arr v -> arr Source #

String/Text field types

newtype FixSizeText len label where Source #

A fixed size string, the first byte is the string length, after the String, the field is padded with 0 bytes. The string must be in UTF8 format.

Constructors

FixSizeText :: Text -> FixSizeText len label 

Instances

IsTextSize len => Default (FixSizeText len label) Source # 

Methods

def :: FixSizeText len label #

IsTextSize len => IsBoxContent (FixSizeText len label) Source # 

Methods

boxSize :: FixSizeText len label -> BoxSize Source #

boxBuilder :: FixSizeText len label -> Builder Source #

type IsTextSize len = (KnownNat len, 1 <= len, len <= 255) Source #

A constraint that matches type level numbers that are valid text sizes for FixSizeTexts.

newtype U32Text label where Source #

Four character strings embedded in a uint32.

Constructors

U32Text :: Word32 -> U32Text label 

Instances

KnownSymbol str => FromTypeLit Symbol (U32Text label) str Source # 

Methods

fromTypeLit :: proxy str v -> str Source #

IsString (U32Text label) Source # 

Methods

fromString :: String -> U32Text label #

Default (U32Text label) Source # 

Methods

def :: U32Text label #

IsBoxContent (U32Text label) Source #