Copyright | (C) 2018 Francesco Ariis |
---|---|
License | BSD3 (see LICENSE file) |
Maintainer | Francesco Ariis <fa-ml@ariis.it> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Timers and timed resources (animations, etc.) utilities for tick-based programs.
Synopsis
- creaTimer :: a -> a -> Integer -> Timed a
- creaBoolTimer :: Integer -> Timed Bool
- creaTimerLoop :: a -> a -> Integer -> Timed a
- creaBoolTimerLoop :: Integer -> Timed Bool
- data Timed a
- creaTimedRes :: Loop -> [(Integer, a)] -> Timed a
- data Loop
- data ExpBehaviour
- tick :: Timed a -> Timed a
- ticks :: Integer -> Timed a -> Timed a
- reset :: Timed a -> Timed a
- isLive :: Timed a -> Bool
- isExpired :: Timed a -> Bool
- fetchFrame :: Timed a -> a
- getFrames :: Timed a -> [(Integer, a)]
Simple timers
creaTimer :: a -> a -> Integer -> Timed a Source #
A simple off/on timer expiring in fixed number of ticks.
Example:
timer = creaTimer Nothing (Just "Over!") 4 test t | isExpired t = print (fetchFrame t) | otherwise = do print (fetchFrame t) test (tick t) -- λ> test timer -- Nothing -- Nothing -- Nothing -- Nothing -- Just "Over"!
creaBoolTimerLoop :: Integer -> Timed Bool Source #
Shorthand for:
.creaTimerLoop
False True i
Timed resources
A timed resource is a timer which, at any given moment, points to a specific item (like an animation).
Example:
timer = creaTimedRes (Times 1 Elapse) [(2, "a "), (1, "b "), (2, "c ")] test t | isExpired t = putStrLn "Fine." | otherwise = do putStr (fetchFrame t) test (tick t) -- λ> test timer -- a a b c c Fine.
creaTimedRes :: Loop -> [(Integer, a)] -> Timed a Source #
Most general way to create a time-based resource (like an animation).
Loop
controls the expiring behaviour, [(Integer, a)]
is a list of
frames and their duration.
Number of times to repeat the animation.
AlwaysLoop | Loops forever, never expires. |
Times Integer ExpBehaviour | Repeats the cycle for a fixed number of times. |
Instances
Eq Loop Source # | |
Show Loop Source # | |
Generic Loop Source # | |
type Rep Loop Source # | |
Defined in Control.Timer.Tick type Rep Loop = D1 (MetaData "Loop" "Control.Timer.Tick" "timers-tick-0.4.1.0-86aYijwsL07macaL4hOFs" False) (C1 (MetaCons "AlwaysLoop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Times" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExpBehaviour))) |
data ExpBehaviour Source #
Expire behaviour.
Instances
Eq ExpBehaviour Source # | |
Defined in Control.Timer.Tick (==) :: ExpBehaviour -> ExpBehaviour -> Bool # (/=) :: ExpBehaviour -> ExpBehaviour -> Bool # | |
Show ExpBehaviour Source # | |
Defined in Control.Timer.Tick showsPrec :: Int -> ExpBehaviour -> ShowS # show :: ExpBehaviour -> String # showList :: [ExpBehaviour] -> ShowS # | |
Generic ExpBehaviour Source # | |
Defined in Control.Timer.Tick type Rep ExpBehaviour :: Type -> Type # from :: ExpBehaviour -> Rep ExpBehaviour x # to :: Rep ExpBehaviour x -> ExpBehaviour # | |
type Rep ExpBehaviour Source # | |
Use
Query
isExpired :: Timed a -> Bool Source #
Checks wheter the timer is expired (an expired timer will not
respond to tick
).
fetchFrame :: Timed a -> a Source #
Fetches the current resource of the timer.