-- |
-- Module:     Control.Wire.Prefab.Accum
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Wires for signal accumulation.

module Control.Wire.Prefab.Accum
    ( -- * General accumulator
      accum,

      -- * Special accumulators
      countFrom,
      countStep,

      -- * Specific instances
      atFirst
    )
    where

import Control.Wire.Prefab.Simple
import Control.Wire.Types


-- | General accumulator.  Outputs the argument value at the first
-- instant, then applies the input function repeatedly for subsequent
-- instants.  This acts like the 'iterate' function for lists.
--
-- * Depends: current instant.

accum :: a -> Wire e (>~) (a -> a) a
accum x =
    mkPure $ \f -> x `seq` (Right x, accum (f x))


-- | Apply the given function at the first instant.  Then act as the
-- identity wire forever.
--
-- * Depends: Current instant.

atFirst :: (b -> b) -> Wire e (>~) b b
atFirst f = mkPure $ \x -> (Right (f x), identity)


-- | Count upwards from the given starting value.

countFrom :: Enum b => b -> Wire e (>~) a b
countFrom n = mkPure $ \_ -> n `seq` (Right n, countFrom (succ n))


-- | Count from the given starting value, repeatedly adding the input
-- signal to it.
--
-- * Depends: current instant.

countStep :: Num a => a -> Wire e (>~) a a
countStep x = mkPure $ \dx -> x `seq` (Right x, countStep (x + dx))