From: PHO Date: Sun, 24 Jul 2011 05:11:23 +0000 (+0900) Subject: working on unpackSamples X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=wavpack.git;a=commitdiff_plain;h=905f72f65d6a6b2b5f068f17a901f56f793209f7 working on unpackSamples --- diff --git a/Codec/Audio/WavPack/Unpack.hs b/Codec/Audio/WavPack/Unpack.hs index 264072c..33c5152 100644 --- a/Codec/Audio/WavPack/Unpack.hs +++ b/Codec/Audio/WavPack/Unpack.hs @@ -1,4 +1,60 @@ +{-# 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" diff --git a/Codec/Audio/WavPack/Words.hs b/Codec/Audio/WavPack/Words.hs index 4bb1191..83c0897 100644 --- a/Codec/Audio/WavPack/Words.hs +++ b/Codec/Audio/WavPack/Words.hs @@ -92,7 +92,7 @@ getWordsLossless ∷ ∀bs v s. (Bitstream bs, MV.MVector v Int32) ⇒ 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 @@ -101,7 +101,8 @@ 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