Nettle.FRPControl.AFRP
- module Control.Arrow
- class 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
- class RandomGen g where
- class Random a where
- (#) :: (a -> b) -> (b -> c) -> a -> c
- dup :: a -> (a, a)
- swap :: (a, b) -> (b, a)
- type Time = Double
- data SF a b
- data Event a
- identity :: SF a a
- constant :: b -> SF a b
- localTime :: SF a Time
- time :: SF a Time
- (-->) :: b -> SF a b -> SF a b
- (>--) :: a -> SF a b -> SF a b
- (-=>) :: (b -> b) -> SF a b -> SF a b
- (>=-) :: (a -> a) -> SF a b -> SF a b
- initially :: a -> SF a a
- never :: SF a (Event b)
- now :: b -> SF a (Event b)
- after :: Time -> b -> SF a (Event b)
- repeatedly :: Time -> b -> SF a (Event b)
- afterEach :: [(Time, b)] -> SF a (Event b)
- edge :: SF Bool (Event ())
- iEdge :: Bool -> SF Bool (Event ())
- edgeTag :: a -> SF Bool (Event a)
- edgeJust :: SF (Maybe a) (Event a)
- edgeBy :: (a -> a -> Maybe b) -> a -> SF a (Event b)
- notYet :: SF (Event a) (Event a)
- once :: SF (Event a) (Event a)
- takeEvents :: Int -> SF (Event a) (Event a)
- dropEvents :: Int -> SF (Event a) (Event a)
- switch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b
- dSwitch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b
- rSwitch :: SF a b -> SF (a, Event (SF a b)) b
- drSwitch :: SF a b -> SF (a, Event (SF a b)) b
- kSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a b
- dkSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a b
- parB :: Functor col => col (SF a b) -> SF a (col b)
- pSwitchB :: Functor col => col (SF a b) -> SF (a, col b) (Event c) -> (col (SF a b) -> c -> SF a (col b)) -> SF a (col b)
- dpSwitchB :: Functor col => col (SF a b) -> SF (a, col b) (Event c) -> (col (SF a b) -> c -> SF a (col b)) -> SF a (col b)
- rpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b)
- drpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b)
- par :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF a (col c)
- pSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, col c) (Event d) -> (col (SF b c) -> d -> SF a (col c)) -> SF a (col c)
- dpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, col c) (Event d) -> (col (SF b c) -> d -> SF a (col c)) -> SF a (col c)
- rpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, Event (col (SF b c) -> col (SF b c))) (col c)
- drpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, Event (col (SF b c) -> col (SF b c))) (col c)
- hold :: a -> SF (Event a) a
- trackAndHold :: a -> SF (Maybe a) a
- accum :: a -> SF (Event (a -> a)) (Event a)
- accumBy :: (b -> a -> b) -> b -> SF (Event a) (Event b)
- accumFilter :: (c -> a -> (c, Maybe b)) -> c -> SF (Event a) (Event b)
- pre :: SF a a
- iPre :: a -> SF a a
- integral :: VectorSpace a s => SF a a
- derivative :: VectorSpace a s => SF a a
- imIntegral :: VectorSpace a s => a -> SF a a
- loopPre :: c -> SF (a, c) (b, c) -> SF a b
- loopIntegral :: VectorSpace c s => SF (a, c) (b, c) -> SF a b
- noEvent :: Event a
- noEventFst :: (Event a, b) -> (Event c, b)
- noEventSnd :: (a, Event b) -> (a, Event c)
- liftE :: (a -> b) -> Event a -> Event b
- event :: a -> (b -> a) -> Event b -> a
- fromEvent :: Monoid a => Event a -> a
- isEvent :: Event a -> Bool
- isNoEvent :: Event a -> Bool
- tag :: Event a -> b -> Event b
- attach :: Event a -> b -> Event (a, b)
- lMerge :: Event a -> Event a -> Event a
- rMerge :: Event a -> Event a -> Event a
- merge :: Event a -> Event a -> Event a
- mergeBy :: (a -> a -> a) -> Event a -> Event a -> Event a
- mapMerge :: (a -> c) -> (b -> c) -> (a -> b -> c) -> Event a -> Event b -> Event c
- mergeEvents :: [Event a] -> Event a
- mergeEventsBy :: (a -> a -> a) -> [Event a] -> Event a
- catEvents :: [Event a] -> Event [a]
- joinE :: Event a -> Event b -> Event (a, b)
- splitE :: Event (a, b) -> (Event a, Event b)
- filterE :: (a -> Bool) -> Event a -> Event a
- mapFilterE :: (a -> Maybe b) -> Event a -> Event b
- gate :: Event a -> Bool -> Event a
- maybeToEvent :: Maybe a -> Event a
- noise :: (RandomGen g, Random b) => g -> SF a b
- noiseR :: (RandomGen g, Random b) => (b, b) -> g -> SF a b
- occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b)
- reactimate :: IO a -> (Bool -> IO (DTime, Maybe a)) -> (Bool -> b -> IO Bool) -> SF a b -> IO ()
- type ReactHandle a b = IORef (ReactState a b)
- reactInit :: IO a -> (ReactHandle a b -> Bool -> b -> IO Bool) -> SF a b -> IO (ReactHandle a b)
- react :: ReactHandle a b -> (DTime, Maybe a) -> IO Bool
- type DTime = Double
- embed :: SF a b -> (a, [(DTime, Maybe a)]) -> [b]
- embedSynch :: SF a b -> (a, [(DTime, Maybe a)]) -> SF Double b
- deltaEncode :: Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)])
- deltaEncodeBy :: (a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])
- evalSF :: SF a b -> (a, [(DTime, a)]) -> [(DTime, b)]
- initDelay :: [a] -> SF a a
Documentation
module Control.Arrow
class Floating a => VectorSpace v a | v -> a whereSource
Instances
VectorSpace Double Double | |
VectorSpace Float Float | |
RealFloat a => VectorSpace (Vector2 a) a | |
RealFloat a => VectorSpace (Vector3 a) a | |
Floating a => VectorSpace (a, a) a | |
Floating a => VectorSpace (a, a, a) a | |
Floating a => VectorSpace (a, a, a, a) a | |
Floating a => VectorSpace (a, a, a, a, a) a |
class RandomGen g where
The class RandomGen
provides a common interface to random number
generators.
Methods
The next
operation returns an Int
that is uniformly distributed
in the range returned by genRange
(including both end points),
and a new generator.
split :: g -> (g, g)
The split
operation allows one to obtain two distinct random number
generators. This is very useful in functional programs (for example, when
passing a random number generator down to recursive calls), but very
little work has been done on statistically robust implementations of
split
([System.Random, System.Random]
are the only examples we know of).
The genRange
operation yields the range of values returned by
the generator.
It is required that:
The second condition ensures that genRange
cannot examine its
argument, and hence the value it returns can be determined only by the
instance of RandomGen
. That in turn allows an implementation to make
a single call to genRange
to establish a generator's range, without
being concerned that the generator returned by (say) next
might have
a different range to the generator passed to next
.
The default definition spans the full range of Int
.
class Random a where
With a source of random number supply in hand, the Random
class allows the
programmer to extract random values of a variety of types.
Methods
randomR :: RandomGen g => (a, a) -> g -> (a, g)
Takes a range (lo,hi) and a random number generator g, and returns a random value uniformly distributed in the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi. For continuous types there is no requirement that the values lo and hi are ever produced, but they may be, depending on the implementation and the interval.
random :: RandomGen g => g -> (a, g)
The same as randomR
, but using a default range determined by the type:
randomRs :: RandomGen g => (a, a) -> g -> [a]
Plural variant of randomR
, producing an infinite list of
random values instead of returning a new generator.
randoms :: RandomGen g => g -> [a]
Plural variant of random
, producing an infinite list of
random values instead of returning a new generator.
A variant of randomR
that uses the global random number generator
(see System.Random).
A variant of random
that uses the global random number generator
(see System.Random).
repeatedly :: Time -> b -> SF a (Event b)Source
pSwitchB :: Functor col => col (SF a b) -> SF (a, col b) (Event c) -> (col (SF a b) -> c -> SF a (col b)) -> SF a (col b)Source
dpSwitchB :: Functor col => col (SF a b) -> SF (a, col b) (Event c) -> (col (SF a b) -> c -> SF a (col b)) -> SF a (col b)Source
rpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b)Source
drpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b)Source
pSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, col c) (Event d) -> (col (SF b c) -> d -> SF a (col c)) -> SF a (col c)Source
dpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, col c) (Event d) -> (col (SF b c) -> d -> SF a (col c)) -> SF a (col c)Source
rpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, Event (col (SF b c) -> col (SF b c))) (col c)Source
drpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, Event (col (SF b c) -> col (SF b c))) (col c)Source
trackAndHold :: a -> SF (Maybe a) aSource
integral :: VectorSpace a s => SF a aSource
derivative :: VectorSpace a s => SF a aSource
imIntegral :: VectorSpace a s => a -> SF a aSource
loopIntegral :: VectorSpace c s => SF (a, c) (b, c) -> SF a bSource
noEventFst :: (Event a, b) -> (Event c, b)Source
noEventSnd :: (a, Event b) -> (a, Event c)Source
fromEvent :: Monoid a => Event a -> aSource
Useful function for projecting a monoidal value out of an Event value.
mergeEvents :: [Event a] -> Event aSource
mergeEventsBy :: (a -> a -> a) -> [Event a] -> Event aSource
mapFilterE :: (a -> Maybe b) -> Event a -> Event bSource
maybeToEvent :: Maybe a -> Event aSource
reactimate :: IO a -> (Bool -> IO (DTime, Maybe a)) -> (Bool -> b -> IO Bool) -> SF a b -> IO ()Source
type ReactHandle a b = IORef (ReactState a b)Source
reactInit :: IO a -> (ReactHandle a b -> Bool -> b -> IO Bool) -> SF a b -> IO (ReactHandle a b)Source
Arguments
:: SF a b | Signal function to evaluate |
-> (a, [(DTime, a)]) | Initial value and sample times, with inputs |
-> [(DTime, b)] |
Evaluate the signal function.
initDelay :: [a] -> SF a aSource
Delay the input by the number of samples in the given list. The first samples
will be from the list, while the next samples will be from the input. Warning: this
operation only makes sense in the case when the sampling interval is constant, in which
case it implements a delay of length xs * dt
time units, where dt
is the sampling
interval and xs
is the input list.