module Control.Wire.Switch
(
(-->),
(>--),
modes,
switch,
dSwitch,
kSwitch,
dkSwitch,
rSwitch,
drSwitch,
alternate,
krSwitch,
dkrSwitch
)
where
import qualified Data.Map as M
import Control.Applicative
import Control.Arrow
import Control.Monad
import Control.Wire.Core
import Control.Wire.Event
import Control.Wire.Unsafe.Event
import Data.Monoid
(-->) :: (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 -->
(>--) :: (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 >--
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)
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'))
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'))
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)
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'))
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)
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'))
modes ::
(Monad m, Ord k)
=> k
-> (k -> Wire s e m a b)
-> 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)
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'))
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)