+{-# LANGUAGE
+ DoAndIfThenElse
+ , FlexibleContexts
+ , ScopedTypeVariables
+ , UnicodeSyntax
+ #-}
module Codec.Audio.WavPack.Unpack
- (
+ ( WavpackStream(..)
+ , unpackSamples
)
where
+import Codec.Audio.WavPack.Block
+import Control.Monad.ST
+import Data.Int
+import Data.STRef
+import qualified Data.Vector.Generic.Mutable as MV
+import Data.Word
+import Prelude.Unicode
+
+-- | FIXME
+data WavpackStream s
+ = WavpackStream {
+ wpsHeader ∷ !BlockHeader
+ , wpsMuteError ∷ !(STRef s Bool)
+ , wpsSampleIndex ∷ !(STRef s Word32)
+ }
+
+-- |This monster actually unpacks the WavPack bitstream(s) into the
+-- specified buffer as 32-bit integers or floats (depending on orignal
+-- data). Lossy samples will be clipped to their original limits
+-- (i.e. 8-bit samples are clipped to -128/+127) but are still
+-- returned in longs. It is up to the caller to potentially reformat
+-- this for the final output including any multichannel distribution,
+-- block alignment or endian compensation.
+unpackSamples ∷ ∀v s. (MV.MVector v Int32)
+ ⇒ WavpackStream s
+ → Int -- ^ Number of channels.
+ → Int -- ^ Reduced number of channels (1 or 2).
+ → Word32 -- ^ Number of samples to get.
+ → ST s (v s Int32)
+{-# INLINEABLE unpackSamples #-}
+unpackSamples wps numChannels reducedChannels nSamples0
+ = do let hdr = wpsHeader wps
+ flags = bhFlags hdr
+ nSamples ← do idx ← readSTRef (wpsSampleIndex wps)
+ if idx + nSamples0 > bhBlockIndex hdr + bhBlockSamples hdr then
+ return $ bhBlockIndex hdr + bhBlockSamples hdr - idx
+ else
+ return nSamples0
+
+ muteError ← readSTRef (wpsMuteError wps)
+ if muteError then
+ do v ← if reducedChannels ≡ 1 ∨ numChannels ≡ 1 ∨ bfMono flags then
+ MV.replicate (fromIntegral nSamples) 0
+ else
+ MV.replicate (fromIntegral nSamples ⋅ 2) 0
+ modifySTRef (wpsSampleIndex wps) (+ nSamples)
+ return v
+ else
+ error "FIXME"
⇒ Bool -- ^ Is the stream monaural?
→ WordsData s
→ STRef s bs -- ^ WV bitstream
- → Int -- ^ Number of samples to get
+ → Word32 -- ^ Number of samples to get
→ ST s (v s Int32)
{-# INLINEABLE getWordsLossless #-}
getWordsLossless isMono w bs nSamples0
return $ MV.take n v
where
nSamples ∷ Int
- nSamples = if isMono
+ nSamples = fromIntegral $
+ if isMono
then nSamples0
else nSamples0 ⋅ 2