Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- class IsBoxContent (BoxContent t) => IsBoxType t where
- type BoxContent t
- class IsBoxContent a where
- data Box brand b where
- Box :: (IsBoxType b, IsBrandConform brand (Just b) ts) => BoxContent b -> Boxes brand ts -> Box brand b
- data Boxes brand boxTypes where
- ($:) :: (Boxes brand '[l] -> r) -> Box brand l -> r
- singletonBox :: Box brand l -> Boxes brand '[l]
- closedBox :: (IsBoxType t, IsBrandConform brand (Just t) '[]) => BoxContent t -> Box brand t
- containerBox :: (IsBoxType t, IsBrandConform brand (Just t) ts, BoxContent t ~ ()) => Boxes brand ts -> Box brand t
- data BoxSize
- data BoxSizeExtension = BoxSizeExtension BoxSize
- data BoxType
- newtype FourCc = FourCc (Char, Char, Char, Char)
- data BoxTypeExtension = BoxTypeExtension BoxType
Box Type Classes
class IsBoxContent (BoxContent t) => IsBoxType t where Source #
Base class for all (abstractphantomnormal-) types that represent boxes
type BoxContent t Source #
toBoxType :: proxy t -> BoxContent t -> BoxType Source #
IsBoxType * FileType Source # | File Type Box |
IsBoxType * Handler Source # | |
IsBoxType * Media Source # | |
IsBoxType * MediaData Source # | |
IsBoxType * MediaInformation Source # | |
IsBoxType * Movie Source # | |
IsBoxType * ProgressiveDownload Source # | |
IsBoxType * Skip Source # | |
IsBoxType * SpecificMediaHeader Source # | |
IsBoxType * Track Source # | |
KnownNat v => IsBoxType * (MediaHeader v) Source # | |
KnownNat version => IsBoxType * (MovieHeader version) Source # | |
KnownNat version => IsBoxType * (TrackHeader version) 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.
Data types
data Box brand b where Source #
A type that wraps the contents of a box and the box type.
Box :: (IsBoxType b, IsBrandConform brand (Just b) ts) => BoxContent b -> Boxes brand ts -> Box brand b |
IsBoxContent (Box brand cnt) Source # | |
data Boxes brand boxTypes where Source #
A heterogenous collection of boxes.
NoBoxes :: Boxes brand '[] | |
(:.) :: Box brand l -> Boxes brand r -> Boxes brand (l ': r) infixr 2 | |
(:|) :: Box brand l -> Box brand r -> Boxes brand '[l, r] infixr 2 | |
(:<>) :: Boxes brand l -> Boxes brand r -> Boxes brand (l :++ r) infixr 1 |
IsBoxContent (Boxes brand bs) Source # | |
singletonBox :: Box brand l -> Boxes brand '[l] Source #
closedBox :: (IsBoxType t, IsBrandConform brand (Just t) '[]) => BoxContent t -> Box brand t Source #
A box that contains no nested boxes.
containerBox :: (IsBoxType t, IsBrandConform brand (Just t) ts, BoxContent t ~ ()) => Boxes brand ts -> Box brand t Source #
A box that contains no fields, but nested boxes.
Box Size and Type
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.
A box has a type, this is the value level representation for the box type.
A type containin a printable four letter character code.
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.