| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry
Description
Detailed visual sample description.
Synopsis
- newtype VideoSampleEntry c where
- VideoSampleEntry :: (U16 "pre_defined" :+ (Constant (U16 "reserved") 0 :+ (U16 "width" :+ (U16 "height" :+ (Template (U32 "horizresolution") 4718592 :+ (Template (U32 "vertresolution") 4718592 :+ (Constant (U32 "reserved") 0 :+ (Template (U16 "frame_count") 1 :+ (FixSizeText 32 "compressorname" :+ (Template (U16 "depth") 24 :+ (Template (I16 "pre_defined") 65535 :+ (Maybe (Box CleanAperture) :+ (Maybe (Box PixelAspectRatio) :+ ([Box SomeColourInformation] :+ c)))))))))))))) -> VideoSampleEntry c
 
 - cleanAperture :: CleanAperture -> Box CleanAperture
 - newtype CleanAperture where
 - pixelAspectRatio :: PixelAspectRatio -> Box PixelAspectRatio
 - newtype PixelAspectRatio where
- PixelAspectRatio :: (U32 "hSpacing" :+ U32 "vSpacing") -> PixelAspectRatio
 
 - colourInformation :: ColourType p -> ColourInformation p
 - onScreenColourInformation :: ColourType OnScreenColours -> ColourInformation OnScreenColours
 - restrictedICCProfileColourInformation :: ColourType RestrictedICCProfile -> ColourInformation RestrictedICCProfile
 - unrestrictedICCProfileColourInformation :: ColourType UnrestrictedICCProfile -> ColourInformation UnrestrictedICCProfile
 - data SomeColourInformation where
- SomeColourInformation :: forall (profile :: ColourTypeProfile). IsBoxContent (ColourInformation profile) => !(ColourInformation profile) -> SomeColourInformation
 
 - newtype ColourInformation (profile :: ColourTypeProfile) where
- ColourInformation :: (Constant (U32Text "colour_type") (ColourTypeCode profile) :+ ColourType profile) -> ColourInformation profile
 
 - data ColourTypeProfile
 - type family ColourType (p :: ColourTypeProfile) where ...
 - data FullRangeFlag
 - type family ColourTypeCode (p :: ColourTypeProfile) :: Symbol where ...
 
