File: Switch.hs

package info (click to toggle)
haskell-netwire 5.0.3-6
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 184 kB
  • sloc: haskell: 1,326; makefile: 2
file content (295 lines) | stat: -rw-r--r-- 8,442 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
-- |
-- Module:     Control.Wire.Switch
-- Copyright:  (c) 2013 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>

module Control.Wire.Switch
    ( -- * Simple switching
      (-->),
      (>--),
      -- * Context switching
      modes,

      -- * Event-based switching
      -- ** Intrinsic
      switch,
      dSwitch,
      -- ** Intrinsic continuable
      kSwitch,
      dkSwitch,
      -- ** Extrinsic
      rSwitch,
      drSwitch,
      alternate,
      -- ** Extrinsic continuable
      krSwitch,
      dkrSwitch
    )
    where

import Control.Applicative
import Control.Arrow
import Control.Monad
import Control.Wire.Core
import Control.Wire.Event
import Control.Wire.Unsafe.Event
import qualified Data.Map as M
import Data.Monoid


-- | Acts like the first wire until it inhibits, then switches to the
-- second wire.  Infixr 1.
--
-- * Depends: like current wire.
--
-- * Inhibits: after switching like the second wire.
--
-- * Switch: now.

(-->) :: (Monad m) => Wire s e m a b -> Wire s e m a b -> Wire s e m a b
w1' --> w2' =
    WGen $ \ds mx' -> do
        (mx, w1) <- stepWire w1' ds mx'
        case mx of
          Left _ | Right _ <- mx' -> stepWire w2' ds mx'
          _                       -> mx `seq` return (mx, w1 --> w2')

infixr 1 -->

-- | Acts like the first wire until the second starts producing, at which point
-- it switches to the second wire.  Infixr 1.
--
-- * Depends: like current wire.
--
-- * Inhibits: after switching like the second wire.
--
-- * Switch: now.

(>--) :: (Monad m) => Wire s e m a b -> Wire s e m a b -> Wire s e m a b
w1' >-- w2' =
    WGen $ \ds mx' -> do
        (m2, w2) <- stepWire w2' ds mx'
        case m2 of
          Right _ -> m2 `seq` return (m2, w2)
          _       -> do (m1, w1) <- stepWire w1' ds mx'
                        m1 `seq` return (m1, w1 >-- w2)

infixr 1 >--


-- | Intrinsic continuable switch:  Delayed version of 'kSwitch'.
--
-- * Inhibits: like the first argument wire, like the new wire after
--   switch.  Inhibition of the second argument wire is ignored.
--
-- * Switch: once, after now, restart state.

dkSwitch ::
    (Monad m)
    => Wire s e m a b
    -> Wire s e m (a, b) (Event (Wire s e m a b -> Wire s e m a b))
    -> Wire s e m a b
dkSwitch w1' w2' =
    WGen $ \ds mx' -> do
        (mx,  w1) <- stepWire w1' ds mx'
        (mev, w2) <- stepWire w2' ds (liftA2 (,) mx' mx)
        let w | Right (Event sw) <- mev = sw w1
              | otherwise = dkSwitch w1 w2
        return (mx, w)


-- | Extrinsic switch:  Delayed version of 'rSwitch'.
--
-- * Inhibits: like the current wire.
--
-- * Switch: recurrent, after now, restart state.

drSwitch ::
    (Monad m)
    => Wire s e m a b
    -> Wire s e m (a, Event (Wire s e m a b)) b
drSwitch w' =
    WGen $ \ds mx' ->
        let nw w | Right (_, Event w1) <- mx' = w1
                 | otherwise = w
        in liftM (second (drSwitch . nw)) (stepWire w' ds (fmap fst mx'))


-- | Acts like the first wire until an event occurs then switches
-- to the second wire. Behaves like this wire until the event occurs
-- at which point a *new* instance of the first wire is switched to.
--
-- * Depends: like current wire.
--
-- * Inhibits: like the argument wires.
--
-- * Switch: once, now, restart state.

alternate ::
  (Monad m)
  => Wire s e m a b
  -> Wire s e m a b
  -> Wire s e m (a, Event x) b
