-- |
-- Module:     Control.Wire.Prefab.Calculus
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Wires for calculus over time.

module Control.Wire.Prefab.Calculus
    ( -- * Integration
      integral,

      -- * Differentiation
      derivative
    )
    where

import Control.Arrow
import Control.Wire.Classes
import Control.Wire.Types
import Data.VectorSpace


-- | Integrate over time.
--
-- * Depends: Current instant.

integral ::
    forall e t v (>~).
    (ArrowClock (>~), Num t, Scalar v ~ t, Time (>~) ~ t, VectorSpace v)
    => v -> Wire e (>~) v v
integral x0 =
    mkGen $ proc _ -> do
        t <- arrTime -< ()
        returnA -< (Right x0, integral' x0 t)

    where
    integral' :: v -> t -> Wire e (>~) v v
    integral' x0 t' =
        mkGen $ proc dx -> do
            t <- arrTime -< ()
            let dt = t - t'
            let x1 = x0 ^+^ (dx ^* dt)
            returnA -< x0 `seq` (Right x0, integral' x1 t)


-- | Calculates the derivative of the input signal over time.
--
-- * Depends: Current instant.

derivative ::
    forall e t v (>~).
    (ArrowClock (>~), Fractional t, Scalar v ~ t, Time (>~) ~ t, VectorSpace v)
    => Wire e (>~) v v
derivative =
    mkGen $ proc x0 -> do
        t <- arrTime -< ()
        returnA -< (Right zeroV, deriv' x0 t)

    where
    deriv' :: v -> t -> Wire e (>~) v v
    deriv' x0 t' =
        mkGen $ proc x1 -> do
            t <- arrTime -< ()
            let dt = t - t'
            let dx = (x1 ^-^ x0) ^/ dt
            returnA -< x0 `seq` (Right dx, deriv' x1 t)