]> gitweb @ CieloNegro.org - wavpack.git/blob - Codec/Audio/WavPack/Metadata.hs
78a99fc5e232dd7e168c971d30d1209a80cd92de
[wavpack.git] / Codec / Audio / WavPack / Metadata.hs
1 {-# LANGUAGE
2     DeriveDataTypeable
3   , ExistentialQuantification
4   , UnicodeSyntax
5   #-}
6 -- | WavPack metadata sub-blocks
7 module Codec.Audio.WavPack.Metadata
8     ( Metadata(..)
9     , SubBlock
10
11     , Dummy(..)
12     , Unknown(..)
13     )
14     where
15 import Control.Monad
16 import Data.Binary
17 import Data.Binary.Get
18 import Data.Binary.Put
19 import Data.Bits
20 import qualified Data.ByteString.Lazy as L
21 import Data.Typeable
22 import Prelude.Unicode
23
24 -- | Type class for every metadata sub-blocks.
25 class (Binary α, Eq α, Show α, Typeable α) ⇒ Metadata α where
26     -- | Get the metadata ID (mandatory).
27     metaID   ∷ α → Word8
28     -- | Get the size of metadata (optional).
29     metaSize ∷ α → Word32
30     metaSize = fromIntegral ∘ L.length ∘ runPut ∘ put
31     -- | Cast a 'SubBlock' to this type of metadata (optional).
32     fromSubBlock ∷ SubBlock → Maybe α
33     fromSubBlock (SubBlock a) = cast a
34     -- | Wrap the metadata into 'SubBlock' (optional).
35     toSubBlock ∷ α → SubBlock
36     toSubBlock = SubBlock
37
38 -- | An opaque sub-block container.
39 data SubBlock = ∀α. Metadata α ⇒ SubBlock α
40                 deriving Typeable
41
42 instance Metadata SubBlock where
43     metaID   (SubBlock a) = metaID a
44     metaSize (SubBlock a) = metaSize a
45     fromSubBlock = Just
46     toSubBlock   = id
47
48 instance Binary SubBlock where
49     put (SubBlock a)
50         = let size     = metaSize a
51               oddBit   = if odd size   then 0x40 else 0
52               largeBit = if size > 255 then 0x80 else 0
53               idWord   = metaID a .|. oddBit .|. largeBit
54           in
55             do putWord8 idWord
56                if size > 255 then
57                    -- Don't forget about the endianness.
58                    do putWord8 $ fromIntegral $ (size `shiftR`  1) .&. 0xFF
59                       putWord8 $ fromIntegral $ (size `shiftR`  9) .&. 0xFF
60                       putWord8 $ fromIntegral $ (size `shiftR` 17) .&. 0xFF
61                  else
62                       putWord8 $ fromIntegral $ (size `shiftR`  1) .&. 0xFF
63                put a
64                when (odd size) $ putWord8 0
65
66     get = do idWord ← getWord8
67              let isOdd   = idWord .&. 0x40 ≢ 0
68                  isLarge = idWord .&. 0x80 ≢ 0
69                  rawID   = idWord .&. (complement 0x40) .&. (complement 0x80)
70                  adj     = if isOdd then -1 else 0
71              size ← if isLarge then
72                          do sz0 ← getWord8
73                             sz1 ← getWord8
74                             sz2 ← getWord8
75                             return $ ( (fromIntegral sz2 `shiftL` 17) .|.
76                                        (fromIntegral sz1 `shiftL`  9) .|.
77                                        (fromIntegral sz0 `shiftL`  1)
78                                      ) + adj
79                      else
80                          fmap ((+ adj) ∘ (`shiftL` 1) ∘ fromIntegral) getWord8
81              subb ← getLazyByteString $ fromIntegral (size ∷ Word32)
82              return $ runGet (getSubBlock rawID) subb
83         where
84           getSubBlock ∷ Word8 → Get SubBlock
85           getSubBlock 0x00 = fmap SubBlock (get ∷ Get Dummy)
86           getSubBlock unknownID
87               = if unknownID .&. 0x20 ≡ 0 then
88                     fail ("Unknown WavPack metadata ID: " ⧺ show unknownID)
89                 else
90                     -- It's unknown but optional. We can safely ignore it.
91                     fmap (SubBlock ∘ Unknown unknownID) getRemainingLazyByteString
92
93 instance Eq SubBlock where
94     (SubBlock a) == (SubBlock b)
95         = Just a ≡ cast b
96
97 instance Show SubBlock where
98     show (SubBlock a) = show a
99
100 -- | Dummy metadata to pad WavPack blocks.
101 data Dummy
102     = Dummy {
103         -- | Must be less than 2^25 bytes long due to the limitation
104         -- of WavPack specification.
105         dumSize ∷ Word32
106       }
107     deriving (Eq, Show, Typeable)
108
109 instance Metadata Dummy where
110     metaID _ = 0x00
111     metaSize = dumSize
112
113 instance Binary Dummy where
114     put = putLazyByteString ∘ flip L.replicate 0x00 ∘ fromIntegral ∘ dumSize
115     get = fmap (Dummy ∘ fromIntegral) remaining
116
117 -- | Unknown but optional metadata found in the WavPack block.
118 data Unknown
119     = Unknown {
120         -- | The ID of this unknown metadata.
121         unkID   ∷ Word8
122         -- | Raw data; must be less than 2^25 bytes long.
123       , unkData ∷ L.ByteString
124       }
125     deriving (Eq, Show, Typeable)
126
127 instance Metadata Unknown where
128     metaID   = unkID
129     metaSize = fromIntegral ∘ L.length ∘ unkData
130
131 instance Binary Unknown where
132     put = putLazyByteString ∘ unkData
133     get = (⊥)