module Simulation.Aivika.Trans.Transform
       (
        Transform(..),
        
        delayTransform,
        
        timeTransform,
        
        integTransform,
        integTransformEither,
        sumTransform,
        sumTransformEither) where
import qualified Control.Category as C
import Control.Arrow
import Control.Monad
import Control.Monad.Fix
import Simulation.Aivika.Trans.Comp
import Simulation.Aivika.Trans.Simulation
import Simulation.Aivika.Trans.Dynamics
import Simulation.Aivika.Trans.Dynamics.Memo
import Simulation.Aivika.Trans.Unboxed
import Simulation.Aivika.Trans.SystemDynamics
newtype Transform m a b =
  Transform { runTransform :: Dynamics m a -> Simulation m (Dynamics m b)
              
            }
instance MonadComp m => C.Category (Transform m) where
  id = Transform return
  
  (Transform g) . (Transform f) =
    Transform $ \a -> f a >>= g
instance MonadComp m => Arrow (Transform m) 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 (MonadComp m, MonadFix m) => ArrowLoop (Transform m) where
  loop (Transform f) =
    Transform $ \b ->
    mdo let bd = liftM2 (,) b d
        cd <- f bd
        (c, d) <- unzip0Dynamics cd
        return c
timeTransform :: MonadComp m => Transform m a Double
timeTransform = Transform $ const $ return time
delayTransform :: MonadComp m
                  => Dynamics m Double     
                  -> Dynamics m a       
                  -> Transform m a a    
delayTransform lagTime init =
  Transform $ \a -> delayI a lagTime init
  
integTransform :: (MonadComp m, MonadFix m)
                  => Dynamics m Double
                  
                  -> Transform m Double Double
                  
integTransform init = Transform $ \diff -> integ diff init
  
integTransformEither :: (MonadComp m, MonadFix m)
                        => Dynamics m Double
                        
                        -> Transform m (Either Double Double) Double
                        
integTransformEither init = Transform $ \diff -> integEither diff init
sumTransform :: (MonadComp m, MonadFix m, Num a, Unboxed m a)
                => Dynamics m a
                
                -> Transform m a a
                
sumTransform init = Transform $ \diff -> diffsum diff init
sumTransformEither :: (MonadComp m, MonadFix m, Num a, Unboxed m a)
                      => Dynamics m a
                      
                      -> Transform m (Either a a) a
                      
sumTransformEither init = Transform $ \diff -> diffsumEither diff init