timers-tick-0.1.0.0: tick based timers

Copyright(C) 2018 Francesco Ariis
LicenseBSD3 (see LICENSE file)
MaintainerFrancesco Ariis <fa-ml@ariis.it>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Timer.Tick

Contents

Description

Timers and timed resources (animations, etc.) utilities for tick-based programs.

Synopsis

Simple timers

creaTimer :: Integer -> Timer Source #

Creates a Timer expiring in x ticks.

Example:

main = count (creaTimer 4)
    where
          count t | isExpired t = putStrLn "Over!"
                  | otherwise   = do putStrLn "Ticking."
                                     count (tick t)

   -- λ> main
   -- Ticking.
   -- Ticking.
   -- Ticking.
   -- Ticking.
   -- Over!

Timed Resources

data TimedRes a Source #

A timed resource is a timer which, at any given moment, points to a specific item (like an animation).

Example:

run = creaTimedRes (Times 1) [(2, "a "), (1, "b "), (2, "c ")]
main = count run
    where
          count t | isExpired t = putStrLn "nOver!"
                  | otherwise   = do putStr (fetch t)
                                     count (tick t)
   -- λ> main
   -- a a b c c
   -- Over!

Instances

Eq a => Eq (TimedRes a) Source # 

Methods

(==) :: TimedRes a -> TimedRes a -> Bool #

(/=) :: TimedRes a -> TimedRes a -> Bool #

Show a => Show (TimedRes a) Source # 

Methods

showsPrec :: Int -> TimedRes a -> ShowS #

show :: TimedRes a -> String #

showList :: [TimedRes a] -> ShowS #

creaTimedRes :: Loop -> [(Integer, a)] -> TimedRes a Source #

Creates a time-based resource, like an animation.

data Loop Source #

Number of times to repeat the animation.

Constructors

Times Integer 
AlwaysLoop 

Instances

Eq Loop Source # 

Methods

(==) :: Loop -> Loop -> Bool #

(/=) :: Loop -> Loop -> Bool #

Show Loop Source # 

Methods

showsPrec :: Int -> Loop -> ShowS #

show :: Loop -> String #

showList :: [Loop] -> ShowS #

Use

tick :: TimedRes a -> TimedRes a Source #

Ticks the timer (one step).

ticks :: Integer -> TimedRes a -> TimedRes a Source #

Ticks the timer (multiple steps).

reset :: TimedRes a -> TimedRes a Source #

Resets the timer to its original state.

Query

isLive :: TimedRes a -> Bool Source #

Equal to not isExpired.

isExpired :: TimedRes a -> Bool Source #

Checks wheter the timer is expired (an expired timer will not respond to tick).

fetch :: TimedRes a -> a Source #

Fetches the current resource of the timer.