module Control.Wire.Event
(
Event,
at,
never,
now,
periodic,
periodicList,
became,
noLonger,
(<&),
(&>),
dropE,
dropWhileE,
filterE,
merge,
mergeL,
mergeR,
notYet,
once,
takeE,
takeWhileE,
accumE,
accum1E,
iterateE,
maximumE,
minimumE,
productE,
sumE
)
where
import Control.Applicative
import Control.Arrow
import Control.Monad.Fix
import Control.Wire.Core
import Control.Wire.Session
import Control.Wire.Unsafe.Event
import Data.Fixed
(<&) :: (Monad m) => Wire s e m a (Event b) -> Wire s e m a (Event b) -> Wire s e m a (Event b)
(<&) = liftA2 (merge const)
infixl 5 <&
(&>) :: (Monad m) => Wire s e m a (Event b) -> Wire s e m a (Event b) -> Wire s e m a (Event b)
(&>) = liftA2 (merge (const id))
infixl 5 &>
accumE ::
(b -> a -> b)
-> b
-> Wire s e m (Event a) (Event b)
accumE f = loop
where
loop x' =
mkSFN $
event (NoEvent, loop x')
(\y -> let x = f x' y in (Event x, loop x))
accum1E ::
(a -> a -> a)
-> Wire s e m (Event a) (Event a)
accum1E f = initial
where
initial =
mkSFN $ event (NoEvent, initial) (Event &&& accumE f)
at ::
(HasTime t s)
=> t
-> Wire s e m a (Event a)
at t' =
mkSF $ \ds x ->
let t = t' dtime ds
in if t <= 0
then (Event x, never)
else (NoEvent, at t)
became :: (a -> Bool) -> Wire s e m a (Event a)
became p = off
where
off = mkSFN $ \x -> if p x then (Event x, on) else (NoEvent, off)
on = mkSFN $ \x -> (NoEvent, if p x then on else off)
dropE :: Int -> Wire s e m (Event a) (Event a)
dropE n | n <= 0 = mkId
dropE n =
fix $ \again ->
mkSFN $ \mev ->
(NoEvent, if occurred mev then dropE (pred n) else again)
dropWhileE :: (a -> Bool) -> Wire s e m (Event a) (Event a)
dropWhileE p =
fix $ \again ->
mkSFN $ \mev ->
case mev of
Event x | not (p x) -> (mev, mkId)
_ -> (NoEvent, again)
filterE :: (a -> Bool) -> Wire s e m (Event a) (Event a)
filterE p =
mkSF_ $ \mev ->
case mev of
Event x | p x -> mev
_ -> NoEvent
iterateE :: a -> Wire s e m (Event (a -> a)) (Event a)
iterateE = accumE (\x f -> f x)
maximumE :: (Ord a) => Wire s e m (Event a) (Event a)
maximumE = accum1E max
minimumE :: (Ord a) => Wire s e m (Event a) (Event a)
minimumE = accum1E min
mergeL :: Event a -> Event a -> Event a
mergeL = merge const
mergeR :: Event a -> Event a -> Event a
mergeR = merge (const id)
never :: Wire s e m a (Event b)
never = mkConst (Right NoEvent)
noLonger :: (a -> Bool) -> Wire s e m a (Event a)
noLonger p = off
where
off = mkSFN $ \x -> if p x then (NoEvent, off) else (Event x, on)
on = mkSFN $ \x -> (NoEvent, if p x then off else on)
notYet :: Wire s e m (Event a) (Event a)
notYet =
mkSFN $ event (NoEvent, notYet) (const (NoEvent, mkId))
now :: Wire s e m a (Event a)
now = mkSFN $ \x -> (Event x, never)
once :: Wire s e m (Event a) (Event a)
once =
mkSFN $ \mev ->
(mev, if occurred mev then never else once)
periodic :: (HasTime t s) => t -> Wire s e m a (Event a)
periodic int | int <= 0 = error "periodic: Non-positive interval"
periodic int = mkSFN $ \x -> (Event x, loop int)
where
loop 0 = loop int
loop t' =
mkSF $ \ds x ->
let t = t' dtime ds
in if t <= 0
then (Event x, loop (mod' t int))
else (NoEvent, loop t)
periodicList :: (HasTime t s) => t -> [b] -> Wire s e m a (Event b)
periodicList int _ | int <= 0 = error "periodic: Non-positive interval"
periodicList _ [] = never
periodicList int (x:xs) = mkSFN $ \_ -> (Event x, loop int xs)
where
loop _ [] = never
loop 0 xs = loop int xs
loop t' xs0@(x:xs) =
mkSF $ \ds _ ->
let t = t' dtime ds
in if t <= 0
then (Event x, loop (mod' t int) xs)
else (NoEvent, loop t xs0)
productE :: (Num a) => Wire s e m (Event a) (Event a)
productE = accumE (*) 1
sumE :: (Num a) => Wire s e m (Event a) (Event a)
sumE = accumE (+) 0
takeE :: Int -> Wire s e m (Event a) (Event a)
takeE n | n <= 0 = never
takeE n =
fix $ \again ->
mkSFN $ \mev ->
(mev, if occurred mev then takeE (pred n) else again)
takeWhileE :: (a -> Bool) -> Wire s e m (Event a) (Event a)
takeWhileE p =
fix $ \again ->
mkSFN $ \mev ->
case mev of
Event x | not (p x) -> (NoEvent, never)
_ -> (mev, again)