{-# LANGUAGE UndecidableInstances #-}
module Data.ByteString.IsoBaseFileFormat.Box where
import Data.ByteString.IsoBaseFileFormat.ReExports
import Data.Singletons.Prelude.List (type (++),
Length)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.ByteString as B
class (KnownSymbol (BoxTypeSymbol t), IsBoxContent (BoxContent t))
=> IsBox (t :: Type) where
type BoxContent t
type BoxContent t = t
toBoxType :: proxy t -> BoxType
toBoxType _ = parseBoxType (Proxy :: Proxy (BoxTypeSymbol t))
type family BoxTypeSymbol (t :: k) :: Symbol
class IsBoxContent a where
boxSize :: a -> BoxSize
boxBuilder :: a -> Builder
data Box b where
Box ::
!(BoxContent b) -> Box b
instance IsBox b => IsBox (Box b) where
type BoxContent (Box b) = BoxContent b
toBoxType _ = toBoxType (Proxy :: Proxy b)
type instance BoxTypeSymbol (Box b) = BoxTypeSymbol b
instance IsBox cnt => IsBoxContent (Box cnt) where
boxBuilder b@(Box cnt) = sB <> tB <> sExtB <> tExtB <> cntB
where s = boxSize b
t = toBoxType b
sB = boxBuilder s
sExtB = boxBuilder (BoxSizeExtension s)
tB = boxBuilder t
tExtB = boxBuilder (BoxTypeExtension t)
cntB = boxBuilder cnt
boxSize b@(Box cnt) = sPayload + boxSize (BoxSizeExtension sPayload)
where sPayload =
boxSize (BoxSize undefined) + boxSize t + boxSize cnt +
boxSize (BoxTypeExtension t)
t = toBoxType b
instance (Default (BoxContent b)) => Default (Box b) where
def = Box def
data ContainerBox b (bs :: [Type]) where
ContainerBox :: IsBox b => !(BoxContent b) -> !(Boxes bs) -> ContainerBox b bs
instance (IsBox b) => IsBox (ContainerBox b bs)
type instance BoxTypeSymbol (ContainerBox b bs) = BoxTypeSymbol b
instance IsBoxContent (ContainerBox b bs) where
boxSize (ContainerBox c bs) = boxSize (c :+ bs)
boxBuilder (ContainerBox c bs) = boxBuilder (c :+ bs)
data Boxes (boxTypes :: [Type]) where
NoBoxes :: Boxes '[]
(:.) :: IsBox l => !(Box l) -> !(Boxes r) -> Boxes (Box l ': r)
(:<>) :: !(Boxes l) -> !(Boxes r) -> Boxes (l ++ r)
(:|) :: (IsBox l, IsBox r) => !(Box l) -> !(Box r) -> Boxes '[Box l, Box r]
infixr 1 :<>
infixr 2 :.
infixr 2 :|
infixr 3 $:
($:) :: IsBox l => (Boxes '[Box l] -> r) -> Box l -> r
($:) f = f . singletonBox
singletonBox :: IsBox l => Box l -> Boxes '[Box l]
singletonBox b = b :. NoBoxes
typeListLength :: forall a proxy (ts :: [k]) . (KnownNat (Length ts), Num a)
=> proxy ts -> a
typeListLength _ = fromIntegral (natVal (Proxy :: Proxy (Length ts)))
instance IsBoxContent (Boxes bs) where
boxSize NoBoxes = 0
boxSize (l :. r) = boxSize l + boxSize r
boxSize (l :| r) = boxSize l + boxSize r
boxSize (l :<> r) = boxSize l + boxSize r
boxBuilder NoBoxes = mempty
boxBuilder (l :. r) = boxBuilder l <> boxBuilder r
boxBuilder (l :| r) = boxBuilder l <> boxBuilder r
boxBuilder (l :<> r) = boxBuilder l <> boxBuilder r
containerBox :: (IsBox t)
=> BoxContent t -> Boxes ts -> Box (ContainerBox t ts)
containerBox c bs = Box (ContainerBox c bs)
data BoxSize
= UnlimitedSize
| BoxSize !Word64
deriving (Show,Eq)
fromBoxSize :: Num a => a -> BoxSize -> a
fromBoxSize !fallback UnlimitedSize = fallback
fromBoxSize _fallback (BoxSize !s) = fromIntegral s
instance IsBoxContent BoxSize where
boxSize _ = BoxSize 4
boxBuilder UnlimitedSize = word32BE 0
boxBuilder (BoxSize n) =
word32BE $
if n < (4294967296 :: Word64)
then fromIntegral n
else 1
instance Num BoxSize where
(+) UnlimitedSize _ = UnlimitedSize
(+) _ UnlimitedSize = UnlimitedSize
(+) (BoxSize l) (BoxSize r) = BoxSize (l + r)
(-) UnlimitedSize _ = UnlimitedSize
(-) _ UnlimitedSize = UnlimitedSize
(-) (BoxSize l) (BoxSize r) = BoxSize (l - r)
(*) UnlimitedSize _ = UnlimitedSize
(*) _ UnlimitedSize = UnlimitedSize
(*) (BoxSize l) (BoxSize r) = BoxSize (l * r)
abs UnlimitedSize = UnlimitedSize
abs (BoxSize n) = BoxSize (abs n)
signum UnlimitedSize = UnlimitedSize
signum (BoxSize n) = BoxSize (signum n)
fromInteger n = BoxSize $ fromInteger n
newtype BoxSizeExtension =
BoxSizeExtension BoxSize
instance IsBoxContent BoxSizeExtension where
boxBuilder (BoxSizeExtension UnlimitedSize) = mempty
boxBuilder (BoxSizeExtension (BoxSize n)) =
if n < 4294967296
then mempty
else word64BE n
boxSize (BoxSizeExtension UnlimitedSize) = 0
boxSize (BoxSizeExtension (BoxSize n)) =
BoxSize $
if n < 4294967296
then 0
else 8
data BoxType
=
StdType !FourCc
|
CustomBoxType !String
deriving (Show,Eq)
parseBoxType :: KnownSymbol t => proxy t -> BoxType
parseBoxType px = StdType (fromString (symbolVal px))
newtype FourCc =
FourCc (Char,Char,Char,Char)
deriving (Show,Eq)
instance IsString FourCc where
fromString !str
| length str == 4 =
let [!a,!b,!c,!d] = str
in FourCc (a,b,c,d)
| otherwise =
error ("cannot make a 'FourCc' of a String which isn't exactly 4 bytes long: " ++
show str ++ " has a length of " ++ show (length str))
instance IsBoxContent FourCc where
boxSize _ = 4
boxBuilder (FourCc (!a,!b,!c,!d)) = putW a <> putW b <> putW c <> putW d
where putW = word8 . fromIntegral . fromEnum
instance IsBoxContent BoxType where
boxSize _ = boxSize (FourCc undefined)
boxBuilder t =
case t of
StdType x -> boxBuilder x
CustomBoxType _ -> boxBuilder (FourCc ('u','u','i','d'))
newtype BoxTypeExtension =
BoxTypeExtension BoxType
instance IsBoxContent BoxTypeExtension where
boxSize (BoxTypeExtension !(StdType _)) = 0
boxSize (BoxTypeExtension !(CustomBoxType _)) = 16 * 4
boxBuilder (BoxTypeExtension !(StdType _)) = mempty
boxBuilder (BoxTypeExtension !(CustomBoxType str)) =
mconcat (map (word8 . fromIntegral . fromEnum)
(take (16 * 4) str) ++
repeat (word8 0))
instance IsBoxContent () where
boxSize _ = 0
boxBuilder _ = mempty
instance IsBoxContent B.ByteString where
boxSize = fromIntegral . B.length
boxBuilder = byteString
instance IsBoxContent T.Text where
boxSize = (1+) . fromIntegral . T.length
boxBuilder txt = boxBuilder (T.encodeUtf8 txtNoNulls) <> word8 0
where txtNoNulls = T.map (\c -> if c == '\0' then ' ' else c) txt
instance IsBoxContent a => IsBoxContent (Maybe a) where
boxSize = maybe 0 boxSize
boxBuilder = maybe mempty boxBuilder
data a :+ b = !a :+ !b
infixr 3 :+
instance (IsBoxContent p,IsBoxContent c) => IsBoxContent (p :+ c) where
boxSize (p :+ c) = boxSize p + boxSize c
boxBuilder (p :+ c) = boxBuilder p <> boxBuilder c
instance (Default a, Default b) => Default (a :+ b) where
def = def :+ def
instance IsBoxContent c => IsBoxContent (Tagged s c) where
boxSize = boxSize . untag
boxBuilder = boxBuilder . untag
newtype ListContent sizeType contentType =
ListContent [contentType]
instance (Num sizeType, IsBoxContent sizeType, IsBoxContent contentType)
=> IsBoxContent (ListContent sizeType contentType) where
boxSize (ListContent es) =
boxSize (fromIntegral (length es) :: sizeType) + sum (boxSize <$> es)
boxBuilder (ListContent es) =
boxBuilder (fromIntegral (length es) :: sizeType)
<> fold (boxBuilder <$> es)
instance Default (ListContent sizeTupe contentType) where
def = ListContent []
instance IsBoxContent Word8 where
boxSize _ = 1
boxBuilder = word8
instance IsBoxContent Word16 where
boxSize _ = 2
boxBuilder = word16BE
instance IsBoxContent Word32 where
boxSize _ = 4
boxBuilder = word32BE
instance IsBoxContent Word64 where
boxSize _ = 8
boxBuilder = word64BE
instance IsBoxContent Int8 where
boxSize _ = 1
boxBuilder = int8
instance IsBoxContent Int16 where
boxSize _ = 2
boxBuilder = int16BE
instance IsBoxContent Int32 where
boxSize _ = 4
boxBuilder = int32BE
instance IsBoxContent Int64 where
boxSize _ = 8
boxBuilder = int64BE
instance IsBoxContent BuilderWithSize where
boxSize (MkBuilderWithSize !s _) = fromIntegral s
boxBuilder (MkBuilderWithSize _ !b) = b
type OM b bs = ContainerBox b bs
type OO b bs = OnceOptionalX (ContainerBox b bs)
type SM b bs = SomeMandatoryX (ContainerBox b bs)
type SO b bs = SomeOptionalX (ContainerBox b bs)
type OM_ b = Box b
type OO_ b = OnceOptionalX (Box b)
type SM_ b = SomeMandatoryX (Box b)
type SO_ b = SomeOptionalX (Box b)
type instance IsRuleConform (Box b) (Box r) = BoxTypeSymbol b == BoxTypeSymbol r
type instance IsRuleConform (Boxes bs) (Boxes rs) = IsRuleConform bs rs
type instance IsRuleConform (Box b) (ContainerBox b' rules)
= IsContainerBox b
&& IsRuleConform (Box b) (Box b')
&& IsRuleConform (ChildBoxes b) (Boxes rules)
type family IsContainerBox t :: Bool where
IsContainerBox (ContainerBox a as) = 'True
IsContainerBox b = 'False
type family ChildBoxes c where
ChildBoxes (ContainerBox a as) = Boxes as