-- |
-- Module      :  FRP.Yampa.Basic
-- Copyright   :  (c) Antony Courtney and Henrik Nilsson, Yale University, 2003
-- License     :  BSD-style (see the LICENSE file in the distribution)
--
-- Maintainer  :  ivan.perez@keera.co.uk
-- Stability   :  provisional
-- Portability :  non-portable (GHC extensions)
--
-- Defines basic signal functions, and elementary ways of altering them.
--
-- This module defines very basic ways of creating and modifying signal
-- functions. In particular, it defines ways of creating constant output
-- producing SFs, and SFs that just pass the signal through unmodified.
--
-- It also defines ways of altering the input and the output signal only
-- by inserting one value in the signal, or by transforming it.
module FRP.Yampa.Basic (

    -- * Basic signal functions
    identity,           -- :: SF a a
    constant,           -- :: b -> SF a b

    -- ** Initialization
    (-->),              -- :: b -> SF a b -> SF a b,            infixr 0
    (-:>),              -- :: b -> SF a b -> SF a b,            infixr 0
    (>--),              -- :: a -> SF a b -> SF a b,            infixr 0
    (-=>),              -- :: (b -> b) -> SF a b -> SF a b      infixr 0
    (>=-),              -- :: (a -> a) -> SF a b -> SF a b      infixr 0
    initially           -- :: a -> SF a a

  ) where

import FRP.Yampa.InternalCore (SF(..), SF'(..), sfConst, sfId)

infixr 0 -->, -:>, >--, -=>, >=-

------------------------------------------------------------------------------
-- Basic signal functions
------------------------------------------------------------------------------

-- | Identity: identity = arr id
--
-- Using 'identity' is preferred over lifting id, since the arrow combinators
-- know how to optimise certain networks based on the transformations being
-- applied.
identity :: SF a a
identity :: SF a a
identity = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a a
sfTF = \a
a -> (SF' a a
forall a. SF' a a
sfId, a
a)}

{-# ANN constant "HLint: ignore Use const" #-}
-- | Identity: constant b = arr (const b)
--
-- Using 'constant' is preferred over lifting const, since the arrow combinators
-- know how to optimise certain networks based on the transformations being
-- applied.
constant :: b -> SF a b
constant :: b -> SF a b
constant b
b = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = \a
_ -> (b -> SF' a b
forall b a. b -> SF' a b
sfConst b
b, b
b)}

------------------------------------------------------------------------------
-- Initialization
------------------------------------------------------------------------------

-- | Initialization operator (cf. Lustre/Lucid Synchrone).
--
-- The output at time zero is the first argument, and from
-- that point on it behaves like the signal function passed as
-- second argument.
(-->) :: b -> SF a b -> SF a b
b
b0 --> :: b -> SF a b -> SF a b
--> (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf10}) = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = \a
a0 -> (Transition a b -> SF' a b
forall a b. (a, b) -> a
fst (a -> Transition a b
tf10 a
a0), b
b0)}

-- | Output pre-insert operator.
--
-- Insert a sample in the output, and from that point on, behave
-- like the given sf.
(-:>) :: b -> SF a b -> SF a b
b
b0 -:> :: b -> SF a b -> SF a b
-:> (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf10}) = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = \a
_a0 -> (SF' a b
ct, b
b0)}
 where ct :: SF' a b
ct = (DTime -> a -> Transition a b) -> SF' a b
forall a b. (DTime -> a -> Transition a b) -> SF' a b
SF' ((DTime -> a -> Transition a b) -> SF' a b)
-> (DTime -> a -> Transition a b) -> SF' a b
forall a b. (a -> b) -> a -> b
$ \DTime
_dt a
a0 -> a -> Transition a b
tf10 a
a0

-- | Input initialization operator.
--
-- The input at time zero is the first argument, and from
-- that point on it behaves like the signal function passed as
-- second argument.
(>--) :: a -> SF a b -> SF a b
a
a0 >-- :: a -> SF a b -> SF a b
>-- (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf10}) = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = \a
_ -> a -> Transition a b
tf10 a
a0}


-- | Transform initial output value.
--
-- Applies a transformation 'f' only to the first output value at
-- time zero.
(-=>) :: (b -> b) -> SF a b -> SF a b
b -> b
f -=> :: (b -> b) -> SF a b -> SF a b
-=> (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf10}) =
    SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = \a
a0 -> let (SF' a b
sf1, b
b0) = a -> Transition a b
tf10 a
a0 in (SF' a b
sf1, b -> b
f b
b0)}


-- | Transform initial input value.
--
-- Applies a transformation 'f' only to the first input value at
-- time zero.
{-# ANN (>=-) "HLint: ignore Avoid lambda" #-}
(>=-) :: (a -> a) -> SF a b -> SF a b
a -> a
f >=- :: (a -> a) -> SF a b -> SF a b
>=- (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf10}) = SF :: forall a b. (a -> Transition a b) -> SF a b
SF {sfTF :: a -> Transition a b
sfTF = \a
a0 -> a -> Transition a b
tf10 (a -> a
f a
a0)}

-- | Override initial value of input signal.
initially :: a -> SF a a
initially :: a -> SF a a
initially = (a -> SF a a -> SF a a
forall b a. b -> SF a b -> SF a b
--> SF a a
forall a. SF a a
identity)