module Simulation.Aivika.Transform
(
Transform(..),
delayTransform,
timeTransform,
integTransform,
sumTransform) where
import qualified Control.Category as C
import Control.Arrow
import Control.Monad
import Simulation.Aivika.Simulation
import Simulation.Aivika.Dynamics
import Simulation.Aivika.Dynamics.Memo
import Simulation.Aivika.Unboxed
import Simulation.Aivika.SystemDynamics
newtype Transform a b =
Transform { runTransform :: Dynamics a -> Simulation (Dynamics b)
}
instance C.Category Transform where
id = Transform return
(Transform g) . (Transform f) =
Transform $ \a -> f a >>= g
instance Arrow Transform where
arr f = Transform $ return . fmap f
first (Transform f) =
Transform $ \bd ->
do (b, d) <- unzip0Dynamics bd
c <- f b
return $ liftM2 (,) c d
second (Transform f) =
Transform $ \db ->
do (d, b) <- unzip0Dynamics db
c <- f b
return $ liftM2 (,) d c
(Transform f) *** (Transform g) =
Transform $ \bb' ->
do (b, b') <- unzip0Dynamics bb'
c <- f b
c' <- g b'
return $ liftM2 (,) c c'
(Transform f) &&& (Transform g) =
Transform $ \b ->
do c <- f b
c' <- g b
return $ liftM2 (,) c c'
instance ArrowLoop Transform where
loop (Transform f) =
Transform $ \b ->
mdo let bd = liftM2 (,) b d
cd <- f bd
(c, d) <- unzip0Dynamics cd
return c
timeTransform :: Transform a Double
timeTransform = Transform $ const $ return time
delayTransform :: Dynamics Double
-> Dynamics a
-> Transform a a
delayTransform lagTime init =
Transform $ \a -> delayI a lagTime init
integTransform :: Dynamics Double
-> Transform Double Double
integTransform = Transform . integ
sumTransform :: (Num a, Unboxed a) =>
Dynamics a
-> Transform a a
sumTransform = Transform . diffsum