]> gitweb @ CieloNegro.org - wavpack.git/blobdiff - Codec/Audio/WavPack/Decorrelation.hs
working on decorrStereoPass...
[wavpack.git] / Codec / Audio / WavPack / Decorrelation.hs
index b72909fd3b0162e46d59f1e073a2ed4942d207b3..0230244b90ff045da22c8579e475aab0c59519c1 100644 (file)
@@ -1,13 +1,22 @@
 {-# LANGUAGE
-    UnicodeSyntax
+    DoAndIfThenElse
+  , FlexibleContexts
+  , ScopedTypeVariables
+  , UnicodeSyntax
   #-}
 -- | FIXME
 module Codec.Audio.WavPack.Decorrelation
     ( DecorrPass(..)
+    , decorrStereoPass
     )
     where
+import Control.Monad.ST
+import Data.Bits
 import Data.Int
-import qualified Data.Vector.Unboxed as UV
+import Data.STRef
+import qualified Data.Strict as S
+import qualified Data.Vector.Generic.Mutable as MV
+import Prelude.Unicode
 
 {-
 maxTerm ∷ Num a ⇒ a
@@ -15,22 +24,55 @@ maxTerm = 8
 -}
 
 -- | FIXME
-data DecorrPass
+data DecorrPass v s
     = DecorrPass {
-      -- | The decorrelation term: (term /= 0) && ((-3 <= term <= 8)
-      --   || (term == 17) || (term <= 18))
+      -- | The decorrelation term: @(term /= 0) && ((-3 <= term <= 8)
+      --   || (term == 17) || (term <= 18))@
         dpTerm     ∷ !Int8
-      -- | The decorrelation delta: 0 <= delta <= 8
+      -- | The decorrelation delta: @0 <= delta <= 8@
       , dpDelta    ∷ !Int8
-      -- | The decorrelation weight for channel A: -1024 <= weight <=
-      --   1024
-      , dpWeightA  ∷ !Int16
-      -- | The decorrelation weight for channel B: -1024 <= weight <=
-      --   1024
-      , dpWeightB  ∷ !Int16
+      -- | The decorrelation weight for channel A: @-1024 <= weight <=
+      --   1024@
+      , dpWeightA  ∷ !(STRef s Int16)
+      -- | The decorrelation weight for channel B: @-1024 <= weight <=
+      --   1024@
+      , dpWeightB  ∷ !(S.Maybe (STRef s Int16))
       -- | The decorrelation samples for channel A.
-      , dpSamplesA ∷ !(UV.Vector Int32)
+      , dpSamplesA ∷ !(v s Int32)
       -- | The decorrelation samples for channel B.
-      , dpSamplesB ∷ !(UV.Vector Int32)
+      , dpSamplesB ∷ !(S.Maybe (v s Int32))
       }
-    deriving (Eq, Show)
+
+-- |General function to perform stereo decorrelation pass on specified
+-- buffer (although since this is the reverse function it might
+-- technically be called /correlation/ instead). This version handles
+-- all sample resolutions and weight deltas. The dpSamplesX data is
+-- *not* returned normalized for term values 1-8, so it should be
+-- normalized if it is going to be used to call this function again.
+decorrStereoPass ∷ ∀v s. MV.MVector v Int32
+                 ⇒ DecorrPass v s
+                 → v s Int32
+                 → ST s ()
+{-# INLINEABLE decorrStereoPass #-}
+decorrStereoPass dp buffer
+    | dpTerm dp ≡ 17
+        = flip mapM_ [0 .. (MV.length buffer `div` 2) - 1] $ \n →
+              do a0 ← MV.unsafeRead (dpSamplesA dp) 0
+                 a1 ← MV.unsafeRead (dpSamplesA dp) 1
+                 let samA = 2 ⋅ a0 - a1
+                 MV.unsafeWrite (dpSamplesA dp) 1 a0
+                 tmpA ← MV.unsafeRead buffer (n ⋅ 2)
+                 fail "FIXME"
+    | otherwise
+        = fail "FIXME"
+
+applyWeight ∷ Int16 → Int32 → Int32
+{-# INLINE applyWeight #-}
+applyWeight weight sample
+    | sample `shiftR` 0xFFFF ≡ 0
+        = (fromIntegral weight ⋅ sample + 512) `shiftR` 10
+    | otherwise
+        = ( (((sample .&. 0xFFFF) ⋅ fromIntegral weight) `shiftR` 9) +
+            (((sample .&. complement 0xFFFF) `shiftR` 9) ⋅ fromIntegral weight) +
+            1
+          ) `shiftR` 1