Difference between revisions of "Yampa/reactimate"

From HaskellWiki
Jump to navigation Jump to search
(Directly use Data.Time.Clock.POSIX)
(6 intermediate revisions by the same user not shown)
Line 6: Line 6:
 
-> IO ()
 
-> IO ()
 
</source>
 
</source>
 
The <code>Bool</code> parameter of <code>sense</code> and <code>actuate</code> are unused if you look up the definition of reactimate so just ignore them (cf. the explanations below).
   
  +
<code>reactimate</code> basically is an input-process-output loop and forms the interface between (pure) Yampa signal functions and the (potentially impure) external world. More specifically, a Yampa signal function of type <code>SF a b</code> is an abstract data type that transforms a signal of type <code>Time -> a</code> into a signal of type <code>Time -> b</code> (note that one does not have direct access to signals in Yampa but just to signal functions). The <code>Time</code> parameter here is assumed to model continuous time but to evaluate a signal function (or a signal for that matter) it is necessary to sample the signals at discrete points in time. This is exactly what <code>reactimate</code> does (among other things).
'reactimate' basically is an input-process-output loop. Keep in mind that the signal function may take pretty complex forms like a [[Yampa/Switches|parallel switch]] embedded in a loop.
 
   
  +
== Further explanations ==
(The 'Bool' parameter of 'input' and 'output' are unused if you look up the definition of reactimate so just ignore them.)
 
  +
* The <code>init</code> action is rather self-explanatory; it executes an initial IO action (e.g. print a welcome message), which then yields an initial sample of type <code>a</code> for the signal function that is passed to <code>reactimate</code> as the last argument.
  +
* The <code>sense</code> argument is then evaluated at <code>False</code> and should return an IO action yielding a pair that contains the time passed since the last sample and a new sample of type <code>a</code> (wrapped in a <code>Maybe</code>) for the signal function. If the second component of <code>sense</code>'s return value is <code>Nothing</code> then the previous sample is used again.
  +
* <code>actuate</code> is evaluated at <code>True</code> and the signal function's output of type <code>b</code>, obtained by processing the input sample previously provided by <code>sense</code>. <code>actuate</code>'s job now is to process the output (e.g. render a collection of objects contained in it) in an IO action that yields a result of type <code>Bool</code>. If this result is <code>True</code> the processing loop stops (i.e. the IO action defined by <code>reactimate</code> returns <code>()</code>).
 
* Finally, the last argument of <code>reactimate</code> is the signal function to be run (or "animated"). Keep in mind that the signal function may take pretty complex forms like a [[Yampa/Switches|parallel switch]] embedded in a loop.
  +
  +
== Example ==
  +
To illustrate this, here's a simple example of a Hello World program but with some time dependence added. Its purpose is to print "Hello... wait for it..." to the console once and then wait for 2 seconds until it prints "World!" and then stops.
  +
<source lang="Haskell">
  +
module Main where
  +
  +
import FRP.Yampa
  +
import Data.IORef
  +
import Data.Time.Clock.POSIX
  +
  +
sf :: SF () Bool -- The signal function to be run
  +
sf = time >>> arr (\t -> if (t < 2) then False else True)
  +
-- the time signal function ignores its input and returns the time
  +
  +
main :: IO ()
  +
main = do
  +
t <- getPOSIXTime -- Current POSIX time in seconds
  +
timeRef <- newIORef t
  +
let init = putStrLn "Hello... wait for it..."
  +
