| Copyright | (c) Atze van der Ploeg 2015 | 
|---|---|
| License | BSD-style | 
| Maintainer | atzeus@gmail.org | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Control.FRPNow.Time
Description
Various utility functions for FRPNow related to the passing of time. All take a "clock" as an argument, i.e. a behavior that gives the seconds since the program started.
The clock itself is created by a function specialized to the
 GUI library you are using FRP with such as getClock
- localTime :: (Floating time, Ord time) => Behavior time -> Behavior (Behavior time)
 - timeFrac :: (Floating time, Ord time) => Behavior time -> time -> Behavior (Behavior time)
 - lastInputs :: (Floating time, Ord time) => Behavior time -> time -> EvStream a -> Behavior (Behavior [a])
 - bufferBehavior :: (Floating time, Ord time) => Behavior time -> time -> Behavior a -> Behavior (Behavior [(time, a)])
 - delayBy :: (Floating time, Ord time) => Behavior time -> time -> Behavior a -> Behavior (Behavior a)
 - delayByN :: (Floating time, Ord time) => Behavior time -> time -> Integer -> Behavior a -> Behavior (Behavior [a])
 - delayTime :: Eq time => Behavior time -> a -> Behavior a -> Behavior (Behavior a)
 - integrate :: VectorSpace v time => Behavior time -> Behavior v -> Behavior (Behavior v)
 - class (Eq a, Eq v, Ord v, Ord a, Floating a) => VectorSpace v a | v -> a where
- zeroVector :: v
 - (*^) :: a -> v -> v
 - (^/) :: v -> a -> v
 - negateVector :: v -> v
 - (^+^) :: v -> v -> v
 - (^-^) :: v -> v -> v
 - dot :: v -> v -> a
 - norm :: v -> a
 - normalize :: v -> v
 
 
Documentation
localTime :: (Floating time, Ord time) => Behavior time -> Behavior (Behavior time) Source
When sampled at time t, gives the time since time t
timeFrac :: (Floating time, Ord time) => Behavior time -> time -> Behavior (Behavior time) Source
Gives a behavior that linearly increases from 0 to 1 in the specified duration
Arguments
| :: (Floating time, Ord time) | |
| => Behavior time | The "clock" behavior, the behavior monotonically increases with time  | 
| -> time | The duration of the history to be kept  | 
| -> EvStream a | The input stream  | 
| -> Behavior (Behavior [a]) | 
Gives a behavior containing the values of the events in the stream that occured in the last n seconds
Arguments
| :: (Floating time, Ord time) | |
| => Behavior time | The "clock" behavior, the behavior monotonically increases with time  | 
| -> time | The duration of the history to be kept  | 
| -> Behavior a | The input behavior  | 
| -> Behavior (Behavior [(time, a)]) | 
Gives a behavior containing the values of the behavior during the last n seconds, with time stamps
Arguments
| :: (Floating time, Ord time) | |
| => Behavior time | The "clock" behavior, the behavior monotonically increases with time  | 
| -> time | The duration of the delay  | 
| -> Behavior a | The input behavior  | 
| -> Behavior (Behavior a) | 
Give a version of the behavior delayed by n seconds
Arguments
| :: (Floating time, Ord time) | |
| => Behavior time | The "clock" behavior, the behavior monotonically increases with time  | 
| -> time | The duration _between_ delayed versions  | 
| -> Integer | The number of delayed versions  | 
| -> Behavior a | The input behavior  | 
| -> Behavior (Behavior [a]) | 
Give n delayed versions of the behavior, each with the given duration in delay between them.
delayTime :: Eq time => Behavior time -> a -> Behavior a -> Behavior (Behavior a) Source
Delay a behavior by one tick of the clock. Occasionally useful to prevent immediate feedback loops. Like delay, but uses the changes of the clock as an event stream.
integrate :: VectorSpace v time => Behavior time -> Behavior v -> Behavior (Behavior v) Source
Integration using rectangle rule approximation. Integration depends on when we start integrating so the result is Behavior (Behavior v).
class (Eq a, Eq v, Ord v, Ord a, Floating a) => VectorSpace v a | v -> a where Source
A type class for vector spaces. Stolen from Yampa. Thanks Henrik :)
Minimal complete definition
zeroVector, (*^), (^+^), dot
Methods
zeroVector :: v Source
(*^) :: a -> v -> v infixr 9 Source
(^/) :: v -> a -> v infixl 9 Source
negateVector :: v -> v Source
(^+^) :: v -> v -> v infixl 6 Source
(^-^) :: v -> v -> v infixl 6 Source
Instances
| VectorSpace Double Double Source | |
| VectorSpace Float Float Source | |
| (Eq a, Floating a, Ord a) => VectorSpace (a, a) a Source | |
| (Eq a, Floating a, Ord a) => VectorSpace (a, a, a) a Source | |
| (Eq a, Floating a, Ord a) => VectorSpace (a, a, a, a) a Source | |
| (Eq a, Floating a, Ord a) => VectorSpace (a, a, a, a, a) a Source |