Yampa-0.9.2.2: Library for programming hybrid systems.Source codeContentsIndex
FRP.Yampa
Portabilitynon-portable (GHC extensions)
Stabilityprovisional
Maintainernilsson@cs.yale.edu
Description

New version using GADTs.

ToDo:

  • Specialize def. of repeatedly. Could have an impact on invaders.
  • New defs for accs using SFAcc
  • Make sure opt worked: e.g.
     repeatedly >>> count >>> arr (fmap sqr)
  • Introduce SFAccHld.
  • See if possible to unify AccHld wity Acc??? They are so close.
  • Introduce SScan. BUT KEEP IN MIND: Most if not all opts would have been possible without GADTs???
  • Look into pairs. At least pairing of SScan ought to be interesting.
  • Would be nice if we could get rid of first & second with impunity thanks to Id optimizations. That's a clear win, with or without an explicit pair combinator.
  • delayEventCat is a bit complicated ...

Random ideas:

  • What if one used rules to optimize - (arr :: SF a ()) to (constant ()) - (arr :: SF a a) to identity But inspection of invader source code seem to indicate that these are not very common cases at all.
  • It would be nice if it was possible to come up with opt. rules that are invariant of how signal function expressions are parenthesized. Right now, we have e.g. arr f >>> (constant c >>> sf) being optimized to cpAuxA1 f (cpAuxC1 c sf) whereas it clearly should be possible to optimize to just cpAuxC1 c sf What if we didn't use SF' but SFComp :: tfun> -> SF' a b -> SF' b c - SF' a c ???
  • The transition function would still be optimized in (pretty much) the current way, but it would still be possible to look inside composed signal functions for lost optimization opts. Seems to me this could be done without too much extra effort/no dupl. work. E.g. new cpAux, the general case:
      cpAux sf1 sf2 = SFComp tf sf1 sf2
          where
              tf dt a = (cpAux sf1' sf2', c)
                  where
                      (sf1', b) = (sfTF' sf1) dt a
                      (sf2', c) = (sfTF' sf2) dt b
  • The ONLY change was changing the constructor from SF' to SFComp and adding sf1 and sf2 to the constructor app.!
  • An optimized case: cpAuxC1 b sf1 sf2 = SFComp tf sf1 sf2 So cpAuxC1 gets an extra arg, and we change the constructor. But how to exploit without writing 1000s of rules??? Maybe define predicates on SFComp to see if the first or second sf are interesting, and if so, make reassociate and make a recursive call? E.g. we're in the arr case, and the first sf is another arr, so we'd like to combine the two.
  • It would also be intersting, then, to know when to STOP playing this game, due to the overhead involved.
  • Why don't we have a SWITCH constructor that indicates that the structure will change, and thus that it is worthwile to keep looking for opt. opportunities, whereas a plain SF' would indicate that things NEVER are going to change, and thus we can just as well give up?
