module Synthesizer.CausalIO.Process (
T(Cons),
fromCausal,
mapAccum,
Synthesizer.CausalIO.Process.traverse,
runCont,
runStorableChunkyCont,
zip,
continue,
continueChunk,
) where
import qualified Synthesizer.Causal.Process as Causal
import qualified Synthesizer.Generic.Signal as SigG
import qualified Synthesizer.Generic.Cut as CutG
import qualified Synthesizer.Zip as Zip
import qualified Data.StorableVector.Lazy as SVL
import qualified Data.StorableVector as SV
import Foreign.Storable (Storable, )
import qualified Control.Monad.Trans.State as MS
import qualified Control.Arrow as Arr
import qualified Control.Category as Cat
import Control.Arrow ((^<<), (&&&), )
import Control.Monad (mplus, )
import Data.Monoid (Monoid, mempty, mappend, )
import System.IO.Unsafe (unsafePerformIO, unsafeInterleaveIO, )
import Prelude hiding (zip, )
data T a b =
forall state.
Cons
(a -> state -> IO (b, state))
(IO state)
(state -> IO ())
instance Cat.Category T where
id = Arr.arr id
(Cons nextB createB deleteB) .
(Cons nextA createA deleteA) = Cons
(\a (sa0,sb0) -> do
(b,sa1) <- nextA a sa0
(c,sb1) <- nextB b sb0
return (c,(sa1,sb1)))
(do
sa <- createA
sb <- createB
return (sa,sb))
(\(sa,sb) ->
deleteA sa >> deleteB sb)
instance Arr.Arrow T where
arr f = Cons
(\ a () -> return (f a, ()))
(return ())
(\ () -> return ())
first (Cons next create delete) = Cons
(\(b,d) sa0 ->
do (c,sa1) <- next b sa0
return ((c,d), sa1))
create
delete
fromCausal ::
(Monoid b) =>
Causal.T a b -> T a b
fromCausal (Causal.Cons next start) = Cons
(\a s0 ->
return $
case MS.runStateT (next a) s0 of
Nothing -> (mempty, s0)
Just (b,s1) -> (b,s1))
(return $ start)
(\ _ -> return ())
mapAccum ::
(a -> state -> (b, state)) ->
state ->
T a b
mapAccum next start =
Cons
(\a s -> return $ next a s)
(return start)
(\ _ -> return ())
traverse ::
state ->
(a -> MS.State state b) ->
T a b
traverse start next =
Cons
(\a s -> return $ MS.runState (next a) s)
(return start)
(\ _ -> return ())
runCont ::
(CutG.Transform a, CutG.Transform b) =>
T a b -> IO (([a] -> [b]) -> [a] -> [b])
runCont (Cons next create delete) =
return $
\ procRest sig ->
unsafePerformIO $ do
let go xt s0 =
unsafeInterleaveIO $
case xt of
[] -> delete s0 >> return []
x:xs -> do
(y,s1) <- next x s0
(if CutG.length y > 0
then fmap (y:)
else id) $
(if CutG.length y < CutG.length x
then return $ procRest $
CutG.drop (CutG.length y) x : xs
else go xs s1)
go sig =<< create
runStorableChunkyCont ::
(Storable a, Storable b) =>
T (SV.Vector a) (SV.Vector b) ->
IO ((SVL.Vector a -> SVL.Vector b) ->
SVL.Vector a -> SVL.Vector b)
runStorableChunkyCont proc =
flip fmap (runCont proc) $ \f cont ->
SVL.fromChunks .
f (SVL.chunks . cont . SVL.fromChunks) .
SVL.chunks
zip ::
(Arr.Arrow arrow) =>
arrow a b -> arrow a c -> arrow a (Zip.T b c)
zip ab ac =
uncurry Zip.Cons ^<< ab &&& ac
instance (CutG.Transform a, CutG.Read b, Monoid b) => Monoid (T a b) where
mempty = Cons
(\ _a () -> return (mempty, ()))
(return ())
(\() -> return ())
mappend
(Cons nextX createX deleteX)
(Cons nextY createY deleteY) = Cons
(\a s ->
case s of
Left s0 -> do
(b1,s1) <- nextX a s0
let lenA = CutG.length a
lenB = CutG.length b1
case compare lenA lenB of
LT -> error "CausalIO.Process.mappend: output chunk is larger than input chunk"
EQ -> return (b1, Left s1)
GT -> do
deleteX s1
(b2,s2) <- nextY (CutG.drop lenB a) =<< createY
return (mappend b1 b2, Right s2)
Right s0 -> do
(b1,s1) <- nextY a s0
return (b1, Right s1))
(fmap Left createX)
(either deleteX deleteY)
data State a b =
forall state.
State
(a -> state -> IO (b, state))
(state -> IO ())
state
forceMaybe :: (Maybe a -> b) -> Maybe a -> b
forceMaybe f ma =
case ma of
Nothing -> f Nothing
Just a -> f $ Just a
continue ::
(CutG.Transform a, SigG.Transform sig b) =>
T a (sig b) -> (b -> T a (sig b)) -> T a (sig b)
continue (Cons nextX createX deleteX) procY = Cons
(\a s ->
case s of
Left (lastB0, s0) -> do
(b1,s1) <- nextX a s0
let lenA = CutG.length a
lenB = CutG.length b1
lastB1 =
mplus (fmap snd $ SigG.viewR b1) lastB0
cont lastB = (b1, Left (lastB,s1))
case compare lenA lenB of
LT -> error "CausalIO.Process.continue: output chunk is larger than input chunk"
EQ -> return $ forceMaybe cont lastB1
GT ->
case lastB1 of
Nothing -> return (mempty, Left (lastB1,s1))
Just lastB ->
case procY lastB of
Cons nextY createY deleteY -> do
deleteX s1
(b2,s2) <- nextY (CutG.drop lenB a) =<< createY
return (mappend b1 b2, Right (State nextY deleteY s2))
Right (State nextY deleteY s0) -> do
(b1,s1) <- nextY a s0
return (b1, Right (State nextY deleteY s1)))
(do
sa <- createX
return (Left (Nothing, sa)))
(\s ->
case s of
Left (_lastB,s0) -> deleteX s0
Right (State _ deleteY s0) -> deleteY s0)
continueChunk ::
(CutG.Transform a, CutG.Transform b) =>
T a b -> (b -> T a b) -> T a b
continueChunk (Cons nextX createX deleteX) procY = Cons
(\a s ->
case s of
Left (lastB0, s0) -> do
(b1,s1) <- nextX a s0
let lenA = CutG.length a
lenB = CutG.length b1
cont lastB = (b1, Left (lastB,s1))
case compare lenA lenB of
LT -> error "CausalIO.Process.continueChunk: output chunk is larger than input chunk"
EQ ->
return $ if lenB==0 then cont lastB0 else cont b1
GT ->
if lenB==0
then return $ cont lastB0
else
case procY b1 of
Cons nextY createY deleteY -> do
deleteX s1
(b2,s2) <- nextY (CutG.drop lenB a) =<< createY
return (mappend b1 b2, Right (State nextY deleteY s2))
Right (State nextY deleteY s0) -> do
(b1,s1) <- nextY a s0
return (b1, Right (State nextY deleteY s1)))
(do
sa <- createX
return (Left (mempty, sa)))
(\s ->
case s of
Left (_lastB,s0) -> deleteX s0
Right (State _ deleteY s0) -> deleteY s0)