]> gitweb @ CieloNegro.org - wavpack.git/blob - Codec/Audio/WavPack/Unpack.hs
working on unpackSamples
[wavpack.git] / Codec / Audio / WavPack / Unpack.hs
1 {-# LANGUAGE
2     DoAndIfThenElse
3   , FlexibleContexts
4   , ScopedTypeVariables
5   , UnicodeSyntax
6   #-}
7 module Codec.Audio.WavPack.Unpack
8     ( WavpackStream(..)
9     , unpackSamples
10     )
11     where
12 import Codec.Audio.WavPack.Block
13 import Control.Monad.ST
14 import Data.Int
15 import Data.STRef
16 import qualified Data.Vector.Generic.Mutable as MV
17 import Data.Word
18 import Prelude.Unicode
19
20 -- | FIXME
21 data WavpackStream s
22     = WavpackStream {
23         wpsHeader      ∷ !BlockHeader
24       , wpsMuteError   ∷ !(STRef s Bool)
25       , wpsSampleIndex ∷ !(STRef s Word32)
26       }
27
28 -- |This monster actually unpacks the WavPack bitstream(s) into the
29 -- specified buffer as 32-bit integers or floats (depending on orignal
30 -- data). Lossy samples will be clipped to their original limits
31 -- (i.e. 8-bit samples are clipped to -128/+127) but are still
32 -- returned in longs. It is up to the caller to potentially reformat
33 -- this for the final output including any multichannel distribution,
34 -- block alignment or endian compensation.
35 unpackSamples ∷ ∀v s. (MV.MVector v Int32)
36               ⇒ WavpackStream s
37               → Int    -- ^ Number of channels.
38               → Int    -- ^ Reduced number of channels (1 or 2).
39               → Word32 -- ^ Number of samples to get.
40               → ST s (v s Int32)
41 {-# INLINEABLE unpackSamples #-}
42 unpackSamples wps numChannels reducedChannels nSamples0
43     = do let hdr   = wpsHeader wps
44              flags = bhFlags hdr
45          nSamples ← do idx ← readSTRef (wpsSampleIndex wps)
46                        if idx + nSamples0 > bhBlockIndex hdr + bhBlockSamples hdr then
47                            return $ bhBlockIndex hdr + bhBlockSamples hdr - idx
48                        else
49                            return nSamples0
50
51          muteError ← readSTRef (wpsMuteError wps)
52          if muteError then
53              do v ← if reducedChannels ≡ 1 ∨ numChannels ≡ 1 ∨ bfMono flags then
54                         MV.replicate (fromIntegral nSamples) 0
55                     else
56                         MV.replicate (fromIntegral nSamples ⋅ 2) 0
57                 modifySTRef (wpsSampleIndex wps) (+ nSamples)
58                 return v
59          else
60              error "FIXME"