Documentation
module FRP.Yampa.VectorSpace
(#) :: (a -> b) -> (b -> c) -> a -> cSource
dup :: a -> (a, a)Source
swap :: (a, b) -> (b, a)Source
type Time = DoubleSource
data SF a b Source
show/hide Instances
data Event a Source
Constructors
NoEvent
Event a
show/hide Instances
arrPrim :: (a -> b) -> SF a bSource
arrEPrim :: (Event a -> b) -> SF (Event a) bSource
identity :: SF a aSource
constant :: b -> SF a bSource
localTime :: SF a TimeSource
time :: SF a TimeSource
(-->) :: b -> SF a b -> SF a bSource
(>--) :: a -> SF a b -> SF a bSource
(-=>) :: (b -> b) -> SF a b -> SF a bSource
(>=-) :: (a -> a) -> SF a b -> SF a bSource
initially :: a -> SF a aSource
sscan :: (b -> a -> b) -> b -> SF a bSource
sscanPrim :: (c -> a -> Maybe (c, b)) -> c -> b -> SF a bSource
never :: SF a (Event b)Source
now :: b -> SF a (Event b)Source
after :: Time -> b -> SF a (Event b)Source
repeatedly :: Time -> b -> SF a (Event b)Source
afterEach :: [(Time, b)] -> SF a (Event b)Source
afterEachCat :: [(Time, b)] -> SF a (Event [b])Source
delayEvent :: Time -> SF (Event a) (Event a)Source
delayEventCat :: Time -> SF (Event a) (Event [a])Source
edge :: SF Bool (Event ())Source
iEdge :: Bool -> SF Bool (Event ())Source
edgeTag :: a -> SF Bool (Event a)Source
edgeJust :: SF (Maybe a) (Event a)Source
edgeBy :: (a -> a -> Maybe b) -> a -> SF a (Event b)Source
notYet :: SF (Event a) (Event a)Source
once :: SF (Event a) (Event a)Source
takeEvents :: Int -> SF (Event a) (Event a)Source
dropEvents :: Int -> SF (Event a) (Event a)Source
switch :: SF a (b, Event c) -> (c -> SF a b) -> SF a bSource
dSwitch :: SF a (b, Event c) -> (c -> SF a b) -> SF a bSource
rSwitch :: SF a b -> SF (a, Event (SF a b)) bSource
drSwitch :: SF a b -> SF (a, Event (SF a b)) bSource
kSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a bSource
dkSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a bSource
parB :: Functor col => col (SF a b) -> SF a (col 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
par :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF a (col c)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
old_hold :: a -> SF (Event a) aSource
hold :: a -> SF (Event a) aSource
dHold :: a -> SF (Event a) aSource
trackAndHold :: a -> SF (Maybe a) aSource
old_accum :: a -> SF (Event (a -> a)) (Event a)Source
old_accumBy :: (b -> a -> b) -> b -> SF (Event a) (Event b)Source
old_accumFilter :: (c -> a -> (c, Maybe b)) -> c -> SF (Event a) (Event b)Source
accum :: a -> SF (Event (a -> a)) (Event a)Source
accumHold :: a -> SF (Event (a -> a)) aSource
dAccumHold :: a -> SF (Event (a -> a)) aSource
accumBy :: (b -> a -> b) -> b -> SF (Event a) (Event b)Source
accumHoldBy :: (b -> a -> b) -> b -> SF (Event a) bSource
dAccumHoldBy :: (b -> a -> b) -> b -> SF (Event a) bSource
accumFilter :: (c -> a -> (c, Maybe b)) -> c -> SF (Event a) (Event b)Source
old_pre :: SF a aSource
old_iPre :: a -> SF a aSource
pre :: SF a aSource
iPre :: a -> SF a aSource
delay :: Time -> a -> SF a aSource
integral :: VectorSpace a s => SF a aSource
derivative :: VectorSpace a s => SF a aSource
imIntegral :: VectorSpace a s => a -> SF a aSource
loopPre :: c -> SF (a, c) (b, c) -> SF a bSource
loopIntegral :: VectorSpace c s => SF (a, c) (b, c) -> SF a bSource
noEvent :: Event aSource
noEventFst :: (Event a, b) -> (Event c, b)Source
noEventSnd :: (a, Event b) -> (a, Event c)Source
event :: a -> (b -> a) -> Event b -> aSource
fromEvent :: Event a -> aSource
isEvent :: Event a -> BoolSource
isNoEvent :: Event a -> BoolSource
tag :: Event a -> b -> Event bSource
tagWith :: b -> Event a -> Event bSource
attach :: Event a -> b -> Event (a, b)Source
lMerge :: Event a -> Event a -> Event aSource
rMerge :: Event a -> Event a -> Event aSource
merge :: Event a -> Event a -> Event aSource
mergeBy :: (a -> a -> a) -> Event a -> Event a -> Event aSource
mapMerge :: (a -> c) -> (b -> c) -> (a -> b -> c) -> Event a -> Event b -> Event cSource
mergeEvents :: [Event a] -> Event aSource
catEvents :: [Event a] -> Event [a]Source
joinE :: Event a -> Event b -> Event (a, b)Source
splitE :: Event (a, b) -> (Event a, Event b)Source
filterE :: (a -> Bool) -> Event a -> Event aSource
mapFilterE :: (a -> Maybe b) -> Event a -> Event bSource
gate :: Event a -> Bool -> Event aSource
noise :: (RandomGen g, Random b) => g -> SF a bSource
noiseR :: (RandomGen g, Random b) => (b, b) -> g -> SF a bSource
occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b)Source
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
react :: ReactHandle a b -> (DTime, Maybe a) -> IO BoolSource
type DTime = DoubleSource
embed :: SF a b -> (a, [(DTime, Maybe a)]) -> [b]Source
embedSynch :: SF a b -> (a, [(DTime, Maybe a)]) -> SF Double bSource
deltaEncode :: Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)])Source
deltaEncodeBy :: (a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])Source
Produced by Haddock version 2.3.0