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

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Util.FullBox

Description

Full Boxes

Synopsis

Documentation

data FullBox t version 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 # 

Methods

def :: FullBox t version #

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

Associated Types

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

Methods

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

type BoxTypeSymbol * (FullBox t v) Source # 
type BoxContent (FullBox t v) Source # 
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 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.