]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Auxiliary.hs
Board SF refactored.
[tmp/julm/arpeggigon.git] / src / RMCA / Auxiliary.hs
1 {-# LANGUAGE Arrows, FlexibleContexts, MultiParamTypeClasses #-}
2
3 module RMCA.Auxiliary where
4
5 import Control.Monad
6 import Data.CBMVar
7 import Data.Maybe
8 import Data.ReactiveValue
9 import FRP.Yampa
10
11 --------------------------------------------------------------------------------
12 -- General functions
13 --------------------------------------------------------------------------------
14
15 bound :: (Ord a) => (a, a) -> a -> a
16 bound (min, max) x
17 | x < min = min
18 | x > max = max
19 | otherwise = x
20
21 fromMaybeM_ :: (Monad m) => Maybe (m ()) -> m ()
22 fromMaybeM_ = fromMaybe (return ())
23
24 --------------------------------------------------------------------------------
25 -- FRP
26 --------------------------------------------------------------------------------
27
28 -- stepBack contains its previous argument as its output. Because it's
29 -- hard to define it at time 0, it's wrapped up in a Maybe.
30 stepBack :: SF a (Maybe a)
31 stepBack = sscan f (Nothing, Nothing) >>^ snd
32 where f :: (Maybe a, Maybe a) -> a -> (Maybe a, Maybe a)
33 f (Nothing,Nothing) x' = (Just x', Nothing)
34 f (Just x, _) x' = (Just x', Just x)
35
36 -- Just like stepBack but the output value is always defined and is
37 -- equal to the input at time 0.
38 stepBack' :: SF a a
39 stepBack' = proc x -> do
40 x' <- stepBack -< x
41 returnA -< fromMaybe x x'
42
43 -- Throws an Event when the incoming signal change. The Event is
44 -- tagged with the new value.
45 onChange :: (Eq a) => SF a (Event a)
46 onChange = proc x -> do
47 x' <- stepBack -< x
48 let makeEvent x x'
49 | isNothing x' = NoEvent
50 | isJust x' = let x'' = fromJust x' in
51 if x'' == x then NoEvent else Event x
52 returnA -< makeEvent x x'
53
54 -- Similar to onChange but contains its initial value in the first
55 -- event.
56 onChange' :: (Eq a) => SF a (Event a)
57 onChange' = proc x -> do
58 x' <- stepBack -< x
59 -- If it's the first value, throw an Event, else behave like onChange.
60 let makeEvent x x'
61 | isNothing x' = Event x
62 | isJust x' = let x'' = fromJust x' in
63 if x'' == x then NoEvent else Event x
64 returnA -< makeEvent x x'
65
66 --------------------------------------------------------------------------------
67 -- Reactive Values
68 --------------------------------------------------------------------------------
69
70 newCBMVarRW :: a -> IO (ReactiveFieldReadWrite IO a)
71 newCBMVarRW val = do
72 mvar <- newCBMVar val
73 let getter = readCBMVar mvar
74 setter = writeCBMVar mvar
75 notifier = installCallbackCBMVar mvar
76 return $ ReactiveFieldReadWrite setter getter notifier
77
78 reactiveValueAppend :: (Monoid b, ReactiveValueReadWrite a b m) =>
79 a -> b -> m ()
80 reactiveValueAppend rv v = do ov <- reactiveValueRead rv
81 reactiveValueWrite rv (ov `mappend` v)
82
83 emptyRW :: (Monoid b, ReactiveValueReadWrite a b m) => a -> m b
84 emptyRW rv = do
85 val <- reactiveValueRead rv
86 reactiveValueWrite rv mempty
87 return val
88
89 -- Update when the value is an Event. It would be nice to have that
90 -- even for Maybe as well.
91 (>:>) :: (ReactiveValueRead a (Event b) IO, ReactiveValueWrite c b IO) =>
92 a -> c -> IO ()
93 eventRV >:> rv = reactiveValueOnCanRead eventRV syncOnEvent
94 where syncOnEvent = do
95 erv <- reactiveValueRead eventRV
96 when (isEvent erv) $ reactiveValueWrite rv $ fromEvent erv
97
98 liftW3 :: ( Monad m
99 , ReactiveValueWrite a b m
100 , ReactiveValueWrite c d m
101 , ReactiveValueWrite e f m) =>
102 (i -> (b,d,f)) -> a -> c -> e -> ReactiveFieldWrite m i
103 liftW3 f a b c = ReactiveFieldWrite setter
104 where setter x = do
105 let (x1,x2,x3) = f x
106 reactiveValueWrite a x1
107 reactiveValueWrite b x2
108 reactiveValueWrite c x3
109
110 liftRW3 :: ( ReactiveValueReadWrite a b m
111 , ReactiveValueReadWrite c d m
112 , ReactiveValueReadWrite e f m) =>
113 BijectiveFunc i (b,d,f) -> a -> c -> e -> ReactiveFieldReadWrite m i
114 liftRW3 bij a b c =
115 ReactiveFieldReadWrite setter getter notifier
116 where ReactiveFieldRead getter notifier = liftR3 (curry3 f2) a b c
117 ReactiveFieldWrite setter = liftW3 f1 a b c
118 (f1, f2) = (direct bij, inverse bij)
119
120 liftR4 :: ( ReactiveValueRead a b m
121 , ReactiveValueRead c d m
122 , ReactiveValueRead e f m
123 , ReactiveValueRead g h m) =>
124 (b -> d -> f -> h -> i) -> a -> c -> e -> g -> ReactiveFieldRead m i
125 liftR4 f a b c d = ReactiveFieldRead getter notifier
126 where getter = do
127 x1 <- reactiveValueRead a
128 x2 <- reactiveValueRead b
129 x3 <- reactiveValueRead c
130 x4 <- reactiveValueRead d
131 return $ f x1 x2 x3 x4
132 notifier p = do
133 reactiveValueOnCanRead a p
134 reactiveValueOnCanRead b p
135 reactiveValueOnCanRead c p
136 reactiveValueOnCanRead d p
137
138 liftW4 :: ( Monad m
139 , ReactiveValueWrite a b m
140 , ReactiveValueWrite c d m
141 , ReactiveValueWrite e f m
142 , ReactiveValueWrite g h m) =>
143 (i -> (b,d,f,h)) -> a -> c -> e -> g -> ReactiveFieldWrite m i
144 liftW4 f a b c d = ReactiveFieldWrite setter
145 where setter x = do
146 let (x1,x2,x3,x4) = f x
147 reactiveValueWrite a x1
148 reactiveValueWrite b x2
149 reactiveValueWrite c x3
150 reactiveValueWrite d x4
151
152 liftRW4 :: ( ReactiveValueReadWrite a b m
153 , ReactiveValueReadWrite c d m
154 , ReactiveValueReadWrite e f m
155 , ReactiveValueReadWrite g h m) =>
156 BijectiveFunc i (b,d,f,h) -> a -> c -> e -> g
157 -> ReactiveFieldReadWrite m i
158 liftRW4 bij a b c d =
159 ReactiveFieldReadWrite setter getter notifier
160 where ReactiveFieldRead getter notifier = liftR4 (curry4 f2) a b c d
161 ReactiveFieldWrite setter = liftW4 f1 a b c d
162 (f1, f2) = (direct bij, inverse bij)
163
164 liftR5 :: ( ReactiveValueRead a b m
165 , ReactiveValueRead c d m
166 , ReactiveValueRead e f m
167 , ReactiveValueRead g h m
168 , ReactiveValueRead i j m) =>
169 (b -> d -> f -> h -> j -> k) -> a -> c -> e -> g -> i
170 -> ReactiveFieldRead m k
171 liftR5 f a b c d e = ReactiveFieldRead getter notifier
172 where getter = do
173 x1 <- reactiveValueRead a
174 x2 <- reactiveValueRead b
175 x3 <- reactiveValueRead c
176 x4 <- reactiveValueRead d
177 x5 <- reactiveValueRead e
178 return $ f x1 x2 x3 x4 x5
179 notifier p = do
180 reactiveValueOnCanRead a p
181 reactiveValueOnCanRead b p
182 reactiveValueOnCanRead c p
183 reactiveValueOnCanRead d p
184 reactiveValueOnCanRead e p
185
186 liftW5 :: ( Monad m
187 , ReactiveValueWrite a b m
188 , ReactiveValueWrite c d m
189 , ReactiveValueWrite e f m
190 , ReactiveValueWrite g h m
191 , ReactiveValueWrite i j m) =>
192 (k -> (b,d,f,h,j)) -> a -> c -> e -> g -> i -> ReactiveFieldWrite m k
193 liftW5 f a b c d e = ReactiveFieldWrite setter
194 where setter x = do
195 let (x1,x2,x3,x4,x5) = f x
196 reactiveValueWrite a x1
197 reactiveValueWrite b x2
198 reactiveValueWrite c x3
199 reactiveValueWrite d x4
200 reactiveValueWrite e x5
201
202 liftRW5 :: ( ReactiveValueReadWrite a b m
203 , ReactiveValueReadWrite c d m
204 , ReactiveValueReadWrite e f m
205 , ReactiveValueReadWrite g h m
206 , ReactiveValueReadWrite i j m) =>
207 BijectiveFunc k (b,d,f,h,j) -> a -> c -> e -> g -> i
208 -> ReactiveFieldReadWrite m k
209 liftRW5 bij a b c d e =
210 ReactiveFieldReadWrite setter getter notifier
211 where ReactiveFieldRead getter notifier = liftR5 (curry5 f2) a b c d e
212 ReactiveFieldWrite setter = liftW5 f1 a b c d e
213 (f1, f2) = (direct bij, inverse bij)
214
215 --------------------------------------------------------------------------------
216 -- Curry and uncurry functions
217 --------------------------------------------------------------------------------
218
219 curry3 :: ((a,b,c) -> d) -> a -> b -> c -> d
220 curry3 f a b c = f (a,b,c)
221
222 uncurry3 :: (a -> b -> c -> d) -> (a,b,c) -> d
223 uncurry3 f (a,b,c) = f a b c
224
225 curry4 :: ((a,b,c,d) -> e) -> a -> b -> c -> d -> e
226 curry4 f a b c d = f (a,b,c,d)
227
228 uncurry4 :: (a -> b -> c -> d -> e) -> (a,b,c,d) -> e
229 uncurry4 f (a,b,c,d) = f a b c d
230
231 curry5 :: ((a,b,c,d,e) -> f) -> a -> b -> c -> d -> e -> f
232 curry5 f a b c d e = f (a,b,c,d,e)
233
234 uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a,b,c,d,e) -> f
235 uncurry5 f (a,b,c,d,e) = f a b c d e