Skip to content

Instantly share code, notes, and snippets.

@maoe
Created May 8, 2012 09:16
Show Gist options
  • Save maoe/2633805 to your computer and use it in GitHub Desktop.
Save maoe/2633805 to your computer and use it in GitHub Desktop.
elereaのチュートリアルをeuphoriaで
module Main where
import Control.Arrow
import Control.Applicative
import Control.Monad
import Data.Maybe
import FRP.Euphoria.Collection
import FRP.Euphoria.Event
import FRP.Euphoria.Signal
import FRP.Elerea.Simple (stateful)
sigtest :: SignalGen (Signal a) -> IO [a]
sigtest gen = do
step <- start gen
replicateM 15 step
countdownE :: Int -> SignalGen (Event ())
countdownE time = do
timerS <- stateful (Just time) tick
return $ const () <$> filterE isNothing (eachSample timerS)
where
tick prev = do
t <- prev
guard $ t > 0
return $ t - 1
makeTimersE :: [(Int, (String, Int))]
-> SignalGen (Event (String, Event ()))
makeTimersE timerData = do
countS <- stateful 0 (+1)
let timerE = flattenE $ fmap occurencesAt $ eachSample countS
generatorE $ setTimer <$> timerE
where
occurencesAt :: Int -> [(String, Int)]
occurencesAt t = map snd $ filter (\(u, _) -> t == u) timerData
setTimer :: (String, Int) -> SignalGen (String, Event ())
setTimer (name, count) = do
timer <- countdownE count
return (name, timer)
timers :: [(Int, (String, Int))]
-> SignalGen (Collection Int String)
timers timerData = do
timerEvent <- makeTimersE timerData
simpleCollection 0 timerEvent
collectionToListSignal :: SignalGen (Collection k a) -> SignalGen (Signal [a])
collectionToListSignal coll =
fmap (map snd) . collectionToDiscreteList <$> coll >>= discreteToSignal
main :: IO ()
main = do
xs <- sigtest $ collectionToListSignal $
timers [ (0, ("a", 3))
, (1, ("b", 5))
, (1, ("c", 3))
, (3, ("d", 4))
]
mapM_ print xs
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment