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

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Boxes.Box

Contents

Description

Definition of the most basic element in an ISOBMFF file: a box. See Chapter 4 in the standard document. A box is a container with a type, a size, some data and some nested boxes. The standard defines - among other characteristics - available box types and their semantics, the fields they contain and how they are nested into each other. This library tries to capture some of these characteristics using modern Haskell type system features, in order to provide compile time checks for (partial) standard compliance.

Synopsis

Box Type Classes

class (KnownSymbol (BoxTypeSymbol t), IsBoxContent (BoxContent t)) => IsBox t where Source #

Base class for all (abstractphantomnormal-) types that represent boxes

Associated Types

type BoxContent t Source #

Methods

toBoxType :: proxy t -> BoxType Source #

Instances

IsBox DataInformation Source # 

Associated Types

type BoxContent DataInformation :: * Source #

IsBox FileType Source #

File Type Box

Associated Types

type BoxContent FileType :: * Source #

Methods

toBoxType :: proxy FileType -> BoxType Source #

IsBox Media Source # 

Associated Types

type BoxContent Media :: * Source #

Methods

toBoxType :: proxy Media -> BoxType Source #

IsBox MediaData Source # 

Associated Types

type BoxContent MediaData :: * Source #

Methods

toBoxType :: proxy MediaData -> BoxType Source #

IsBox MediaInformation Source # 

Associated Types

type BoxContent MediaInformation :: * Source #

IsBox Movie Source # 

Associated Types

type BoxContent Movie :: * Source #

Methods

toBoxType :: proxy Movie -> BoxType Source #

IsBox Skip Source # 

Associated Types

type BoxContent Skip :: * Source #

Methods

toBoxType :: proxy Skip -> BoxType Source #

IsBox Track Source # 

Associated Types

type BoxContent Track :: * Source #

Methods

toBoxType :: proxy Track -> BoxType Source #

IsBox DataEntryUrn Source # 

Associated Types

type BoxContent DataEntryUrn :: * Source #

IsBox DataEntryUrl Source # 

Associated Types

type BoxContent DataEntryUrl :: * Source #

IsBox DataReference Source # 

Associated Types

type BoxContent DataReference :: * Source #

IsBox Handler Source # 

Associated Types

type BoxContent Handler :: * Source #

Methods

toBoxType :: proxy Handler -> BoxType Source #

IsBox ProgressiveDownload Source # 
IsBox NullMediaHeader Source # 

Associated Types

type BoxContent NullMediaHeader :: * Source #

IsBox HintMediaHeader Source # 

Associated Types

type BoxContent HintMediaHeader :: * Source #

IsBox SoundMediaHeader Source # 

Associated Types

type BoxContent SoundMediaHeader :: * Source #

IsBox VideoMediaHeader Source # 

Associated Types

type BoxContent VideoMediaHeader :: * Source #

IsBox b => IsBox (Box b) Source # 

Associated Types

type BoxContent (Box b) :: * Source #

Methods

toBoxType :: proxy (Box b) -> BoxType Source #

IsBox (MediaHeader v) Source # 

Associated Types

type BoxContent (MediaHeader v) :: * Source #

Methods

toBoxType :: proxy (MediaHeader v) -> BoxType Source #

IsBox (MovieHeader version) Source # 

Associated Types

type BoxContent (MovieHeader version) :: * Source #

Methods

toBoxType :: proxy (MovieHeader version) -> BoxType Source #

IsBox (TrackHeader version) Source # 

Associated Types

type BoxContent (TrackHeader version) :: * Source #

Methods

toBoxType :: proxy (TrackHeader version) -> BoxType Source #

IsBox b => IsBox (ContainerBox b bs) Source # 

Associated Types

type BoxContent (ContainerBox b bs) :: * Source #

Methods

toBoxType :: proxy (ContainerBox b bs) -> BoxType Source #

(KnownNat v, IsBox t) => IsBox (FullBox t v) Source # 

Associated Types

type BoxContent (FullBox t v) :: * Source #

Methods

toBoxType :: proxy (FullBox t v) -> BoxType Source #

type family BoxTypeSymbol t :: Symbol Source #

A type family used by the type-level consistency checks. It is required that an instance of this type family exists for every IsBox instance. This family could not be associative since it is used by type families that cannot have type class constraints.

Instances