Documentation
newtype VideoSampleEntry c where 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.
Constructors
| VideoSampleEntry :: (U16 "pre_defined" :+ (Constant (U16 "reserved") 0 :+ (U16 "width" :+ (U16 "height" :+ (Template (U32 "horizresolution") 4718592 :+ (Template (U32 "vertresolution") 4718592 :+ (Constant (U32 "reserved") 0 :+ (Template (U16 "frame_count") 1 :+ (FixSizeText 32 "compressorname" :+ (Template (U16 "depth") 24 :+ (Template (I16 "pre_defined") 65535 :+ (Maybe (Box CleanAperture) :+ (Maybe (Box PixelAspectRatio) :+ ([Box SomeColourInformation] :+ c)))))))))))))) -> VideoSampleEntry c | 
Instances
| Default c => Default (VideoSampleEntry c) Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods def :: VideoSampleEntry c #  | |
| IsBoxContent c => IsBoxContent (VideoSampleEntry c) Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods boxSize :: VideoSampleEntry c -> BoxSize Source # boxBuilder :: VideoSampleEntry c -> Builder Source #  | |
| type GetHandlerType (VideoSampleEntry c) Source # | |
| type BoxTypeSymbol (VideoSampleEntry c :: Type) Source # | |
Clean Aperture sub box
cleanAperture :: CleanAperture -> Box CleanAperture Source #
Construct a CleanAperture (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 | 
Instances
| Default CleanAperture Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods def :: CleanAperture #  | |
| IsBoxContent CleanAperture Source # | |
| IsBox CleanAperture Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Associated Types type BoxContent CleanAperture :: Type Source # Methods toBoxType :: proxy CleanAperture -> BoxType Source #  | |
| type BoxContent CleanAperture Source # | |
| type BoxTypeSymbol CleanAperture Source # | |
Pixel aspect ratio sub box
pixelAspectRatio :: PixelAspectRatio -> Box PixelAspectRatio Source #
Construct a PixelAspectRatio (sub-) Box
newtype PixelAspectRatio where Source #
The pixel aspect ratio.
Constructors
| PixelAspectRatio :: (U32 "hSpacing" :+ U32 "vSpacing") -> PixelAspectRatio | 
Instances
| Default PixelAspectRatio Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods def :: PixelAspectRatio #  | |
| IsBoxContent PixelAspectRatio Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods boxSize :: PixelAspectRatio -> BoxSize Source # boxBuilder :: PixelAspectRatio -> Builder Source #  | |
| IsBox PixelAspectRatio Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Associated Types type BoxContent PixelAspectRatio :: Type Source # Methods toBoxType :: proxy PixelAspectRatio -> BoxType Source #  | |
| type BoxContent PixelAspectRatio Source # | |
| type BoxTypeSymbol PixelAspectRatio Source # | |
Colour information sub box
colourInformation :: ColourType p -> ColourInformation p Source #
Construct a ColourInformation (sub-) Box
onScreenColourInformation :: ColourType OnScreenColours -> ColourInformation OnScreenColours Source #
Construct a ColourInformation (sub-) Box from OnScreenColours
restrictedICCProfileColourInformation :: ColourType RestrictedICCProfile -> ColourInformation RestrictedICCProfile Source #
Construct a ColourInformation (sub-) Box from RestrictedICCProfile
unrestrictedICCProfileColourInformation :: ColourType UnrestrictedICCProfile -> ColourInformation UnrestrictedICCProfile Source #
Construct a ColourInformation (sub-) Box from UnrestrictedICCProfile
data SomeColourInformation where Source #
A wrapper that hides the concrete ColourTypeProfile of a
 ColourInformation.
Constructors
| SomeColourInformation :: forall (profile :: ColourTypeProfile). IsBoxContent (ColourInformation profile) => !(ColourInformation profile) -> SomeColourInformation | 
Instances
| IsBoxContent SomeColourInformation Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods  | |
| IsBox SomeColourInformation Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Associated Types type BoxContent SomeColourInformation :: Type Source # Methods toBoxType :: proxy SomeColourInformation -> BoxType Source #  | |
| IsBoxContent [Box SomeColourInformation] Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods boxSize :: [Box SomeColourInformation] -> BoxSize Source # boxBuilder :: [Box SomeColourInformation] -> Builder Source #  | |
| type BoxContent SomeColourInformation Source # | |
| type BoxTypeSymbol SomeColourInformation Source # | |
newtype ColourInformation (profile :: ColourTypeProfile) where Source #
Profile dependent colour information
Constructors
| ColourInformation :: (Constant (U32Text "colour_type") (ColourTypeCode profile) :+ ColourType profile) -> ColourInformation profile | 
Instances
| Default (ColourType profile) => Default (ColourInformation profile) Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods def :: ColourInformation profile #  | |
| (KnownSymbol (ColourTypeCode profile), IsBoxContent (ColourType profile)) => IsBoxContent (ColourInformation profile) Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods boxSize :: ColourInformation profile -> BoxSize Source # boxBuilder :: ColourInformation profile -> Builder Source #  | |
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.
Constructors
| IsFullRange | |
| IsNotFullRange | 
Instances
| Default FullRangeFlag Source # | |
Defined in Data.ByteString.IsoBaseFileFormat.Boxes.VisualSampleEntry Methods def :: FullRangeFlag #  | |
| IsBoxContent FullRangeFlag Source # | |
type family ColourTypeCode (p :: ColourTypeProfile) :: Symbol where ... Source #
Return the color type four letter code for a ColourTypeProfile.
Equations
| ColourTypeCode OnScreenColours = "nclx" | |
| ColourTypeCode RestrictedICCProfile = "rICC" | |
| ColourTypeCode UnrestrictedICCProfile = "prof" |