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

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Util.FullBox

Description

Full Boxes

Synopsis

Documentation

data FullBox t (version :: Nat) where Source #

A FullBox contains an extra version and a flags field. In this implementation it is wrapped around the rest of the box content. This enforces that the FullBox header fields are always at the beginning - at least as long as this module hides the FullBox constructor ;)

Constructors

FullBox :: (KnownNat version, IsBox t) => !(BoxFlags 24) -> !(BoxContent t) -> FullBox t version 
Instances
(KnownNat version, IsBox t, Default (BoxContent t)) => Default (FullBox t version) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

Methods

def :: FullBox t version #

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

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

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

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

Associated Types

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

Methods

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

type BoxTypeSymbol (FullBox t v :: Type) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

type BoxContent (FullBox t v) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

type BoxContent (FullBox t v) = FullBox t v

fullBox :: (KnownNat v, IsBox t) => BoxFlags 24 -> BoxContent t -> Box (FullBox t v) Source #

Create a FullBox from a BoxVersion and BoxFlags

newtype BoxFlags bits Source #

In addition to a version there can be 24 bits for custom flags etc in a FullBox.

Constructors

BoxFlags Integer 
Instances
Eq (BoxFlags bits) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

Methods

(==) :: BoxFlags bits -> BoxFlags bits -> Bool #

(/=) :: BoxFlags bits -> BoxFlags bits -> Bool #

Num (BoxFlags bits) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

Methods

(+) :: BoxFlags bits -> BoxFlags bits -> BoxFlags bits #

(-) :: BoxFlags bits -> BoxFlags bits -> BoxFlags bits #

(*) :: BoxFlags bits -> BoxFlags bits -> BoxFlags bits #

negate :: BoxFlags bits -> BoxFlags bits #

abs :: BoxFlags bits -> BoxFlags bits #

signum :: BoxFlags bits -> BoxFlags bits #

fromInteger :: Integer -> BoxFlags bits #

Show (BoxFlags bits) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

Methods

showsPrec :: Int -> BoxFlags bits -> ShowS #

show :: BoxFlags bits -> String #

showList :: [BoxFlags bits] -> ShowS #

KnownNat bits => Bits (BoxFlags bits) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox

Methods

(.&.) :: BoxFlags bits -> BoxFlags bits -> BoxFlags bits #

(.|.) :: BoxFlags bits -> BoxFlags bits -> BoxFlags bits #

xor :: BoxFlags bits -> BoxFlags bits -> BoxFlags bits #

complement :: BoxFlags bits -> BoxFlags bits #

shift :: BoxFlags bits -> Int -> BoxFlags bits #

rotate :: BoxFlags bits -> Int -> BoxFlags bits #

zeroBits :: BoxFlags bits #

bit :: Int -> BoxFlags bits #

setBit :: BoxFlags bits -> Int -> BoxFlags bits #

clearBit :: BoxFlags bits -> Int -> BoxFlags bits #

complementBit :: BoxFlags bits -> Int -> BoxFlags bits #

testBit :: BoxFlags bits -> Int -> Bool #

bitSizeMaybe :: BoxFlags bits -> Maybe Int #

bitSize :: BoxFlags bits -> Int #

isSigned :: BoxFlags bits -> Bool #

shiftL :: BoxFlags bits -> Int -> BoxFlags bits #

unsafeShiftL :: BoxFlags bits -> Int -> BoxFlags bits #

shiftR :: BoxFlags bits -> Int -> BoxFlags bits #

unsafeShiftR :: BoxFlags bits -> Int -> BoxFlags bits #

rotateL :: BoxFlags bits -> Int -> BoxFlags bits #

rotateR :: BoxFlags bits -> Int -> BoxFlags bits #

popCount :: BoxFlags bits -> Int #

KnownNat bits => IsBoxContent (BoxFlags bits) Source #

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

Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.FullBox