From e70043673023f33823bd9617c52a84c5aef4b419 Mon Sep 17 00:00:00 2001 From: PHO Date: Fri, 22 Jul 2011 01:56:08 +0900 Subject: [PATCH] C style "for" loop --- Codec/Audio/WavPack/Words.hs | 75 +++++++++++++++++++++++++++++++----- wavpack.cabal | 1 + 2 files changed, 66 insertions(+), 10 deletions(-) diff --git a/Codec/Audio/WavPack/Words.hs b/Codec/Audio/WavPack/Words.hs index e477505..182c23c 100644 --- a/Codec/Audio/WavPack/Words.hs +++ b/Codec/Audio/WavPack/Words.hs @@ -2,7 +2,6 @@ BangPatterns , FlexibleContexts , ScopedTypeVariables - , UnboxedTuples , UnicodeSyntax #-} {-| This module provides entropy word encoding and decoding functions @@ -23,22 +22,23 @@ efficient with this data and results in about 1.22 bits per sample. -} module Codec.Audio.WavPack.Words ( WordsData(..) --- , getWordsLossless + , getWordsLossless ) where import Codec.Audio.WavPack.Entropy import Codec.Audio.WavPack.Internal +import Control.Monad.Cont import Control.Monad.ST +import Control.Monad.Trans +import Control.Monad.Unicode import Data.Bits import Data.Bitstream.Generic (Bitstream) import qualified Data.Bitstream.Generic as B import Data.Int import Data.STRef -import qualified Data.Vector.Generic as GV import qualified Data.Vector.Generic.Mutable as MV -import Data.Vector.Generic.New (New) -import qualified Data.Vector.Generic.New as New import Data.Word +import Prelude hiding (break) import Prelude.Unicode -- | FIXME @@ -58,6 +58,47 @@ data WordsData s -- lossless only ('edErrorLimit' ≡ 0). Also, rather than obtaining a -- single sample, it can be used to obtain an entire buffer of either -- mono or stereo samples. +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 + → ST s (v s Int32) +{-# INLINEABLE getWordsLossless #-} +getWordsLossless isMono w bs nSamples0 + = do v ← MV.new nSamples + n ← runContT (for 0 (< nSamples) (+ 1) (loop v)) return + return $ MV.take n v + where + nSamples ∷ Int + nSamples = if isMono + then nSamples0 + else nSamples0 ⋅ 2 + + loop ∷ v s Int32 + → Int + → ContT Int (ST s) () + → ContT Int (ST s) () + → ContT Int (ST s) () + loop v n break continue + = do let c | isMono = fst $ wdEntropyData w + | n `testBit` 0 = fst $ wdEntropyData w + | otherwise = snd $ wdEntropyData w + med00 ← lift $ readSTRef (edMedian0 $ fst $ wdEntropyData w) + hldZero ← lift $ readSTRef (wdHoldingZero w) + hldOne ← lift $ readSTRef (wdHoldingOne w) + med10 ← lift $ readSTRef (edMedian0 $ snd $ wdEntropyData w) + when (med00 < 2 ∧ hldZero ≡ False ∧ hldOne ≡ 0 ∧ med10 < 2) $ + do zAcc ← lift $ readSTRef (wdZeroesAcc w) + if zAcc > 0 then + do lift $ modifySTRef (wdZeroesAcc w) ((-) 1) + when (zAcc > 1) $ + do lift $ MV.unsafeWrite v n 0 + continue + else + error "FIXME" + error "FIXME" + {- getWordsLossless ∷ ∀bs v. (Bitstream bs, GV.Vector v Int32) ⇒ Bool -- ^ Is the stream monaural? @@ -74,11 +115,6 @@ getWordsLossless isMono w0 bs0 nSamples0 in (# w1, bs1, v2 #) where - nSamples ∷ Int - nSamples = if isMono - then nSamples0 - else nSamples0 ⋅ 2 - go0 ∷ WordsData → bs → Int → New v Int32 → (# WordsData, bs, Int, New v Int32 #) go0 w bs n v @@ -268,3 +304,22 @@ takeBits bsr n = do bs ← readSTRef bsr writeSTRef bsr (B.drop n bs) return (B.toBits (B.take n bs)) + +-- | C style /for/ loop with /break/ and /continue/. +for ∷ ∀m α. MonadCont m + ⇒ α -- ^ Initial state + → (α → Bool) -- ^ Continue-the-loop predicate + → (α → α) -- ^ State modifier + → (α → m () → m () → m ()) -- ^ Loop body taking breaker and + -- continuer + → m α -- ^ Final state +for α0 contLoop next body + = callCC $ \break → loop break α0 + where + loop ∷ (α → m ()) → α → m α + loop break α + | contLoop α + = do callCC $ \continue → body α (break α) (continue ()) + loop break (next α) + | otherwise + = return α diff --git a/wavpack.cabal b/wavpack.cabal index c4eb301..c836097 100644 --- a/wavpack.cabal +++ b/wavpack.cabal @@ -37,6 +37,7 @@ Library binary-strict == 0.4.*, bitstream == 0.2.*, bytestring == 0.9.*, + mtl == 2.0.*, strict == 0.3.*, vector == 0.7.* -- 2.40.0