type BoxTypeSymbol DataInformation Source # 
type BoxTypeSymbol FileType Source # 
type BoxTypeSymbol FileType = "ftyp"
type BoxTypeSymbol Media Source # 
type BoxTypeSymbol Media = "mdia"
type BoxTypeSymbol MediaData Source # 
type BoxTypeSymbol MediaData = "mdat"
type BoxTypeSymbol MediaInformation Source # 
type BoxTypeSymbol Movie Source # 
type BoxTypeSymbol Movie = "moov"
type BoxTypeSymbol Skip Source # 
type BoxTypeSymbol Skip = "skip"
type BoxTypeSymbol Track Source # 
type BoxTypeSymbol Track = "trak"
type BoxTypeSymbol DataEntryUrn Source # 
type BoxTypeSymbol DataEntryUrl Source # 
type BoxTypeSymbol DataReference Source # 
type BoxTypeSymbol Handler Source # 
type BoxTypeSymbol Handler = "hdlr"
type BoxTypeSymbol ProgressiveDownload Source # 
type BoxTypeSymbol NullMediaHeader Source # 
type BoxTypeSymbol HintMediaHeader Source # 
type BoxTypeSymbol SoundMediaHeader Source # 
type BoxTypeSymbol VideoMediaHeader Source # 
type BoxTypeSymbol (Box b) Source # 
type BoxTypeSymbol (MediaHeader v) Source # 
type BoxTypeSymbol (MediaHeader v) = "mdhd"
type BoxTypeSymbol (MovieHeader v) Source # 
type BoxTypeSymbol (MovieHeader v) = "mvhd"
type BoxTypeSymbol (TrackHeader version) Source # 
type BoxTypeSymbol (TrackHeader version) = "tkhd"
type BoxTypeSymbol (ContainerBox b bs) Source # 
type BoxTypeSymbol (FullBox t v) Source # 

class IsBoxContent a where Source #

Types that go into a box. A box content is a piece of data that can be reused in different instances of IsBox. It has no BoxType and hence defines no box.

Minimal complete definition

boxSize, boxBuilder

Instances

IsBoxContent () Source #

An empty box content can by represented by () (i.e. unit).

Methods

boxSize :: () -> BoxSize Source #

boxBuilder :: () -> Builder Source #

IsBoxContent ByteString Source #

Trivial instance for ByteString

IsBoxContent Text Source #

This Text instance writes a null terminated UTF-8 string.

IsBoxContent BoxTypeExtension Source # 
IsBoxContent FourCc Source # 
IsBoxContent BoxType Source # 
IsBoxContent BoxSizeExtension Source # 
IsBoxContent BoxSize Source # 
IsBoxContent FileType Source # 
IsBoxContent MediaData Source # 
IsBoxContent Language Source # 
IsBoxContent Skip Source # 
IsBoxContent DataEntryUrn Source # 
IsBoxContent DataEntryUrl Source # 
IsBoxContent DataReference Source # 
IsBoxContent HandlerType Source # 
IsBoxContent Handler Source # 
IsBoxContent NullMediaHeader Source # 
IsBoxContent HintMediaHeader Source # 
IsBoxContent SoundMediaHeader Source # 
IsBoxContent VideoMediaHeader Source # 
IsBoxContent a => IsBoxContent (Maybe a) Source #

This instance writes zero bytes for Nothing and delegates on Just.

IsBoxContent (Boxes bs) Source # 
IsBoxContent (Box cnt) Source # 

Methods

boxSize :: Box cnt -> BoxSize Source #

boxBuilder :: Box cnt -> Builder Source #

IsBoxContent (ApplyVersioned c) Source # 
IsBoxContent (MediaHeader v) Source # 
IsBoxContent (MovieHeader version) Source # 
IsBoxContent (TrackHeader version) Source # 
(IsBoxContent p, IsBoxContent c) => IsBoxContent ((:+) p c) Source # 

Methods

boxSize :: (p :+ c) -> BoxSize Source #

boxBuilder :: (p :+ c) -> Builder Source #

IsBoxContent (ContainerBox b bs) Source # 
KnownNat bits => IsBoxContent (BoxFlags Nat bits) Source #

Get the number of bytes required to store a number of bits.

(IsBox t, KnownNat v) => IsBoxContent (FullBox t v) Source # 
IsBoxContent (Versioned v0 v1 version) Source # 

Methods

boxSize :: Versioned v0 v1 version -> BoxSize Source #

boxBuilder :: Versioned v0 v1 version -> Builder Source #

(IsBoxContent o, FromTypeLit k o v) => IsBoxContent (Template k o v) Source # 
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 #

