timers-tick-0.4.2.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 :: 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"!

creaBoolTimer :: Integer -> Timed Bool Source #

Shorthand for: creaTimer False True i.

creaTimerLoop :: a -> a -> Integer -> Timed a Source #

A looped version of creaTimer.

creaBoolTimerLoop :: Integer -> Timed Bool Source #

Shorthand for: creaTimerLoop False True i.

Timed resources

data Timed a Source #

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.
Instances
Functor Timed Source #

Mapping on frames.

Instance details

Defined in Control.Timer.Tick

Methods

fmap :: (a -> b) -> Timed a -> Timed b #

(<$) :: a -> Timed b -> Timed a #

Eq a => Eq (Timed a) Source # 
Instance details

Defined in Control.Timer.Tick

Methods

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

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

Show a => Show (Timed a) Source # 
Instance details

Defined in Control.Timer.Tick

Methods

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

show :: Timed a -> String #

showList :: [Timed a] -> ShowS #

Generic (Timed a) Source # 
Instance details

Defined in Control.Timer.Tick

Associated Types

type Rep (Timed a) :: Type -> Type #

Methods

from :: Timed a -> Rep (Timed a) x #

to :: Rep (Timed a) x -> Timed a #

type Rep (Timed a) Source # 
Instance details

Defined in Control.Timer.Tick

type Rep (Timed a)

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.

data Loop Source #

Number of times to repeat the animation.

Constructors

AlwaysLoop

Loops forever, never expires.

Times Integer ExpBehaviour

Repeats the cycle for a fixed number of times.

Instances
Eq Loop Source # 
Instance details

Defined in Control.Timer.Tick

Methods

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

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

Show Loop Source # 
Instance details

Defined in Control.Timer.Tick

Methods

showsPrec :: Int -> Loop -> ShowS #

show :: Loop -> String #

showList :: [Loop] -> ShowS #

Generic Loop Source # 
Instance details

Defined in Control.Timer.Tick

Associated Types

type Rep Loop :: Type -> Type #

Methods

from :: Loop -> Rep Loop x #

to :: Rep Loop x -> Loop #

type Rep Loop Source # 
Instance details

Defined in Control.Timer.Tick

type Rep Loop = D1 (MetaData "Loop" "Control.Timer.Tick" "timers-tick-0.4.2.0-IVXpqUmkBB94BwpFTCmacX" 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.

Constructors

Reach

Expires upon reaching last frame.

Elapse

Expires when last frame is over.

Instances
Eq ExpBehaviour Source # 
Instance details

Defined in Control.Timer.Tick

Show ExpBehaviour Source # 
Instance details

Defined in Control.Timer.Tick

Generic ExpBehaviour Source # 
Instance details

Defined in Control.Timer.Tick

Associated Types

type Rep ExpBehaviour :: Type -> Type #

type Rep ExpBehaviour Source # 
Instance details

Defined in Control.Timer.Tick

type Rep ExpBehaviour = D1 (MetaData "ExpBehaviour" "Control.Timer.Tick" "timers-tick-0.4.2.0-IVXpqUmkBB94BwpFTCmacX" False) (C1 (MetaCons "Reach" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Elapse" PrefixI False) (U1 :: Type -> Type))

Use

tick :: Timed a -> Timed a Source #

Ticks the timer (one step).

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

Ticks the timer (multiple steps).

reset :: Timed a -> Timed a Source #

Resets the timer to its original state.

lapse :: Timed a -> Timed a Source #

Ticks the timer until isExpired is True.

Query

isLive :: Timed a -> Bool Source #

Antonym of isExpired.

isLive = not isExpired

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.

getFrames :: Timed a -> [(Integer, a)] Source #

Return a list of all frames plus their duration.