module Control.FRPNow.EvStream(
EvStream,
next, nextAll,
emptyEs,
merge,
collapseSimul,
dropEv,
toChanges,
edges,
joinEs,
scanlEv,
foldrEv,
foldriEv,
fromChanges,
foldrSwitch,
foldEs,
foldBs,
catMaybesEs,filterEs,filterMapEs,filterMapEsB, filterB, during, beforeEs,
(<@@>) , snapshots, delay,
callbackStream,callStream, callIOStream,
traceEs)
where
import Data.Maybe
import Control.Monad hiding (when)
import Control.Applicative hiding (empty)
import Data.IORef
import qualified Data.Sequence as Seq
import Prelude hiding (until,length)
import qualified Prelude as P
import Debug.Trace
import Data.Monoid
import Control.FRPNow.Core
import Control.FRPNow.Lib
import Debug.Trace
newtype EvStream a = S { getEs :: Behavior (Event [a]) }
instance Functor EvStream where
fmap f (S b) = S $ (fmap f <$>) <$> b
instance Monoid (EvStream a) where
mempty = emptyEs
mappend = merge
emptyEs :: EvStream a
emptyEs = S $ pure never
merge :: EvStream a -> EvStream a -> EvStream a
merge l r = loop where
loop = S $
do l' <- getEs l
r' <- getEs r
e <- fmap nxt <$> cmpTime l' r'
let again = getEs loop
pure e `switch` fmap (const again) e
nxt (Simul l r) = l ++ r
nxt (LeftEarlier l) = l
nxt (RightEarlier r) = r
collapseSimul :: EvStream a -> EvStream [a]
collapseSimul (S s) = S $ ((\x -> [x]) <$>) <$> s
next :: EvStream a -> Behavior (Event a)
next s = (head <$>) <$> (nextAll s)
nextAll :: EvStream a -> Behavior (Event [a])
nextAll e = futuristic $ getEs e
(<@@>) :: Behavior (a -> b) -> EvStream a -> EvStream b
(<@@>) f es = S $ loop where
loop = do e <- getEs es
plan (nxt <$> e)
nxt l = (<$> l) <$> f
snapshots :: Behavior a -> EvStream () -> EvStream a
snapshots b s = S $
do e <- getEs s
((\x -> [x]) <$>) <$> snapshot b (head <$> e)
toChanges :: Eq a => Behavior a -> EvStream a
toChanges = repeatEv . change
edges :: Behavior Bool -> EvStream ()
edges = repeatEv . edge
repeatEv :: Behavior (Event a) -> EvStream a
repeatEv b = S $ loop where
loop = do e <- b
return $ (\x -> [x]) <$> e
fromChanges :: a -> EvStream a -> Behavior (Behavior a)
fromChanges i s = loop i where
loop i = do e <- nextAll s
e' <- plan (loop . last <$> e)
return (i `step` e')
dropEv :: Int -> EvStream a -> EvStream a
dropEv i (S s) = S $ loop i where
loop 0 = s
loop i = do e <- s
join <$> plan (loop (i1) <$ e)
catMaybesEs :: EvStream (Maybe a) -> EvStream a
catMaybesEs s = S $ loop where
loop = do e <- getEs s
join <$> plan (nxt <$> e)
nxt l = case catMaybes l of
[] -> loop
l -> return (return l)
filterEs :: (a -> Bool) -> EvStream a -> EvStream a
filterEs f s = catMaybesEs (toMaybef <$> s)
where toMaybef x | f x = Just x
| otherwise = Nothing
filterMapEs :: (a -> Maybe b) -> EvStream a -> EvStream b
filterMapEs f e = catMaybesEs $ f <$> e
filterMapEsB :: Behavior (a -> Maybe b) -> EvStream a -> EvStream b
filterMapEsB f e = catMaybesEs $ f <@@> e
filterB :: Behavior (a -> Bool) -> EvStream a -> EvStream a
filterB f = filterMapEsB (toMaybe <$> f)
where toMaybe f = \a -> if f a then Just a else Nothing
during :: EvStream a -> Behavior Bool -> EvStream a
e `during` b = filterB (const <$> b) e
scanlEv :: (a -> b -> a) -> a -> EvStream b -> Behavior (EvStream a)
scanlEv f i es = S <$> loop i where
loop i =
do e <- nextAll es
let e' = (\(h : t) -> tail $ scanl f i (h : t)) <$> e
ev <- plan (loop . last <$> e')
return (pure e' `switch` ev)
joinEs :: Event (EvStream b) -> EvStream b
joinEs e = S $ before `switch` after where
before = join <$> plan (getEs <$> e)
after = getEs <$> e
foldEs :: (a -> b -> a) -> a -> EvStream b -> Behavior (Behavior a)
foldEs f i s = loop i where
loop i = do e <- nextAll s
let e' = foldl f i <$> e
ev <- plan (loop <$> e')
return (i `step` ev)
foldrEv :: (a -> Event b -> b) -> EvStream a -> Behavior (Event b)
foldrEv f es = loop where
loop =
do e <- nextAll es
plan (nxt <$> e)
nxt [h] = f h <$> loop
nxt (h : t) = f h . return <$> nxt t
foldriEv :: a -> (a -> Event b -> b) -> EvStream a -> Behavior b
foldriEv i f es = f i <$> foldrEv f es
foldrSwitch :: Behavior a -> EvStream (Behavior a) -> Behavior (Behavior a)
foldrSwitch b = foldriEv b switch
foldBs :: Behavior a -> (Behavior a -> b -> Behavior a) -> EvStream b -> Behavior (Behavior a)
foldBs b f es = scanlEv f b es >>= foldrSwitch b
beforeEs :: EvStream a -> Event () -> EvStream a
beforeEs s e = S $ beforeEv `switch` en
where en = pure never <$ e
beforeEv = do se <- getEs s
ev <- first (Left <$> e) (Right <$> se)
return (ev >>= choose)
choose (Left _) = never
choose (Right x) = return x
delay :: EvStream x
-> a
-> Behavior a
-> Behavior (Behavior a)
delay s i b = loop i where
loop i =
do e <- futuristic $
do cur <- b
e <- getEs s
return (cur <$ e)
e' <- plan ( loop <$> e)
return (i `step` e')
callbackStream :: forall a. Now (EvStream a, a -> IO ())
callbackStream = do mv <- sync $ newIORef ([], Nothing)
(_,s) <- loop mv
return (S s, func mv) where
loop :: IORef ( [a], Maybe (() -> IO ()) ) -> Now ([a], Behavior (Event [a]))
loop mv =
do (l, Nothing) <- sync $ readIORef mv
(e,cb) <- callback
sync $ writeIORef mv ([], Just cb)
es <- planNow $ loop mv <$ e
let h = fst <$> es
let t = snd <$> es
return (reverse l, h `step` t)
func mv x =
do (l,mcb) <- readIORef mv
writeIORef mv (x:l, Nothing)
case mcb of
Just x -> x ()
Nothing -> return ()
callStream :: ([a] -> Now ()) -> EvStream a -> Now ()
callStream f evs = do e2 <- sample (nextAll evs)
planNow (again <$> e2)
return () where
again a = do f a
e <- sample (nextAll evs)
planNow (again <$> e)
return ()
callIOStream :: (a -> IO ()) -> EvStream a -> Now ()
callIOStream f = callStream (\x -> sync (mapM_ f x) >> return ())
traceEs :: (Show a, Eq a) => String -> EvStream a -> Now ()
traceEs s es = callIOStream (\x -> traceIO (s ++ show x)) es