-- |
-- Module      : FRP.Yampa.Loop
-- Copyright   : (c) Ivan Perez, 2014-2022
--               (c) George Giorgidze, 2007-2012
--               (c) Henrik Nilsson, 2005-2006
--               (c) Antony Courtney and Henrik Nilsson, Yale University, 2003-2004
-- License     : BSD-style (see the LICENSE file in the distribution)
--
-- Maintainer  : ivan.perez@keera.co.uk
-- Stability   : provisional
--
-- Portability : non-portable -GHC extensions-
--
-- Well-initialised loops.
module FRP.Yampa.Loop
    (
      -- * Loops with guaranteed well-defined feedback
      loopPre
    , loopIntegral
    )
  where

-- External imports
import Control.Arrow    (loop, second, (>>>))
import Data.VectorSpace (VectorSpace)

-- Internal imports
import FRP.Yampa.Delays       (iPre)
import FRP.Yampa.Integration  (integral)
import FRP.Yampa.InternalCore (SF)

-- * Loops with guaranteed well-defined feedback

-- | Loop with an initial value for the signal being fed back.
loopPre :: c -> SF (a, c) (b, c) -> SF a b
loopPre :: forall c a b. c -> SF (a, c) (b, c) -> SF a b
loopPre c
cInit SF (a, c) (b, c)
sf = SF (a, c) (b, c) -> SF a b
forall b d c. SF (b, d) (c, d) -> SF b c
forall (a :: * -> * -> *) b d c.
ArrowLoop a =>
a (b, d) (c, d) -> a b c
loop (SF c c -> SF (a, c) (a, c)
forall b c d. SF b c -> SF (d, b) (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second (c -> SF c c
forall a. a -> SF a a
iPre c
cInit) SF (a, c) (a, c) -> SF (a, c) (b, c) -> SF (a, c) (b, c)
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> SF (a, c) (b, c)
sf)

-- | Loop by integrating the second value in the pair and feeding the result
-- back. Because the integral at time 0 is zero, this is always well defined.
loopIntegral :: (Fractional s, VectorSpace c s) => SF (a, c) (b, c) -> SF a b
loopIntegral :: forall s c a b.
(Fractional s, VectorSpace c s) =>
SF (a, c) (b, c) -> SF a b
loopIntegral SF (a, c) (b, c)
sf = SF (a, c) (b, c) -> SF a b
forall b d c. SF (b, d) (c, d) -> SF b c
forall (a :: * -> * -> *) b d c.
ArrowLoop a =>
a (b, d) (c, d) -> a b c
loop (SF c c -> SF (a, c) (a, c)
forall b c d. SF b c -> SF (d, b) (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second SF c c
forall s a. (Fractional s, VectorSpace a s) => SF a a
integral SF (a, c) (a, c) -> SF (a, c) (b, c) -> SF (a, c) (b, c)
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> SF (a, c) (b, c)
sf)