sense = (\_ -> do
  +
t' <- getPOSIXTime
  +
t <- readIORef timeRef
  +
let dt = realToFrac (t' - t) -- Time difference in seconds
  +
writeIORef timeRef t'
  +
return (dt, Nothing)) -- we could equally well return (dt, Just ())
  +
actuate = (\_ x -> if x
  +
then putStrLn "World!" >> return x
  +
else return x)
  +
reactimate init sense actuate sf
  +
</source>
  +
  +
Note that as soon as <code>x</code> in the definition of <code>actuate</code> becomes <code>True</code> (that is after 2 seconds), <code>actuate</code> returns <code>True</code>, hence reactimate returns <code>()</code> and the program stops. If we change the definition of <code>actuate</code> to always return <code>False</code> the line "World!" will be print out indefinitely.
  +
  +
== Precision Issues ==
  +
In the above example, we used the <code>Data.Time.Clock.POSIX</code> module to measure time differences (alternatively <code>Data.Time.Clock</code> can be used, which internally again uses POSIX but with the disadvantage of having leap seconds). One should not use <code>System.CPUTime</code> because its precision is hardware dependent and can be very low. E.g. on a Core i7-2720QM, the precision is reduced by a factor of 10<sup>10</sup> compared to <code>Data.Time.Clock</code> (10ms vs. 1ps). This hardware dependence and potentially low precision make <code>System.CPUTime</code> unusable even for simple real time applications (like the game Pong) because the <code>integral</code> and <code>derivative</code> signal functions provided by Yampa behave unpredictably. This results in programs being highly system dependent; e.g. the ball in Pong moving significantly faster on faster hardware or even moving through a paddle because a collision is missed.

Revision as of 16:58, 22 September 2012

reactimate :: IO a                          -- init
           -> (Bool -> IO (DTime, Maybe a)) -- input/sense
           -> (Bool -> b -> IO Bool)        -- output/actuate
           -> SF a b                        -- process/signal function
           -> IO ()

The Bool parameter of sense and actuate are unused if you look up the definition of reactimate so just ignore them (cf. the explanations below).

reactimate basically is an input-process-output loop and forms the interface between (pure) Yampa signal functions and the (potentially impure) external world. More specifically, a Yampa signal function of type SF a b is an abstract data type that transforms a signal of type Time -> a into a signal of type Time -> b (note that one does not have direct access to signals in Yampa but just to signal functions). The Time parameter here is assumed to model continuous time but to evaluate a signal function (or a signal for that matter) it is necessary to sample the signals at discrete points in time. This is exactly what reactimate does (among other things).

Further explanations

  • The init action is rather self-explanatory; it executes an initial IO action (e.g. print a welcome message), which then yields an initial sample of type a for the signal function that is passed to reactimate as the last argument.
  • The sense argument is then evaluated at False and should return an IO action yielding a pair that contains the time passed since the last sample and a new sample of type a (wrapped in a Maybe) for the signal function. If the second component of sense's return value is Nothing then the previous sample is used again.
  • actuate is evaluated at True and the signal function's output of type b, obtained by processing the input sample previously provided by sense. actuate's job now is to process the output (e.g. render a collection of objects contained in it) in an IO action that yields a result of type Bool. If this result is True the processing loop stops (i.e. the IO action defined by reactimate returns ()).
  • Finally, the last argument of reactimate is the signal function to be run (or "animated"). Keep in mind that the signal function may take pretty complex forms like a parallel switch embedded in a loop.

Example

To illustrate this, here's a simple example of a Hello World program but with some time dependence added. Its purpose is to print "Hello... wait for it..." to the console once and then wait for 2 seconds until it prints "World!" and then stops.

module Main where

import FRP.Yampa
import Data.IORef
import Data.Time.Clock.POSIX

sf :: SF () Bool -- The signal function to be run
sf = time >>> arr (\t -> if (t < 2) then False else True)
-- the time signal function ignores its input and returns the time

main :: IO ()
main = do
  t <- getPOSIXTime -- Current POSIX time in seconds
  timeRef <- newIORef t
  let init = putStrLn "Hello... wait for it..."
      sense = (\_ -> do
                 t' <- getPOSIXTime
                 t <- readIORef timeRef
                 let dt = realToFrac (t' - t) -- Time difference in seconds
                 writeIORef timeRef t'
                 return (dt, Nothing)) -- we could equally well return (dt, Just ())
      actuate = (\_ x -> if x
                          then putStrLn "World!" >> return x
                          else return x)
  reactimate init sense actuate sf

Note that as soon as x in the definition of actuate becomes True (that is after 2 seconds), actuate returns True, hence reactimate returns () and the program stops. If we change the definition of actuate to always return False the line "World!" will be print out indefinitely.

Precision Issues

In the above example, we used the Data.Time.Clock.POSIX module to measure time differences (alternatively Data.Time.Clock can be used, which internally again uses POSIX but with the disadvantage of having leap seconds). One should not use System.CPUTime because its precision is hardware dependent and can be very low. E.g. on a Core i7-2720QM, the precision is reduced by a factor of 1010 compared to Data.Time.Clock (10ms vs. 1ps). This hardware dependence and potentially low precision make System.CPUTime unusable even for simple real time applications (like the game Pong) because the integral and derivative signal functions provided by Yampa behave unpredictably. This results in programs being highly system dependent; e.g. the ball in Pong moving significantly faster on faster hardware or even moving through a paddle because a collision is missed.