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

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

Description

Connect a sample description to a data reference via an index into the data reference entry table.

Synopsis

Documentation

sampleEntry :: U16 "data_reference_index" -> handlerSpecific -> Box (SampleEntry handlerSpecific) Source #

Create a SampleEntry Box from the data reference index and the HandlerType specific SampleEntry instance.

newtype SampleEntry handlerSpecific where Source #

A common header for all specific sample entries, the BoxContent of the abstract SampleEntry is SampleEntry (SampleEntry h f).

Constructors

SampleEntry :: (Constant (U8Arr "reserved" 6) '[0, 0, 0, 0, 0, 0] :+ (U16 "data_reference_index" :+ handlerSpecific)) -> SampleEntry handlerSpecific 
Instances
Default handlerSpecific => Default (SampleEntry handlerSpecific) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

Methods

def :: SampleEntry handlerSpecific #

IsBoxContent handlerSpecific => IsBoxContent (SampleEntry handlerSpecific) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

Methods

boxSize :: SampleEntry handlerSpecific -> BoxSize Source #

boxBuilder :: SampleEntry handlerSpecific -> Builder Source #

(IsBoxContent handlertype, KnownSymbol (BoxTypeSymbol handlertype)) => IsBox (SampleEntry handlertype) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

Associated Types

type BoxContent (SampleEntry handlertype) :: Type Source #

Methods

toBoxType :: proxy (SampleEntry handlertype) -> BoxType Source #

type BoxContent (SampleEntry handlertype) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

type BoxContent (SampleEntry handlertype) = SampleEntry handlertype
type IsRuleConform (Box (SampleEntry handlerSpecificEntry) :: Type) (MatchSampleEntry handlerType :: Type) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

type IsRuleConform (Box (SampleEntry handlerSpecificEntry) :: Type) (MatchSampleEntry handlerType :: Type) = HandlerTypeCode (GetHandlerType handlerSpecificEntry) == HandlerTypeCode handlerType
type BoxTypeSymbol (SampleEntry handlerSpecific :: Type) Source #

The BoxTypeSymbol of sample entry is exactly the format type index of the SampleEntry family.

Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

type BoxTypeSymbol (SampleEntry handlerSpecific :: Type) = BoxTypeSymbol handlerSpecific

data MatchSampleEntry :: HandlerType -> Type Source #

Use this in IsMediaFileFormats BoxLayout to range over any specific SampleEntry, disregarding the second parameter (that indicates low-level format, protocol or codec characteristics). Add a GetHandlerType instance for MatchSampleEntry to match a sample type specific entry.

Instances
type IsRuleConform (Box (SampleEntry handlerSpecificEntry) :: Type) (MatchSampleEntry handlerType :: Type) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Boxes.SampleEntry

type IsRuleConform (Box (SampleEntry handlerSpecificEntry) :: Type) (MatchSampleEntry handlerType :: Type) = HandlerTypeCode (GetHandlerType handlerSpecificEntry) == HandlerTypeCode handlerType