-- |
-- Module:     Control.Wire.Prefab.Sample
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Signal sampling wires.

module Control.Wire.Prefab.Sample
    ( -- * Simple samplers
      discrete,
      keep
    )
    where

import Control.Arrow
import Control.Wire.Classes
import Control.Wire.Prefab.Simple
import Control.Wire.Types


-- | Sample the right signal at discrete intervals given by the left
-- input signal.
--
-- * Depends: Current instant (left), last sampling instant (right).

discrete ::
    forall b e t (>~). (ArrowClock (>~), Num t, Ord t, Time (>~) ~ t)
    => Wire e (>~) (t, b) b
discrete =
    mkGen $ proc (_, x) -> do
        t <- arrTime -< ()
        returnA -< (Right x, discrete' t x)

    where
    discrete' :: t -> b -> Wire e (>~) (t, b) b
    discrete' t' x0 =
        mkGen $ proc (dt, x) -> do
            t <- arrTime -< ()
            returnA -<
                if (t - t' >= dt)
                  then (Right x, discrete' t x)
                  else (Right x0, discrete' t' x0)


-- | Keep the signal in the first instant forever.
--
-- * Depends: First instant.

keep :: Wire e (>~) b b
keep = mkPure $ \x -> (Right x, constant x)