]> Git — Sourcephile - tmp/julm/arpeggigon.git/blob - src/RMCA/Auxiliary.hs
Sound works with multiple layers, but strange shift problem.
[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.Fixed
8 import Data.Maybe
9 import Data.ReactiveValue
10 import FRP.Yampa
11
12 --------------------------------------------------------------------------------
13 -- General functions
14 --------------------------------------------------------------------------------
15
16 (<$$>) :: (Functor f) => f a -> (a -> b) -> f b
17 (<$$>) = flip (<$>)
18
19 ($>) :: (Functor f) => f a -> b -> f b
20 ($>) = flip (<$)
21
22 bound :: (Ord a) => (a, a) -> a -> a
23 bound (min, max) x
24 | x < min = min
25 | x > max = max
26 | otherwise = x
27
28 fromMaybeM_ :: (Monad m) => Maybe (m ()) -> m ()
29 fromMaybeM_ = fromMaybe (return ())
30
31 safeHead :: [a] -> Maybe a
32 safeHead [] = Nothing
33 safeHead (x:_) = Just x
34
35 safeTail :: [a] -> [a]
36 safeTail [] = []
37 safeTail (_:xs) = xs
38
39 maybeToEvent :: Maybe a -> Event a
40 maybeToEvent Nothing = NoEvent
41 maybeToEvent (Just x) = Event x
42
43 eventToMaybe :: Event a -> Maybe a
44 eventToMaybe NoEvent = Nothing
45 eventToMaybe (Event x) = Just x
46
47 eventToList :: Event [a] -> [a]
48 eventToList NoEvent = []
49 eventToList (Event x) = x
50
51 --------------------------------------------------------------------------------
52 -- FRP
53 --------------------------------------------------------------------------------
54
55 -- stepBack contains its previous argument as its output. Because it's
56 -- 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 -- Just like stepBack but the output value is always defined and is
64 -- equal to the input at time 0.
65 stepBack' :: SF a a
66 stepBack' = proc x -> do
67 x' <- stepBack -< x
68 returnA -< fromMaybe x x'
69
70 -- Throws an Event when the incoming signal change. The Event is
71 -- tagged with the new value.
72 onChange :: (Eq a) => SF a (Event a)
73 onChange = proc x -> do
74 x' <- stepBack -< x
75 let makeEvent x x'
76 | isNothing x' = NoEvent
77 | otherwise = let x'' = fromJust x' in
78 if x'' == x then NoEvent else Event x
79 returnA -< makeEvent x x'
80
81 varFreqSine :: SF DTime Double
82 varFreqSine = sin ^<< (2*pi*) ^<< (`mod'` 1) ^<< integral <<^ (1/)
83
84 repeatedlyS :: a -> SF DTime (Event a)
85 repeatedlyS x = edgeBy (\a b -> if a * b < 0 then Just x else Nothing) 0
86 <<< varFreqSine <<^ (2*)
87
88 -- Similar to onChange but contains its initial value in the first
89 -- event.
90 onChange' :: (Eq a) => SF a (Event a)
91 onChange' = proc x -> do
92 x' <- stepBack -< x
93 -- If it's the first value, throw an Event, else behave like onChange.
94 let makeEvent x x'
95 | isNothing x' = Event x
96 | otherwise = let x'' = fromJust x' in
97 if x'' == x then NoEvent else Event x
98 returnA -< makeEvent x x'
99
100 updateRV :: (ReactiveValueReadWrite a b m) => a -> m ()
101 updateRV rv = reactiveValueRead rv >>= reactiveValueWrite rv
102
103 --------------------------------------------------------------------------------
104 -- Reactive Values
105 --------------------------------------------------------------------------------
106
107 newCBMVarRW :: a -> IO (ReactiveFieldReadWrite IO a)
108 newCBMVarRW val = do
109 mvar <- newCBMVar val
110 let getter = readCBMVar mvar
111 setter = writeCBMVar mvar
112 notifier = installCallbackCBMVar mvar
113 return $ ReactiveFieldReadWrite setter getter notifier
114
115 reactiveValueAppend :: (Monoid b, ReactiveValueReadWrite a b m) =>
116 a -> b -> m ()
117 reactiveValueAppend rv v = do ov <- reactiveValueRead rv
118 reactiveValueWrite rv (ov `mappend` v)
119
120 reactiveValueEmpty :: (Monoid b, ReactiveValueReadWrite a b m) =>
121 a -> m ()
122 reactiveValueEmpty rv = reactiveValueWrite rv mempty
123
124 reactiveValueWriteOnNotEq :: ( Eq b
125 , ReactiveValueReadWrite a b m) =>
126 a -> b -> m ()
127 reactiveValueWriteOnNotEq rv nv = do
128 ov <- reactiveValueRead rv
129 when (ov /= nv) $ reactiveValueWrite rv nv
130
131 -- Update when the value is an Event. It would be nice to have that
132 -- even for Maybe as well.
133 (>:>) :: (ReactiveValueRead a (Event b) IO, ReactiveValueWrite c b IO) =>
134 a -> c -> IO ()
135 eventRV >:> rv = reactiveValueOnCanRead eventRV syncOnEvent
136 where syncOnEvent = do
137 erv <- reactiveValueRead eventRV
138 when (isEvent erv) $ reactiveValueWrite rv $ fromEvent erv
139
140 syncRightOnLeftWithBoth :: ( ReactiveValueRead a b m
141 , ReactiveValueReadWrite c d m
142 ) => (b -> d -> d) -> a -> c -> m ()
143 syncRightOnLeftWithBoth f l r = reactiveValueOnCanRead l $ do
144 nl <- reactiveValueRead l
145 or <- reactiveValueRead r
146 reactiveValueWrite r (f nl or)
147
148 liftW3 :: ( Monad m
149 , ReactiveValueWrite a b m
150 , ReactiveValueWrite c d m
151 , ReactiveValueWrite e f m) =>
152 (i -> (b,d,f)) -> a -> c -> e -> ReactiveFieldWrite m i
153 liftW3 f a b c = ReactiveFieldWrite setter
154 where setter x = do
155 let (x1,x2,x3) = f x
156 reactiveValueWrite a x1
157 reactiveValueWrite b x2
158 reactiveValueWrite c x3
159
160 liftRW3 :: ( ReactiveValueReadWrite a b m
161 , ReactiveValueReadWrite c d m
162 , ReactiveValueReadWrite e f m) =>
163 BijectiveFunc i (b,d,f) -> a -> c -> e -> ReactiveFieldReadWrite m i
164 liftRW3 bij a b c =
165 ReactiveFieldReadWrite setter getter notifier
166 where ReactiveFieldRead getter notifier = liftR3 (curry3 f2) a b c
167 ReactiveFieldWrite setter = liftW3 f1 a b c
168 (f1, f2) = (direct bij, inverse bij)
169
170 liftR4 :: ( ReactiveValueRead a b m
171 , ReactiveValueRead c d m
172 , ReactiveValueRead e f m
173 , ReactiveValueRead g h m) =>
174 (b -> d -> f -> h -> i) -> a -> c -> e -> g -> ReactiveFieldRead m i
175 liftR4 f a b c d = ReactiveFieldRead getter notifier
176 where getter = do
177 x1 <- reactiveValueRead a
178 x2 <- reactiveValueRead b
179 x3 <- reactiveValueRead c
180 x4 <- reactiveValueRead d
181 return $ f x1 x2 x3 x4
182 notifier p = do
183 reactiveValueOnCanRead a p
184 reactiveValueOnCanRead b p
185 reactiveValueOnCanRead c p
186 reactiveValueOnCanRead d p
187
188 liftW4 :: ( Monad m
189 , ReactiveValueWrite a b m
190 , ReactiveValueWrite c d m
191 , ReactiveValueWrite e f m
192 , ReactiveValueWrite g h m) =>
193 (i -> (b,d,f,h)) -> a -> c -> e -> g -> ReactiveFieldWrite m i
194 liftW4 f a b c d = ReactiveFieldWrite setter
195 where setter x = do
196 let (x1,x2,x3,x4) = f x
197 reactiveValueWrite a x1
198 reactiveValueWrite b x2
199 reactiveValueWrite c x3
200 reactiveValueWrite d x4
201
202 liftRW4 :: ( ReactiveValueReadWrite a b m
203 , ReactiveValueReadWrite c d m
204 , ReactiveValueReadWrite e f m
205 , ReactiveValueReadWrite g h m) =>
206 BijectiveFunc i (b,d,f,h) -> a -> c -> e -> g
207 -> ReactiveFieldReadWrite m i
208 liftRW4 bij a b c d =
209 ReactiveFieldReadWrite setter getter notifier
210 where ReactiveFieldRead getter notifier = liftR4 (curry4 f2) a b c d
211 ReactiveFieldWrite setter = liftW4 f1 a b c d
212 (f1, f2) = (direct bij, inverse bij)
213
214 liftR5 :: ( ReactiveValueRead a b m
215 , ReactiveValueRead c d m
216 , ReactiveValueRead e f m
217 , ReactiveValueRead g h m
218 , ReactiveValueRead i j m) =>
219 (b -> d -> f -> h -> j -> k) -> a -> c -> e -> g -> i
220 -> ReactiveFieldRead m k
221 liftR5 f a b c d e = ReactiveFieldRead getter notifier
222 where getter = do
223 x1 <- reactiveValueRead a
224 x2 <- reactiveValueRead b
225 x3 <- reactiveValueRead c
226 x4 <- reactiveValueRead d
227 x5 <- reactiveValueRead e
228 return $ f x1 x2 x3 x4 x5
229 notifier p = do
230 reactiveValueOnCanRead a p
231 reactiveValueOnCanRead b p
232 reactiveValueOnCanRead c p
233 reactiveValueOnCanRead d p
234 reactiveValueOnCanRead e p
235
236 liftW5 :: ( Monad m
237 , ReactiveValueWrite a b m
238 , ReactiveValueWrite c d m
239 , ReactiveValueWrite e f m
240 , ReactiveValueWrite g h m
241 , ReactiveValueWrite i j m) =>
242 (k -> (b,d,f,h,j)) -> a -> c -> e -> g -> i -> ReactiveFieldWrite m k
243 liftW5 f a b c d e = ReactiveFieldWrite setter
244 where setter x = do
245 let (x1,x2,x3,x4,x5) = f x
246 reactiveValueWrite a x1
247 reactiveValueWrite b x2
248 reactiveValueWrite c x3
249 reactiveValueWrite d x4
250 reactiveValueWrite e x5
251
252 liftRW5 :: ( ReactiveValueReadWrite a b m
253 , ReactiveValueReadWrite c d m
254 , ReactiveValueReadWrite e f m
255 , ReactiveValueReadWrite g h m
256 , ReactiveValueReadWrite i j m) =>
257 BijectiveFunc k (b,d,f,h,j) -> a -> c -> e -> g -> i
258 -> ReactiveFieldReadWrite m k
259 liftRW5 bij a b c d e =
260 ReactiveFieldReadWrite setter getter notifier
261 where ReactiveFieldRead getter notifier = liftR5 (curry5 f2) a b c d e
262 ReactiveFieldWrite setter = liftW5 f1 a b c d e
263 (f1, f2) = (direct bij, inverse bij)
264
265 --------------------------------------------------------------------------------
266 -- Curry and uncurry functions
267 --------------------------------------------------------------------------------
268
269 curry3 :: ((a,b,c) -> d) -> a -> b -> c -> d
270 curry3 f a b c = f (a,b,c)
271
272 uncurry3 :: (a -> b -> c -> d) -> (a,b,c) -> d
273 uncurry3 f (a,b,c) = f a b c
274
275 curry4 :: ((a,b,c,d) -> e) -> a -> b -> c -> d -> e
276 curry4 f a b c d = f (a,b,c,d)
277
278 uncurry4 :: (a -> b -> c -> d -> e) -> (a,b,c,d) -> e
279 uncurry4 f (a,b,c,d) = f a b c d
280
281 curry5 :: ((a,b,c,d,e) -> f) -> a -> b -> c -> d -> e -> f
282 curry5 f a b c d e = f (a,b,c,d,e)
283
284 uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a,b,c,d,e) -> f
285 uncurry5 f (a,b,c,d,e) = f a b c d e