(IsBoxContent o, FromTypeLit k o v) => IsBoxContent (Constant * k o v) Source # 
(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 #

Data types

data Box b where Source #

A type that wraps the contents of a box and the box type.

Constructors

Box :: IsBox b => BoxContent b -> Box b 

Instances

IsBoxContent (Box cnt) Source # 

Methods

boxSize :: Box cnt -> BoxSize Source #

boxBuilder :: Box cnt -> Builder Source #

IsBox b => IsBox (Box b) Source # 

Associated Types

type BoxContent (Box b) :: * Source #

Methods

toBoxType :: proxy (Box b) -> BoxType Source #

type BoxTypeSymbol (Box b) Source # 
type BoxContent (Box b) Source # 
type IsRuleConform * * (Box b) (Box r) Source # 
type IsRuleConform * * (Box b) (ContainerBox b' rules) Source # 
type IsRuleConform * * (Box b) (ContainerBox b' rules) = (&&) (IsContainerBox b) ((&&) (IsRuleConform * * (Box b) (Box b')) (IsRuleConform * * (ChildBoxes b) (Boxes rules)))

data ContainerBox b bs where Source #

Compose BoxContent and Boxes under the Constraint that they are composable.

Constructors

ContainerBox :: IsBox b => BoxContent b -> Boxes bs -> ContainerBox b bs 

Instances

data Boxes boxTypes where Source #

A heterogenous collection of boxes.

Constructors

NoBoxes :: Boxes '[] 
(:.) :: Box l -> Boxes r -> Boxes (Box l ': r) infixr 2 
(:<>) :: Boxes l -> Boxes r -> Boxes (l :++ r) infixr 1

Create a Boxes collection from two Boxes

(:|) :: Box l -> Box r -> Boxes '[Box l, Box r] infixr 2 

Instances

($:) :: (Boxes '[Box l] -> r) -> Box l -> r infixr 3 Source #

Apply a function to a Boxes collection containing only a single Box.

singletonBox :: Box l -> Boxes '[Box l] Source #

Create a Boxes collection with a single Box.

typeListLength :: forall a proxy ts. (KnownNat (Length ts), Num a) => proxy ts -> a Source #

Get the elements in a type level array

containerBox :: IsBox t => BoxContent t -> Boxes ts -> Box (ContainerBox t ts) Source #

A box that contains no fields, but nested boxes.

Box Size and Type

data BoxSize Source #

The size of the box. If the size is limited to a (fixed) value, it can be provided as a Word64 which will be represented as either a 32bit compact size or as 64 bit largesize. If UnlimitedSize is used, the box extends to the end of the file.

data BoxSizeExtension Source #

The BoxSize can be > 2^32 in which case an BoxSizeExtension must be added after the type field.

data BoxType Source #

A box has a type, this is the value level representation for the box type.

Constructors

StdType FourCc

FourCc can be used as boxType in Box, standard four letter character code, e.g. ftyp

CustomBoxType String

CustomBoxType defines custom boxTypes in Boxes.

parseBoxType :: KnownSymbol t => proxy t -> BoxType Source #

Create a box type from a Symbol. Parse the symbol value, if it's a four charachter code, then return that as StdType otherwise parse a UUID (TODO) and return a CustomBoxType.

newtype FourCc Source #

A type containin a printable four letter character code.

Constructors

FourCc (Char, Char, Char, Char) 

data BoxTypeExtension Source #

When using custom types extra data must be written after the extra size information. Since the box type and the optional custom box type are not guaranteed to be consequtive, this type handles the second part seperately.

IsBoxContent instances

Box concatenation

data a :+ b infixr 3 Source #

Box content composition

Constructors

a :+ b infixr 3 

Instances

(Default a, Default b) => Default ((:+) a b) Source # 

Methods

def :: a :+ b #

(IsBoxContent p, IsBoxContent c) => IsBoxContent ((:+) p c) Source # 

Methods

boxSize :: (p :+ c) -> BoxSize Source #

boxBuilder :: (p :+ c) -> Builder Source #

Type Layout Rule Matchers

type OM b bs = ContainerBox b bs Source #

Mandatory, container box, exactly one

type OO b bs = OnceOptionalX (ContainerBox b bs) Source #

Optional, container box, zero or one

type SM b bs = SomeMandatoryX (ContainerBox b bs) Source #

Mandatory, container box, one or more

type SO b bs = SomeOptionalX (ContainerBox b bs) Source #

Optional, container box, zero or more

type OM_ b = Box b Source #

Mandatory, exactly one, no children

type OO_ b = OnceOptionalX (Box b) Source #

Optional, zero or one, no children

type SM_ b = SomeMandatoryX (Box b) Source #

Mandatory, one or more, no children

type SO_ b = SomeOptionalX (Box b) Source #

Optional, zero or more, no children

type family IsContainerBox t :: Bool where ... Source #

type family ChildBoxes c where ... Source #

Equations

ChildBoxes (ContainerBox a as) = Boxes as