, DecorrWeights(..)
, DecorrSamples(..)
, EntropyVars(..)
+ , WVBitstream(..)
, RIFFHeader(..)
, RIFFTrailer(..)
, ConfigInfo(..)
getSubBlock 0x03 = fmap SubBlock (get ∷ Get DecorrWeights)
getSubBlock 0x04 = fmap SubBlock (get ∷ Get DecorrSamples)
getSubBlock 0x05 = fmap SubBlock (get ∷ Get EntropyVars )
+ getSubBlock 0x0A = fmap SubBlock (get ∷ Get WVBitstream )
getSubBlock 0x21 = fmap SubBlock (get ∷ Get RIFFHeader )
getSubBlock 0x22 = fmap SubBlock (get ∷ Get RIFFTrailer )
getSubBlock 0x25 = fmap SubBlock (get ∷ Get ConfigInfo )
= Dummy {
-- | Must be less than 2^25 bytes long due to the limitation
-- of WavPack specification.
- dumSize ∷ Word32
+ dumSize ∷ !Word32
}
deriving (Eq, Show, Typeable)
med2 ← fmap exp2 getWord16le
return (med0, med1, med2)
+-- | WV Bitstream
+data WVBitstream
+ = WVBitstream {
+ wvStream ∷ !L.ByteString
+ }
+ deriving (Eq, Show, Typeable)
+
+instance Metadata WVBitstream where
+ metaID _ = 0x0A
+ metaSize = fromIntegral ∘ L.length ∘ wvStream
+
+instance Binary WVBitstream where
+ put = putLazyByteString ∘ wvStream
+ get = fmap WVBitstream getRemainingLazyByteString
+
-- | RIFF header for .wav files (before audio)
data RIFFHeader
= RIFFHeader {
- riffHeader ∷ L.ByteString
+ riffHeader ∷ !L.ByteString
}
deriving (Eq, Show, Typeable)
instance Metadata RIFFHeader where
metaID _ = 0x21
+ metaSize = fromIntegral ∘ L.length ∘ riffHeader
instance Binary RIFFHeader where
put = putLazyByteString ∘ riffHeader
-- | RIFF trailer for .wav files (after audio)
data RIFFTrailer
= RIFFTrailer {
- riffTrailer ∷ L.ByteString
+ riffTrailer ∷ !L.ByteString
}
deriving (Eq, Show, Typeable)
instance Metadata RIFFTrailer where
metaID _ = 0x22
+ metaSize = fromIntegral ∘ L.length ∘ riffTrailer
instance Binary RIFFTrailer where
put = putLazyByteString ∘ riffTrailer
#-}
module Main where
import Codec.Audio.WavPack.Block
+import Codec.Audio.WavPack.Metadata
import qualified Data.ByteString.Lazy as L
import qualified Data.Strict as S
+import Data.Maybe
+import Prelude.Unicode
import System.Environment
import System.IO
main ∷ IO ()
main = do [wvFile] ← getArgs
- wvStream ← L.readFile wvFile
+ wvData ← L.readFile wvFile
hSetBuffering stdout NoBuffering
- showWvInfo wvStream
+ showWvInfo wvData
showWvInfo ∷ L.ByteString → IO ()
showWvInfo stream
= case findNextBlock stream of
(# S.Just block, _ #)
- → print block
+ → printBlock block
(# S.Nothing , _ #)
→ fail "Can't find any WavPack block headers."
+
+printBlock ∷ Block → IO ()
+printBlock b
+ = do putStrLn "- Block header:"
+ print $ blockHeader b
+ putStrLn "- Block metadata sub-blocks:"
+ mapM_ printSub $ blockMetadata b
+ where
+ printSub ∷ SubBlock → IO ()
+ printSub sub
+ | isJust (fromSubBlock sub ∷ Maybe WVBitstream)
+ = putStrLn ( "(WV Bitstream omitted: " ⧺
+ show (metaSize sub) ⧺
+ " bytes)"
+ )
+ | otherwise
+ = print sub