alternate w1 w2 = go w1 w2 w1
    where
    go w1' w2' w' =
        WGen $ \ds mx' ->
            let (w1, w2, w) | Right (_, Event _) <- mx' = (w2', w1', w2')
                            | otherwise  = (w1', w2', w')
            in liftM (second (go w1 w2)) (stepWire w ds (fmap fst mx'))


-- | Intrinsic switch:  Delayed version of 'switch'.
--
-- * Inhibits: like argument wire until switch, then like the new wire.
--
-- * Switch: once, after now, restart state.

dSwitch ::
    (Monad m)
    => Wire s e m a (b, Event (Wire s e m a b))
    -> Wire s e m a b
dSwitch w' =
    WGen $ \ds mx' -> do
        (mx, w) <- stepWire w' ds mx'
        let nw | Right (_, Event w1) <- mx = w1
               | otherwise = dSwitch w
        return (fmap fst mx, nw)


-- | Extrinsic continuable switch.  Delayed version of 'krSwitch'.
--
-- * Inhibits: like the current wire.
--
-- * Switch: recurrent, after now, restart state.

dkrSwitch ::
    (Monad m)
    => Wire s e m a b
    -> Wire s e m (a, Event (Wire s e m a b -> Wire s e m a b)) b
dkrSwitch w' =
    WGen $ \ds mx' ->
        let nw w | Right (_, Event f) <- mx' = f w
                 | otherwise = w
        in liftM (second (dkrSwitch . nw)) (stepWire w' ds (fmap fst mx'))


-- | Intrinsic continuable switch:  @kSwitch w1 w2@ starts with @w1@.
-- Its signal is received by @w2@, which may choose to switch to a new
-- wire.  Passes the wire we are switching away from to the new wire,
-- such that it may be reused in it.
--
-- * Inhibits: like the first argument wire, like the new wire after
--   switch.  Inhibition of the second argument wire is ignored.
--
-- * Switch: once, now, restart state.

kSwitch ::
    (Monad m, Monoid s)
    => Wire s e m a b
    -> Wire s e m (a, b) (Event (Wire s e m a b -> Wire s e m a b))
    -> Wire s e m a b
kSwitch w1' w2' =
    WGen $ \ds mx' -> do
        (mx,  w1) <- stepWire w1' ds mx'
        (mev, w2) <- stepWire w2' ds (liftA2 (,) mx' mx)
        case mev of
          Right (Event sw) -> stepWire (sw w1) mempty mx'
          _                -> return (mx, kSwitch w1 w2)


-- | Extrinsic continuable switch.  This switch works like 'rSwitch',
-- except that it passes the wire we are switching away from to the new
-- wire.
--
-- * Inhibits: like the current wire.
--
-- * Switch: recurrent, now, restart state.

krSwitch ::
    (Monad m)
    => Wire s e m a b
    -> Wire s e m (a, Event (Wire s e m a b -> Wire s e m a b)) b
krSwitch w'' =
    WGen $ \ds mx' ->
        let w' | Right (_, Event f) <- mx' = f w''
               | otherwise = w''
        in liftM (second krSwitch) (stepWire w' ds (fmap fst mx'))


-- | Route the left input signal based on the current mode.  The right
-- input signal can be used to change the current mode.  When switching
-- away from a mode and then switching back to it, it will be resumed.
-- Freezes time during inactivity.
--
-- * Complexity: O(n * log n) space, O(log n) lookup time on switch wrt
--   number of started, inactive modes.
--
-- * Depends: like currently active wire (left), now (right).
--
-- * Inhibits: when active wire inhibits.
--
-- * Switch: now on mode change.

modes ::
    (Monad m, Ord k)
    => k  -- ^ Initial mode.
    -> (k -> Wire s e m a b)  -- ^ Select wire for given mode.
    -> Wire s e m (a, Event k) b
modes m0 select = loop M.empty m0 (select m0)
    where
    loop ms' m' w'' =
        WGen $ \ds mxev' ->
            case mxev' of
              Left _ -> do
                  (mx, w) <- stepWire w'' ds (fmap fst mxev')
                  return (mx, loop ms' m' w)
              Right (x', ev) -> do
                  let (ms, m, w') = switch ms' m' w'' ev
                  (mx, w) <- stepWire w' ds (Right x')
                  return (mx, loop ms m w)

    switch ms' m' w' NoEvent = (ms', m', w')
    switch ms' m' w' (Event m) =
        let ms = M.insert m' w' ms' in
        case M.lookup m ms of
          Nothing -> (ms, m, select m)
          Just w  -> (M.delete m ms, m, w)


-- | Extrinsic switch:  Start with the given wire.  Each time the input
-- event occurs, switch to the wire it carries.
--
-- * Inhibits: like the current wire.
--
-- * Switch: recurrent, now, restart state.

rSwitch ::
    (Monad m)
    => Wire s e m a b
    -> Wire s e m (a, Event (Wire s e m a b)) b
rSwitch w'' =
    WGen $ \ds mx' ->
        let w' | Right (_, Event w1) <- mx' = w1
               | otherwise = w''
        in liftM (second rSwitch) (stepWire w' ds (fmap fst mx'))


-- | Intrinsic switch:  Start with the given wire.  As soon as its event
-- occurs, switch to the wire in the event's value.
--
-- * Inhibits: like argument wire until switch, then like the new wire.
--
-- * Switch: once, now, restart state.

switch ::
    (Monad m, Monoid s)
    => Wire s e m a (b, Event (Wire s e m a b))
    -> Wire s e m a b
switch w' =
    WGen $ \ds mx' -> do
        (mx, w) <- stepWire w' ds mx'
        case mx of
          Right (_, Event w1) -> stepWire w1 mempty mx'
          _                   -> return (fmap fst mx, switch w)