isobmff-builder-0.9.0.0: A (bytestring-) builder for the ISO-14496-12 base media file format

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Boxes.FullBox

Description

Full Boxes

Synopsis

Documentation

data FullBox version t 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 :: BoxVersion version -> BoxFlags 24 -> t -> FullBox version t 

Instances

(KnownNat version, IsBoxContent t) => IsBoxContent (FullBox Nat version t) Source # 

Methods

boxSize :: FullBox Nat version t -> BoxSize Source #

boxBuilder :: FullBox Nat version t -> Builder Source #

fullBox :: (IsBoxType t, ValidContainerBox brand t ts, BoxContent t ~ FullBox version c) => BoxVersion version -> BoxFlags 24 -> c -> Boxes brand ts -> Box brand t Source #

Create a FullBox from a BoxVersion and BoxFlags

closedFullBox :: (IsBoxType t, ValidBox brand t, BoxContent t ~ FullBox version c) => BoxVersion version -> BoxFlags 24 -> c -> Box brand t Source #

Create a FullBox from a BoxVersion and BoxFlags without nested boxes.

type BoxVersion v = Template (U8 "fullbox-version") v Source #

The box version (in a FullBox) is a single byte

newtype BoxFlags bits Source #

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

Constructors

BoxFlags Integer 

Instances

Eq (BoxFlags k bits) Source # 

Methods

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

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

Num (BoxFlags k bits) Source # 

Methods

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

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

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

negate :: BoxFlags k bits -> BoxFlags k bits #

abs :: BoxFlags k bits -> BoxFlags k bits #

signum :: BoxFlags k bits -> BoxFlags k bits #

fromInteger :: Integer -> BoxFlags k bits #

Show (BoxFlags k bits) Source # 

Methods

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

show :: BoxFlags k bits -> String #

showList :: [BoxFlags k bits] -> ShowS #

KnownNat bits => Bits (BoxFlags Nat bits) Source # 

Methods

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

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

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

complement :: BoxFlags Nat bits -> BoxFlags Nat bits #

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

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

zeroBits :: BoxFlags Nat bits #

bit :: Int -> BoxFlags Nat bits #

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

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

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

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

bitSizeMaybe :: BoxFlags Nat bits -> Maybe Int #

bitSize :: BoxFlags Nat bits -> Int #

isSigned :: BoxFlags Nat bits -> Bool #

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

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

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

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

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

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

popCount :: BoxFlags Nat bits -> Int #

KnownNat bits => IsBoxContent (BoxFlags Nat bits) Source #

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