{-# LANGUAGE Arrows     #-}
{-# LANGUAGE CPP        #-}
{-# LANGUAGE RankNTypes #-}
-- The following warning is disabled so that we do not see warnings due to
-- using ListT on an MSF to implement parallelism with broadcasting.
#if __GLASGOW_HASKELL__ < 800
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
#else
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
{-# OPTIONS_HADDOCK ignore-exports #-}
-- |
-- Copyright  : (c) Ivan Perez, 2019-2022
--              (c) Ivan Perez and Manuel Baerenz, 2016-2018
-- License    : BSD3
-- Maintainer : ivan.perez@keera.co.uk
--
-- Implementation of Yampa using Monadic Stream Processing library.
module FRP.BearRiver
    (module FRP.BearRiver, module X)
  where

-- External imports
import Control.Arrow         as X
import Control.Monad.Random  (MonadRandom)
import Data.Functor.Identity (Identity (..))
import Data.Maybe            (fromMaybe)
import Data.VectorSpace      as X

-- Internal imports (dunai)
import           Control.Monad.Trans.MSF                 hiding (dSwitch)
import qualified Control.Monad.Trans.MSF                 as MSF
import           Data.MonadicStreamFunction              as X hiding (iPre,
                                                               once, reactimate,
                                                               repeatedly,
                                                               switch, trace)
import qualified Data.MonadicStreamFunction              as MSF
import           Data.MonadicStreamFunction.InternalCore (MSF (MSF, unMSF))
import           FRP.BearRiver.Arrow                     as X
import           FRP.BearRiver.Basic                     as X
import           FRP.BearRiver.Conditional               as X
import           FRP.BearRiver.Delays                    as X
import           FRP.BearRiver.Event                     as X
import           FRP.BearRiver.EventS                    as X
import           FRP.BearRiver.Integration               as X
import           FRP.BearRiver.InternalCore              as X
import           FRP.BearRiver.Scan                      as X
import           FRP.BearRiver.Switches                  as X
import           FRP.BearRiver.Time                      as X

-- Internal imports (dunai, instances)
import Data.MonadicStreamFunction.Instances.ArrowLoop () -- not needed, just
                                                         -- re-exported

-- * Events

-- | Apply an 'MSF' to every input. Freezes temporarily if the input is
-- 'NoEvent', and continues as soon as an 'Event' is received.
mapEventS :: Monad m => MSF m a b -> MSF m (Event a) (Event b)
mapEventS :: forall (m :: * -> *) a b.
Monad m =>
MSF m a b -> MSF m (Event a) (Event b)
mapEventS MSF m a b
msf = proc Event a
eventA -> case Event a
eventA of
  Event a
a -> forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr forall a. a -> Event a
Event forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
<<< MSF m a b
msf -< a
a
  Event a
NoEvent -> forall (a :: * -> * -> *) b. Arrow a => a b b
returnA           -< forall a. Event a
NoEvent

-- ** Relation to other types

-- | Convert an 'Event' into a 'Maybe' value.
--
-- Both types are isomorphic, where a value containing an event is mapped to a
-- 'Just', and 'NoEvent' is mapped to 'Nothing'. There is, however, a semantic
-- difference: a signal carrying a Maybe may change constantly, but, for a
-- signal carrying an 'Event', there should be a bounded frequency such that
-- sampling the signal faster does not render more event occurrences.
eventToMaybe :: Event a -> Maybe a
eventToMaybe :: forall a. Event a -> Maybe a
eventToMaybe = forall a b. a -> (b -> a) -> Event b -> a
event forall a. Maybe a
Nothing forall a. a -> Maybe a
Just

-- | Create an event if a 'Bool' is 'True'.
boolToEvent :: Bool -> Event ()
boolToEvent :: Bool -> Event ()
boolToEvent Bool
True  = forall a. a -> Event a
Event ()
boolToEvent Bool
False = forall a. Event a
NoEvent

-- * Discrete to continuous-time signal functions

-- ** Wave-form generation

-- | Zero-order hold.
--
-- Converts a discrete-time signal into a continuous-time signal, by holding
-- the last value until it changes in the input signal. The given parameter may
-- be used for time zero, and until the first event occurs in the input signal,
-- so hold is always well-initialized.
--
-- >>> embed (hold 1) (deltaEncode 0.1 [NoEvent, NoEvent, Event 2, NoEvent, Event 3, NoEvent])
-- [1,1,2,2,3,3]
hold :: Monad m => a -> SF m (Event a) a
hold :: forall (m :: * -> *) a. Monad m => a -> SF m (Event a) a
hold a
a = forall (m :: * -> *) c a b.
Monad m =>
c -> MSF m (a, c) (b, c) -> MSF m a b
feedback a
a forall a b. (a -> b) -> a -> b
$ forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr forall a b. (a -> b) -> a -> b
$ \(Event a
e, a
a') ->
  forall a. a -> (a, a)
dup (forall a b. a -> (b -> a) -> Event b -> a
event a
a' forall a. a -> a
id Event a
e)

-- ** Accumulators

-- | Accumulator parameterized by the accumulation function.
accumBy :: Monad m => (b -> a -> b) -> b -> SF m (Event a) (Event b)
accumBy :: forall (m :: * -> *) b a.
Monad m =>
(b -> a -> b) -> b -> SF m (Event a) (Event b)
accumBy b -> a -> b
f b
b = forall (m :: * -> *) a b.
Monad m =>
MSF m a b -> MSF m (Event a) (Event b)
mapEventS forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a s.
Monad m =>
(a -> s -> s) -> s -> MSF m a s
accumulateWith (forall a b c. (a -> b -> c) -> b -> a -> c
flip b -> a -> b
f) b
b

-- | Zero-order hold accumulator parameterized by the accumulation function.
accumHoldBy :: Monad m => (b -> a -> b) -> b -> SF m (Event a) b
accumHoldBy :: forall (m :: * -> *) b a.
Monad m =>
(b -> a -> b) -> b -> SF m (Event a) b
accumHoldBy b -> a -> b
f b
b = forall (m :: * -> *) c a b.
Monad m =>
c -> MSF m (a, c) (b, c) -> MSF m a b
feedback b
b forall a b. (a -> b) -> a -> b
$ forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr forall a b. (a -> b) -> a -> b
$ \(Event a
a, b
b') ->
  let b'' :: b
b'' = forall a b. a -> (b -> a) -> Event b -> a
event b
b' (b -> a -> b
f b
b') Event a
a
  in (b
b'', b
b'')

-- * State keeping combinators

-- ** Loops with guaranteed well-defined feedback

-- | Loop with an initial value for the signal being fed back.
loopPre :: Monad m => c -> SF m (a, c) (b, c) -> SF m a b
loopPre :: forall (m :: * -> *) c a b.
Monad m =>
c -> SF m (a, c) (b, c) -> SF m a b
loopPre = forall (m :: * -> *) c a b.
Monad m =>
c -> MSF m (a, c) (b, c) -> MSF m a b
feedback

-- * Noise (random signal) sources and stochastic event sources

-- | Stochastic event source with events occurring on average once every tAvg
-- seconds. However, no more than one event results from any one sampling
-- interval in the case of relatively sparse sampling, thus avoiding an "event
-- backlog" should sampling become more frequent at some later point in time.
occasionally :: MonadRandom m
             => Time -- ^ The time /q/ after which the event should be produced
                     -- on average
             -> b    -- ^ Value to produce at time of event
             -> SF m a (Event b)
occasionally :: forall (m :: * -> *) b a.
MonadRandom m =>
Time -> b -> SF m a (Event b)
occasionally Time
tAvg b
b
    | Time
tAvg forall a. Ord a => a -> a -> Bool
<= Time
0
    = forall a. HasCallStack => [Char] -> a
error [Char]
"bearriver: Non-positive average interval in occasionally."

    | Bool
otherwise = proc a
_ -> do
        Time
r   <- forall (m :: * -> *) b a.
(MonadRandom m, Random b) =>
(b, b) -> MSF m a b
getRandomRS (Time
0, Time
1) -< ()
        Time
dt  <- forall (m :: * -> *) a. Monad m => SF m a Time
timeDelta          -< ()
        let p :: Time
p = Time
1 forall a. Num a => a -> a -> a
- forall a. Floating a => a -> a
exp (-(Time
dt forall a. Fractional a => a -> a -> a
/ Time
tAvg))
        forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< if Time
r forall a. Ord a => a -> a -> Bool
< Time
p then forall a. a -> Event a
Event b
b else forall a. Event a
NoEvent
  where
    timeDelta :: Monad m => SF m a DTime
    timeDelta :: forall (m :: * -> *) a. Monad m => SF m a Time
timeDelta = forall (m :: * -> *) b a. Monad m => m b -> MSF m a b
constM forall (m :: * -> *) r. Monad m => ReaderT r m r
ask

-- * Execution/simulation

-- ** 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
           -> (Bool -> m (DTime, Maybe a))
           -> (Bool -> b -> m Bool)
           -> SF Identity a b
           -> m ()
reactimate :: forall (m :: * -> *) a b.
Monad m =>
m a
-> (Bool -> m (Time, Maybe a))
-> (Bool -> b -> m Bool)
-> SF Identity a b
-> m ()
reactimate m a
senseI Bool -> m (Time, Maybe a)
sense Bool -> b -> m Bool
actuate SF Identity a b
sf = do
    forall (m :: * -> *). Monad m => MSF m () Bool -> m ()
MSF.reactimateB forall a b. (a -> b) -> a -> b
$ forall {a}. MSF m a (Time, a)
senseSF forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> MSF m (Time, a) b
sfIO forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> MSF m b Bool
actuateSF
    forall (m :: * -> *) a. Monad m => a -> m a
return ()
  where
    sfIO :: MSF m (Time, a) b
sfIO = forall (m2 :: * -> *) (m1 :: * -> *) a b.
(Monad m2, Monad m1) =>
(forall c. m1 c -> m2 c) -> MSF m1 a b -> MSF m2 a b
morphS (forall (m :: * -> *) a. Monad m => a -> m a
returnforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. Identity a -> a
runIdentity) (forall (m :: * -> *) r a b.
Monad m =>
MSF (ReaderT r m) a b -> MSF m (r, a) b
runReaderS SF Identity a b
sf)

    -- Sense
    senseSF :: MSF m a (Time, a)
senseSF = forall (m :: * -> *) a b c.
Monad m =>
MSF m a (b, Maybe c) -> (c -> MSF m a b) -> MSF m a b
MSF.dSwitch forall {a}. MSF m a ((Time, a), Maybe a)
senseFirst forall {a}. a -> MSF m a (Time, a)
senseRest

    -- Sense: First sample
    senseFirst :: MSF m a ((Time, a), Maybe a)
senseFirst = forall (m :: * -> *) b a. Monad m => m b -> MSF m a b
constM m a
senseI forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (\a
x -> ((Time
0, a
x), forall a. a -> Maybe a
Just a
x))

    -- Sense: Remaining samples
    senseRest :: a -> MSF m a (Time, a)
senseRest a
a = forall (m :: * -> *) b a. Monad m => m b -> MSF m a b
constM (Bool -> m (Time, Maybe a)
sense Bool
True) forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr forall a. a -> a
id forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** forall (m :: * -> *) a. Monad m => a -> MSF m (Maybe a) a
keepLast a
a)

    keepLast :: Monad m => a -> MSF m (Maybe a) a
    keepLast :: forall (m :: * -> *) a. Monad m => a -> MSF m (Maybe a) a
keepLast a
a = forall (m :: * -> *) a b. (a -> m (b, MSF m a b)) -> MSF m a b
MSF forall a b. (a -> b) -> a -> b
$ \Maybe a
ma ->
      let a' :: a
a' = forall a. a -> Maybe a -> a
fromMaybe a
a Maybe a
ma
      in a
a' seq :: forall a b. a -> b -> b
`seq` forall (m :: * -> *) a. Monad m => a -> m a
return (a
a', forall (m :: * -> *) a. Monad m => a -> MSF m (Maybe a) a
keepLast a
a')

    -- Consume/render
    actuateSF :: MSF m b Bool
actuateSF = forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (\b
x -> (Bool
True, b
x)) forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> forall (m :: * -> *) a b. Monad m => (a -> m b) -> MSF m a b
arrM (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Bool -> b -> m Bool
actuate)

-- * Debugging / Step by step simulation

-- | 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 Identity a b -> a -> (b, SF Identity a b)
evalAtZero :: forall a b. SF Identity a b -> a -> (b, SF Identity a b)
evalAtZero SF Identity a b
sf a
a = forall a. Identity a -> a
runIdentity forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall (m :: * -> *) a b. MSF m a b -> a -> m (b, MSF m a b)
unMSF SF Identity a b
sf a
a) Time
0

-- | 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 :: SF Identity a b -> DTime -> a -> (b, SF Identity a b)
evalAt :: forall a b. SF Identity a b -> Time -> a -> (b, SF Identity a b)
evalAt SF Identity a b
sf Time
dt a
a = forall a. Identity a -> a
runIdentity forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall (m :: * -> *) a b. MSF m a b -> a -> m (b, MSF m a b)
unMSF SF Identity a b
sf a
a) Time
dt

-- | 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 Identity a b -> a -> DTime -> (b, SF Identity a b)
evalFuture :: forall a b. SF Identity a b -> a -> Time -> (b, SF Identity a b)
evalFuture SF Identity a b
sf = forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall a b. SF Identity a b -> Time -> a -> (b, SF Identity a b)
evalAt SF Identity a b
sf)