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.VisualSampleEntry

Contents

Description

Detailed visual sample description.

Synopsis

Documentation

visualSampleEntry :: KnownSymbol (BoxTypeSymbol (SampleEntry VideoTrack (VideoCoding codec))) => VideoCoding codec -> U16 "data_reference_index" -> SampleEntry VideoTrack (VideoCoding codec) -> Box (SampleEntry VideoTrack (VideoCoding codec)) Source #

Construct a visual sample entry box

data family VideoCoding (c :: Symbol) Source #

A coproduct of video codec types

Instances

Default (SampleEntry * VideoTrack (VideoCoding c)) Source # 
IsBoxContent (SampleEntry * VideoTrack (VideoCoding c)) Source # 
data VideoCoding "mp4v" Source #

Simple default MPEG-4 video

data VideoCoding "mp4v" = Mpeg4Avc
data SampleEntry * VideoTrack (VideoCoding c) Source #

Fields if visual sample entries. A depth of 0x0018 means colour image with no alpha. The horizresolution and vertresolution of 0x00480000 means 72 dpi. The frame_count indicates the number of video frames per sample.

data SampleEntry * VideoTrack (VideoCoding c) = VideoSampleEntry ((:+) (U16 Symbol "pre_defined") ((:+) (Constant * Nat (U16 Symbol "reserved") 0) ((:+) (U16 Symbol "width") ((:+) (U16 Symbol "height") ((:+) (Template Nat (U32 Symbol "horizresolution") 4718592) ((:+) (Template Nat (U32 Symbol "vertresolution") 4718592) ((:+) (Constant * Nat (U32 Symbol "reserved") 0) ((:+) (Template Nat (U16 Symbol "frame_count") 1) ((:+) (FixSizeText 32 "compressorname") ((:+) (Template Nat (U16 Symbol "depth") 24) ((:+) (Template Nat (I16 Symbol "pre_defined") 65535) ((:+) (Maybe (Box CleanAperture)) ((:+) (Maybe (Box PixelAspectRatio)) [Box SomeColourInformation])))))))))))))
type BoxTypeSymbol * (VideoCoding c) Source # 

Clean Aperture sub box

newtype CleanAperture where Source #

The clean aperture settings

Constructors

CleanAperture :: (U32 "cleanApertureWidthN" :+ (U32 "cleanApertureWidthD" :+ (U32 "cleanApertureHeightN" :+ (U32 "cleanApertureHeightD" :+ (U32 "horizOffN" :+ (U32 "horizOffD" :+ (U32 "vertOffN" :+ U32 "vertOffD"))))))) -> CleanAperture 

Pixel aspect ratio sub box

Colour information sub box

newtype ColourInformation profile where Source #

Profile dependent colour information

Constructors

ColourInformation :: (Constant (U32Text "colour_type") (ColourTypeCode profile) :+ ColourType profile) -> ColourInformation profile 

data ColourTypeProfile Source #

Colour type profiles

Constructors

OnScreenColours

PTM_COLOR_INFO from A.7.2 of ISO/IEC 29199-2, mind the full range flag.

RestrictedICCProfile

A restricted ICC.1 (2010) profile

UnrestrictedICCProfile

An unrestricted IEC ISO-15076 part 1, ICC.1 (2010) profile

type family ColourType (p :: ColourTypeProfile) where ... Source #

Profile dependent colour information family

Equations

ColourType OnScreenColours = U16 "colour_primaries" :+ (U16 "transfer_characteristics" :+ (U16 "matrix_coefficients" :+ FullRangeFlag)) 
ColourType RestrictedICCProfile = Text 
ColourType UnrestrictedICCProfile = Text 

data FullRangeFlag Source #

The full range flag, note the different bit layout compared to PTM_COLOR_INFO in ISO 29199-2.

type family ColourTypeCode (p :: ColourTypeProfile) :: Symbol where ... Source #

Return the color type four letter code for a ColourTypeProfile.