-- |
-- Module      :  FRP.Yampa.Simulation
-- 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)
--
-- Execution/simulation of signal functions.
--
-- SFs can be executed in two ways: by running them, feeding input samples one
-- by one, obtained from a monadic environment (presumably, @IO@), or by
-- passing an input stream and calculating an output stream. The former is
-- called /reactimation/, and the latter is called /embedding/.
--
-- * Running:
-- Normally, to run an SF, you would use 'reactimate', providing input samples,
-- and consuming the output samples in the 'IO' monad. This function takes over
-- the program, implementing a "main loop". If you want more control over the
-- evaluation loop (for instance, if you are using Yampa in combination with a
-- backend that also implements some main loop), you may want to use the
-- lower-level API for reactimation ('ReactHandle', 'reactInit', 'react').
--
-- * Embedding:
-- You can use 'embed' for testing, to evaluate SFs in a terminal, and to embed
-- an SF inside a larger system. The helper functions 'deltaEncode' and
-- 'deltaEncodeBy' facilitate producing input /signals/ from plain lists of
-- input samples.
--
-- This module also includes debugging aids needed to execute signal functions
-- step by step, which are used by Yampa's testing facilities.
module FRP.Yampa.Simulation
    (
      -- * Reactimation
      reactimate

      -- ** Low-level reactimation interface
    , ReactHandle
    , reactInit
    , react

      -- * Embedding
    , embed
    , embedSynch
    , deltaEncode
    , deltaEncodeBy

      -- * Debugging / Step by step simulation

    , FutureSF
    , evalAtZero
    , evalAt
    , evalFuture
    )
  where

import Control.Monad (unless)
import Data.IORef
import Data.Maybe    (fromMaybe)

import FRP.Yampa.Diagnostics
import FRP.Yampa.InternalCore (DTime, SF (..), SF' (..), sfTF')

-- * Reactimation

-- | Convenience function to run a signal function indefinitely, using a IO
-- actions to obtain new input and process the output.
--
-- This function first runs the initialization action, which provides the
-- initial input for the signal transformer at time 0.
--
-- Afterwards, an input sensing action is used to obtain new input (if any) and
-- the time since the last iteration. The argument to the input sensing
-- function indicates if it can block. If no new input is received, it is
-- assumed to be the same as in the last iteration.
--
-- After applying the signal function to the input, the actuation IO action is
-- executed. The first argument indicates if the output has changed, the second
-- gives the actual output). Actuation functions may choose to ignore the first
-- argument altogether. This action should return True if the reactimation must
-- stop, and False if it should continue.
--
-- Note that this becomes the program's /main loop/, which makes using this
-- function incompatible with GLUT, Gtk and other graphics libraries. It may
-- also impose a sizeable constraint in larger projects in which different
-- subparts run at different time steps. If you need to control the main loop
-- yourself for these or other reasons, use 'reactInit' and 'react'.

reactimate :: Monad m
           => m a                          -- ^ Initialization action
           -> (Bool -> m (DTime, Maybe a)) -- ^ Input sensing action
           -> (Bool -> b -> m Bool)        -- ^ Actuation (output processing)
                                           --   action
           -> SF a b                       -- ^ Signal function
           -> m ()
reactimate :: forall (m :: * -> *) a b.
Monad m =>
m a
-> (Bool -> m (DTime, Maybe a))
-> (Bool -> b -> m Bool)
-> SF a b
-> m ()
reactimate m a
init Bool -> m (DTime, Maybe a)
sense Bool -> b -> m Bool
actuate (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf0}) = do
    a
a0 <- m a
init
    let (SF' a b
sf, b
b0) = a -> Transition a b
tf0 a
a0
    SF' a b -> a -> b -> m ()
loop SF' a b
sf a
a0 b
b0
  where
    loop :: SF' a b -> a -> b -> m ()
loop SF' a b
sf a
a b
b = do
      Bool
