]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Auxiliary/Yampa.hs
Changes to make Arpeggigon compile and run with GHC 7.8.3 and base 4.7.
[tmp/julm/arpeggigon.git] / src / RMCA / Auxiliary / Yampa.hs
1 {-# LANGUAGE Arrows #-}
2
3 module RMCA.Auxiliary.Yampa where
4
5 import FRP.Yampa
6 import Data.Maybe
7 import RMCA.Auxiliary.Misc
8
9 -- | = Yampa
10
11 countTo :: (Integral b) => b -> SF (Event a) (Event b)
12 countTo n = count >>^ filterE (== n)
13
14 -- | Synchonizes two event sources. An event on the first source will be delayed until an event occurs on the second.
15 --
16 -- Ex:
17 -- Event a => . . 1 . . . . 2 . . . 3 . . 4 . . . . . 5 . . 6 . . . . .
18 -- Event b => . a . . . b . . . c . . . . . . d . e . f . . . . . g . .
19 -- wairFor => . . . . . 1 . . . 2 . . . . . . 4 . . . 5 . . . . . 6 . .
20
21 -- A more direct approach, and without any use of *> to avoid depending
22 -- on applicatives.
23
24 waitForEvent :: SF (Event a, Event b) (Event a)
25 waitForEvent = sscanPrim procEvts NoEvent NoEvent
26 where
27 procEvts eaPrev (NoEvent, NoEvent) = Just (eaPrev, NoEvent)
28 procEvts _ (ea@(Event _), NoEvent) = Just (ea, NoEvent)
29 procEvts eaPrev (NoEvent, Event _) = Just (NoEvent, eaPrev)
30 procEvts _ (ea@(Event _), Event _) = Just (NoEvent, ea)
31
32 {-
33 waitForEvent :: SF (Event a, Event b) (Event a)
34 waitForEvent = proc (ea,eb) -> do
35 em <- arr $ uncurry $ mapMerge Left Right (\_ b -> Right b) -< (ea,eb)
36 hob <- dAccumHoldBy accumulator NoEvent -< em
37 returnA -< eb *> (ea `lMerge` hob)
38 where accumulator :: Event a -> Either a b -> Event a
39 accumulator _ (Left a) = Event a
40 accumulator _ (Right _) = NoEvent
41 --accumulator _ (Right b) =
42 -}
43
44 {-
45 waitForEvent :: SF (Event b, Event a) (Event b)
46 waitForEvent = proc (eb,ea) -> do
47 rec
48 es' <- iPre NoEvent -< es
49 es <- rSwitch waitAux -< ((eb,ea),es' `tag` waitAux)
50 returnA -< es
51 where waitAux = proc (eb,ea) -> do
52 --ea' <- (if b then notYet else identity) -< ea
53 eb' <- accumHoldBy (\_ b -> Event b) NoEvent -< eb
54 returnA -< ea *> eb'
55 -}
56 -- | 'stepBack' contains its previous argument as its output. Because it's hard to define it at time 0, it's wrapped up in a 'Maybe'.
57 stepBack :: SF a (Maybe a)
58 stepBack = sscan f (Nothing, Nothing) >>^ snd
59 where f :: (Maybe a, Maybe a) -> a -> (Maybe a, Maybe a)
60 f (Nothing,_) x' = (Just x', Nothing)
61 f (Just x, _) x' = (Just x', Just x)
62
63 -- | Like 'stepBack' but the output value is always defined and is equal to the input at time 0.
64 stepBack' :: SF a a
65 stepBack' = proc x -> do
66 x' <- stepBack -< x
67 returnA -< fromMaybe x x'
68
69 -- | Throws an 'Event' when the incoming signal change. The 'Event' is tagged with the new value.
70 onChange :: (Eq a) => SF a (Event a)
71 onChange = proc x -> do
72 x' <- stepBack -< x
73 let makeEvent x x'
74 | isNothing x' = NoEvent
75 | otherwise = let x'' = fromJust x' in
76 if x'' == x then NoEvent else Event x
77 returnA -< makeEvent x x'
78
79 -- | Similar to 'onChange' but contains its initial value in the first
80 -- event.
81 onChange' :: (Eq a) => SF a (Event a)
82 onChange' = proc x -> do
83 x' <- stepBack -< x
84 -- If it's the first value, throw an Event, else behave like onChange.
85 let makeEvent x x'
86 | isNothing x' = Event x
87 | otherwise = let x'' = fromJust x' in
88 if x'' == x then NoEvent else Event x
89 returnA -< makeEvent x x'
90
91 -- | Integrates some variable modulo something.
92 integralMod :: (Real a, VectorSpace a s) => a -> SF a a
93 integralMod x = intMod' 0
94 where intMod' x0 = switch (intMod'' x0) (\y -> intMod' (y - x))
95 intMod'' x0 = proc t -> do
96 it <- (+ x0) ^<< integral -< t
97 es <- edgeBy (\_ y -> if y > x then Just y else Nothing) 0 -< it
98 returnA -< (it,es)
99
100
101
102 -- | Generates a sine function whose period is given as a varying input.
103 varFreqSine :: SF DTime Double
104 varFreqSine = sin ^<< (2*pi*) ^<< integralMod 1 <<^ (1/)
105
106 -- | Generates an 'Event' with a regular period, which is given as an input to the signal function.
107 repeatedlyS :: a -> SF DTime (Event a)
108 repeatedlyS x = edgeBy (\a b -> if a * b < 0 then Just x else Nothing) 0
109 <<< varFreqSine <<^ (2*)
110
111 repeatedlyS' :: a -> SF DTime (Event a)
112 repeatedlyS' x = (repeatedlyS x &&& now x) >>> arr (uncurry lMerge)
113
114 -- |
115 -- = Curry and uncurry functions