X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=wavpack.git;a=blobdiff_plain;f=Codec%2FAudio%2FWavPack%2FUnpack.hs;h=98d9f4eb8a140411b8055da98afd630940dc630a;hp=33c51522df4ea463bf641c2de927795961af1a64;hb=14e615d1521862ddfab67156d48e00798b1615bc;hpb=905f72f65d6a6b2b5f068f17a901f56f793209f7 diff --git a/Codec/Audio/WavPack/Unpack.hs b/Codec/Audio/WavPack/Unpack.hs index 33c5152..98d9f4e 100644 --- a/Codec/Audio/WavPack/Unpack.hs +++ b/Codec/Audio/WavPack/Unpack.hs @@ -10,19 +10,27 @@ module Codec.Audio.WavPack.Unpack ) where import Codec.Audio.WavPack.Block +import Codec.Audio.WavPack.Words import Control.Monad.ST +import Data.Bits +import Data.Bitstream.Generic (Bitstream) import Data.Int import Data.STRef +import qualified Data.Strict as S import qualified Data.Vector.Generic.Mutable as MV import Data.Word import Prelude.Unicode -- | FIXME -data WavpackStream s +data WavpackStream bs s = WavpackStream { - wpsHeader ∷ !BlockHeader + wpsWVBlock ∷ !Block + , wpsWVCBlock ∷ !(S.Maybe Block) + , wpsWordsData ∷ !(WordsData s) , wpsMuteError ∷ !(STRef s Bool) , wpsSampleIndex ∷ !(STRef s Word32) + , wpsWVBits ∷ !(STRef s bs) + , wpsWVCBits ∷ !(S.Maybe (STRef s bs)) } -- |This monster actually unpacks the WavPack bitstream(s) into the @@ -32,16 +40,24 @@ data WavpackStream s -- 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 +unpackSamples ∷ ∀bs v s. (Bitstream bs, MV.MVector v Int32) + ⇒ WavpackStream bs 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 + = do let hdr = blockHeader $ wpsWVBlock wps + flags = bhFlags hdr + muteLimit0 = (1 `shiftL` fromIntegral (bfMaxMagnitude flags)) + 2 + muteLimit ∷ Int32 -- FIXME: Do we really need to explicitly type this? + muteLimit + | bfHybrid flags ∧ S.isNothing (wpsWVCBlock wps) + = muteLimit0 ⋅ 2 + | otherwise + = muteLimit0 + nSamples ← do idx ← readSTRef (wpsSampleIndex wps) if idx + nSamples0 > bhBlockIndex hdr + bhBlockSamples hdr then return $ bhBlockIndex hdr + bhBlockSamples hdr - idx @@ -57,4 +73,23 @@ unpackSamples wps numChannels reducedChannels nSamples0 modifySTRef (wpsSampleIndex wps) (+ nSamples) return v else - error "FIXME" + do v ← if S.isNothing (wpsWVCBlock wps) ∧ bfMono flags then + -- handle lossless or hybrid lossy mono data + fail "FIXME: unsupported stream type: monaural stream" + else + if S.isNothing (wpsWVCBlock wps) ∧ (¬) (bfMono flags) then + -- handle lossless or hybrid lossy stereo data + do v ← if bfHybrid flags then + fail "FIXME: unsupported stream type: lossy stereo stream" + else + getWordsLossless + (bfMono flags) + (wpsWordsData wps) + (wpsWVBits wps) + nSamples + error "FIXME" + return v + else + error "FIXME" + error "FIXME" + return v