done <- Bool -> b -> m Bool
actuate Bool
True b
b
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (a
a seq :: forall a b. a -> b -> b
`seq` b
b seq :: forall a b. a -> b -> b
`seq` Bool
done) forall a b. (a -> b) -> a -> b
$ do
        (DTime
dt, Maybe a
ma') <- Bool -> m (DTime, Maybe a)
sense Bool
False
        let a' :: a
a' = forall a. a -> Maybe a -> a
fromMaybe a
a Maybe a
ma'
            (SF' a b
sf', b
b') = (forall a b. SF' a b -> DTime -> a -> Transition a b
sfTF' SF' a b
sf) DTime
dt a
a'
        SF' a b -> a -> b -> m ()
loop SF' a b
sf' a
a' b
b'

-- An API for animating a signal function when some other library
-- needs to own the top-level control flow:

-- reactimate's state, maintained across samples:
data ReactState a b = ReactState
  { forall a b.
ReactState a b -> ReactHandle a b -> Bool -> b -> IO Bool
rsActuate :: ReactHandle a b -> Bool -> b -> IO Bool
  , forall a b. ReactState a b -> SF' a b
rsSF :: SF' a b
  , forall a b. ReactState a b -> a
rsA :: a
  , forall a b. ReactState a b -> b
rsB :: b
  }

-- | A reference to reactimate's state, maintained across samples.
newtype ReactHandle a b = ReactHandle
  { forall a b. ReactHandle a b -> IORef (ReactState a b)
reactHandle :: IORef (ReactState a b) }

-- | Initialize a top-level reaction handle.
reactInit :: IO a -- init
             -> (ReactHandle a b -> Bool -> b -> IO Bool) -- actuate
             -> SF a b
             -> IO (ReactHandle a b)
reactInit :: forall a b.
IO a
-> (ReactHandle a b -> Bool -> b -> IO Bool)
-> SF a b
-> IO (ReactHandle a b)
reactInit IO a
init ReactHandle a b -> Bool -> b -> IO Bool
actuate (SF {sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf0}) = do
  a
a0 <- IO a
init
  let (SF' a b
sf,b
b0) = a -> Transition a b
tf0 a
a0
  -- TODO: really need to fix this interface, since right now we
  -- just ignore termination at time 0:
  IORef (ReactState a b)
r' <- forall a. a -> IO (IORef a)
newIORef (ReactState { rsActuate :: ReactHandle a b -> Bool -> b -> IO Bool
rsActuate = ReactHandle a b -> Bool -> b -> IO Bool
actuate, rsSF :: SF' a b
rsSF = SF' a b
sf
                             , rsA :: a
rsA = a
a0, rsB :: b
rsB = b
b0
                             }
                 )
  let r :: ReactHandle a b
r = forall a b. IORef (ReactState a b) -> ReactHandle a b
ReactHandle IORef (ReactState a b)
r'
  Bool
_ <- ReactHandle a b -> Bool -> b -> IO Bool
actuate ReactHandle a b
r Bool
True b
b0
  forall (m :: * -> *) a. Monad m => a -> m a
return ReactHandle a b
r

-- | Process a single input sample.
react :: ReactHandle a b
      -> (DTime,Maybe a)
      -> IO Bool
react :: forall a b. ReactHandle a b -> (DTime, Maybe a) -> IO Bool
react ReactHandle a b
rh (DTime
dt,Maybe a
ma') = do
  ReactState a b
rs <- forall a. IORef a -> IO a
readIORef (forall a b. ReactHandle a b -> IORef (ReactState a b)
reactHandle ReactHandle a b
rh)
  let ReactState {rsActuate :: forall a b.
ReactState a b -> ReactHandle a b -> Bool -> b -> IO Bool
rsActuate = ReactHandle a b -> Bool -> b -> IO Bool
actuate, rsSF :: forall a b. ReactState a b -> SF' a b
rsSF = SF' a b
sf, rsA :: forall a b. ReactState a b -> a
rsA = a
a, rsB :: forall a b. ReactState a b -> b
rsB = b
_b } = ReactState a b
rs

  let a' :: a
a' = forall a. a -> Maybe a -> a
fromMaybe a
a Maybe a
ma'
      (SF' a b
sf',b
b') = (forall a b. SF' a b -> DTime -> a -> Transition a b
sfTF' SF' a b
sf) DTime
dt a
a'
  forall a. IORef a -> a -> IO ()
writeIORef (forall a b. ReactHandle a b -> IORef (ReactState a b)
reactHandle ReactHandle a b
rh) (ReactState a b
rs {rsSF :: SF' a b
rsSF = SF' a b
sf',rsA :: a
rsA = a
a',rsB :: b
rsB = b
b'})
  Bool
done <- ReactHandle a b -> Bool -> b -> IO Bool
actuate ReactHandle a b
rh Bool
True b
b'
  forall (m :: * -> *) a. Monad m => a -> m a
return Bool
done

-- * Embedding

-- | Given a signal function and a pair with an initial
-- input sample for the input signal, and a list of sampling
-- times, possibly with new input samples at those times,
-- it produces a list of output samples.
--
-- This is a simplified, purely-functional version of 'reactimate'.
embed :: SF a b -> (a, [(DTime, Maybe a)]) -> [b]
embed :: forall a b. SF a b -> (a, [(DTime, Maybe a)]) -> [b]
embed SF a b
sf0 (a
a0, [(DTime, Maybe a)]
dtas) = b
b0 forall a. a -> [a] -> [a]
: forall {t} {a}. t -> SF' t a -> [(DTime, Maybe t)] -> [a]
loop a
a0 SF' a b
sf [(DTime, Maybe a)]
dtas
  where
    (SF' a b
sf, b
b0) = (forall a b. SF a b -> a -> Transition a b
sfTF SF a b
sf0) a
a0

    loop :: t -> SF' t a -> [(DTime, Maybe t)] -> [a]
loop t
_ SF' t a
_ [] = []
    loop t
a_prev SF' t a
sf ((DTime
dt, Maybe t
ma) : [(DTime, Maybe t)]
dtas) =
        a
b forall a. a -> [a] -> [a]
: (t
a seq :: forall a b. a -> b -> b
`seq` a
b seq :: forall a b. a -> b -> b
`seq` t -> SF' t a -> [(DTime, Maybe t)] -> [a]
loop t
a SF' t a
sf' [(DTime, Maybe t)]
dtas)
      where
        a :: t
a        = forall a. a -> Maybe a -> a
fromMaybe t
a_prev Maybe t
ma
        (SF' t a
sf', a
b) = (forall a b. SF' a b -> DTime -> a -> Transition a b
sfTF' SF' t a
sf) DTime
dt t
a

-- | Synchronous embedding. The embedded signal function is run on the supplied
-- input and time stream at a given (but variable) ratio >= 0 to the outer time
-- flow. When the ratio is 0, the embedded signal function is paused.
embedSynch :: SF a b -> (a, [(DTime, Maybe a)]) -> SF Double b
embedSynch :: forall a b. SF a b -> (a, [(DTime, Maybe a)]) -> SF DTime b
embedSynch SF a b
sf0 (a
a0, [(DTime, Maybe a)]
dtas) = SF {sfTF :: DTime -> Transition DTime b
sfTF = forall {p}. p -> Transition DTime b
tf0}
  where
    tts :: [DTime]
tts       = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl (\DTime
t (DTime
dt, Maybe a
_) -> DTime
t forall a. Num a => a -> a -> a
+ DTime
dt) DTime
0 [(DTime, Maybe a)]
dtas
    bbs :: [b]
bbs@(b
b:[b]
_) = forall a b. SF a b -> (a, [(DTime, Maybe a)]) -> [b]
embed SF a b
sf0 (a
a0, [(DTime, Maybe a)]
dtas)

    tf0 :: p -> Transition DTime b
tf0 p
_ = (forall {b}. DTime -> [(DTime, b)] -> SF' DTime b
esAux DTime
0 (forall a b. [a] -> [b] -> [(a, b)]
zip [DTime]
tts [b]
bbs), b
b)

    esAux :: DTime -> [(DTime, b)] -> SF' DTime b
esAux DTime
_       []    = forall a. String -> String -> String -> a
intErr String
"Yampa" String
"embedSynch" String
"Empty list!"
    -- Invarying below since esAux [] is an error.
    esAux DTime
tp_prev [(DTime, b)]
tbtbs = forall a b. (DTime -> a -> Transition a b) -> SF' a b
SF' DTime -> DTime -> (SF' DTime b, b)
tf -- True
      where
        tf :: DTime -> DTime -> (SF' DTime b, b)
tf DTime
dt DTime
r | DTime
r forall a. Ord a => a -> a -> Bool
< DTime
0     = forall a. String -> String -> String -> a
usrErr String
"Yampa" String
"embedSynch" String
"Negative ratio."
                | Bool
otherwise = let tp :: DTime
tp = DTime
tp_prev forall a. Num a => a -> a -> a
+ DTime
dt forall a. Num a => a -> a -> a
* DTime
r
                                  (b
b, [(DTime, b)]
tbtbs') = forall {t} {a}. Ord t => t -> [(t, a)] -> (a, [(t, a)])
advance DTime
tp [(DTime, b)]
tbtbs
                              in (DTime -> [(DTime, b)] -> SF' DTime b
esAux DTime
tp [(DTime, b)]
tbtbs', b
b)

    -- Advance the time stamped stream to the perceived time tp.  Under the
    -- assumption that the perceived time never goes backwards (non-negative
    -- ratio), advance maintains the invariant that the perceived time is
    -- always >= the first time stamp.
    advance :: t -> [(t, a)] -> (a, [(t, a)])
advance t
_  tbtbs :: [(t, a)]
tbtbs@[(t
_, a
b)] = (a
b, [(t, a)]
tbtbs)
    advance t
tp tbtbtbs :: [(t, a)]
tbtbtbs@((t
_, a
b) : tbtbs :: [(t, a)]
tbtbs@((t
t', a
_) : [(t, a)]
_))
      | t
tp forall a. Ord a => a -> a -> Bool
<  t
t' = (a
b, [(t, a)]
tbtbtbs)
      | t
t' forall a. Ord a => a -> a -> Bool
<= t
tp = t -> [(t, a)] -> (a, [(t, a)])
advance t
tp [(t, a)]
tbtbs
    advance t
_ [(t, a)]
_ = forall a. HasCallStack => a
undefined

-- | Spaces a list of samples by a fixed time delta, avoiding
--   unnecessary samples when the input has not changed since
--   the last sample.
deltaEncode :: Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncode :: forall a. Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncode DTime
_  []        = forall a. String -> String -> String -> a
usrErr String
"Yampa" String
"deltaEncode" String
"Empty input list."
deltaEncode DTime
dt aas :: [a]
aas@(a
_:[a]
_) = forall a.
(a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncodeBy forall a. Eq a => a -> a -> Bool
(==) DTime
dt [a]
aas

-- | 'deltaEncode' parameterized by the equality test.
deltaEncodeBy :: (a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncodeBy :: forall a.
(a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncodeBy a -> a -> Bool
_  DTime
_  []      = forall a. String -> String -> String -> a
usrErr String
"Yampa" String
"deltaEncodeBy" String
"Empty input list."
deltaEncodeBy a -> a -> Bool
eq DTime
dt (a
a0:[a]
as) = (a
a0, forall a b. [a] -> [b] -> [(a, b)]
zip (forall a. a -> [a]
repeat DTime
dt) (a -> [a] -> [Maybe a]
debAux a
a0 [a]
as))
  where
    debAux :: a -> [a] -> [Maybe a]
debAux a
_      []                     = []
    debAux a
a_prev (a
a:[a]
as) | a
a a -> a -> Bool
`eq` a
a_prev = forall a. Maybe a
Nothing forall a. a -> [a] -> [a]
: a -> [a] -> [Maybe a]
debAux a
a [a]
as
                         | Bool
otherwise     = forall a. a -> Maybe a
Just a
a  forall a. a -> [a] -> [a]
: a -> [a] -> [Maybe a]
debAux a
a [a]
as

-- * Debugging / Step by step simulation

-- | A wrapper around an initialized SF (continuation), needed for testing and
-- debugging purposes.
--
newtype FutureSF a b = FutureSF { forall a b. FutureSF a b -> SF' a b
unsafeSF :: SF' a b }

-- | Evaluate an SF, and return an output and an initialized SF.
--
--   /WARN/: Do not use this function for standard simulation. This function is
--   intended only for debugging/testing. Apart from being potentially slower
--   and consuming more memory, it also breaks the FRP abstraction by making
--   samples discrete and step based.
evalAtZero :: SF a b
           -> a                  -- ^ Input sample
           -> (b, FutureSF a b)  -- ^ Output x Continuation
evalAtZero :: forall a b. SF a b -> a -> (b, FutureSF a b)
evalAtZero (SF { sfTF :: forall a b. SF a b -> a -> Transition a b
sfTF = a -> Transition a b
tf }) a
a = (b
b, forall a b. SF' a b -> FutureSF a b
FutureSF SF' a b
tf' )
  where (SF' a b
tf', b
b) = a -> Transition a b
tf a
a

-- | Evaluate an initialized SF, and return an output and a continuation.
--
--   /WARN/: Do not use this function for standard simulation. This function is
--   intended only for debugging/testing. Apart from being potentially slower
--   and consuming more memory, it also breaks the FRP abstraction by making
--   samples discrete and step based.
evalAt :: FutureSF a b
       -> DTime -> a         -- ^ Input sample
       -> (b, FutureSF a b)  -- ^ Output x Continuation
evalAt :: forall a b. FutureSF a b -> DTime -> a -> (b, FutureSF a b)
evalAt (FutureSF { unsafeSF :: forall a b. FutureSF a b -> SF' a b
unsafeSF = SF' a b
tf }) DTime
dt a
a = (b
b, forall a b. SF' a b -> FutureSF a b
FutureSF SF' a b
tf')
  where (SF' a b
tf', b
b) = (forall a b. SF' a b -> DTime -> a -> Transition a b
sfTF' SF' a b
tf) DTime
dt a
a

-- | Given a signal function and time delta, it moves the signal function into
--   the future, returning a new uninitialized SF and the initial output.
--
--   While the input sample refers to the present, the time delta refers to the
--   future (or to the time between the current sample and the next sample).
--
--   /WARN/: Do not use this function for standard simulation. This function is
--   intended only for debugging/testing. Apart from being potentially slower
--   and consuming more memory, it also breaks the FRP abstraction by making
--   samples discrete and step based.
--
evalFuture :: SF a b -> a -> DTime -> (b, SF a b)
evalFuture :: forall a b. SF a b -> a -> DTime -> (b, SF a b)
evalFuture SF a b
sf a
a DTime
dt = (b
b, DTime -> SF a b
sf' DTime
dt)
  where (b
b, DTime -> SF a b
sf') = forall a b. SF a b -> a -> (b, DTime -> SF a b)
evalStep SF a b
sf a
a

-- | Steps the signal function into the future one step. It returns the current
-- output, and a signal function that expects, apart from an input, a time
-- between samples.
evalStep :: SF a b -> a -> (b, DTime -> SF a b)
evalStep :: forall a b. SF a b -> a -> (b, DTime -> SF a b)
evalStep (SF a -> Transition a b
sf) a
a = (b
b, \DTime
dt -> forall a b. (a -> Transition a b) -> SF a b
SF (forall a b. SF' a b -> DTime -> a -> Transition a b
sfTF' SF' a b
sf' DTime
dt))
  where (SF' a b
sf', b
b) = a -> Transition a b
sf a
a