module Data.ByteString.IsoBaseFileFormat.Boxes.SegmentType where
import Data.ByteString.IsoBaseFileFormat.Box
import Data.ByteString.IsoBaseFileFormat.ReExports
instance IsBox SegmentType where
  type BoxContent SegmentType = SegmentType
type instance BoxTypeSymbol SegmentType = "styp"
segmentTypeBox :: SegmentType -> Box SegmentType
segmentTypeBox = Box
data SegmentType =
  SegmentType {majorBrand :: !FourCc 
           ,minorVersion :: !Word32 
           ,compatibleBrands :: ![FourCc]}  
instance IsBoxContent SegmentType where
  boxSize (SegmentType maj _ver comps) = boxSize maj + 4 + sum (boxSize <$> comps)
  boxBuilder (SegmentType maj ver comps) =
    boxBuilder maj <> word32BE ver <> mconcat (boxBuilder <$> comps)