sdl2-2.5.4.0: Both high- and low-level bindings to the SDL library (version 2.0.6+).
Safe HaskellSafe-Inferred
LanguageHaskell2010

SDL.Time

Synopsis

Time Measurement

ticks :: MonadIO m => m Word32 Source #

Number of milliseconds since library initialization.

See SDL_GetTicks for C documentation.

time :: (Fractional a, MonadIO m) => m a Source #

The current time in seconds since some arbitrary starting point (consist over the life of the application).

This time is derived from the system's performance counter - see SDL_GetPerformanceFrequency and SDL_GetPerformanceCounter for C documentation about the implementation.

Timer

delay :: MonadIO m => Word32 -> m () Source #

Wait a specified number of milliseconds before returning.

Users are generally recommended to use threadDelay instead, to take advantage of the abilities of the Haskell runtime.

See SDL_Delay for C documentation.

type TimerCallback = Word32 -> IO RetriggerTimer Source #

A TimerCallback is called with the interval size of the callback. It can return information as to whether or not the timer should continue to exist.

data Timer Source #

A timer created by addTimer. This Timer can be removed with removeTimer.

data RetriggerTimer Source #

RetriggerTimer allows a callback to inform SDL if the timer should be retriggered or cancelled

Constructors

Reschedule Word32

Retrigger the timer again in a given number of milliseconds.

Cancel

Cancel future invocations of this timer.

Instances

Instances details
Data RetriggerTimer Source # 
Instance details

Defined in SDL.Time

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RetriggerTimer -> c RetriggerTimer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RetriggerTimer #

toConstr :: RetriggerTimer -> Constr #

dataTypeOf :: RetriggerTimer -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RetriggerTimer) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RetriggerTimer) #

gmapT :: (forall b. Data b => b -> b) -> RetriggerTimer -> RetriggerTimer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RetriggerTimer -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RetriggerTimer -> r #

gmapQ :: (forall d. Data d => d -> u) -> RetriggerTimer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RetriggerTimer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RetriggerTimer -> m RetriggerTimer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RetriggerTimer -> m RetriggerTimer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RetriggerTimer -> m RetriggerTimer #

Generic RetriggerTimer Source # 
Instance details

Defined in SDL.Time

Associated Types

type Rep RetriggerTimer :: Type -> Type #

Read RetriggerTimer Source # 
Instance details

Defined in SDL.Time

Show RetriggerTimer Source # 
Instance details

Defined in SDL.Time

Eq RetriggerTimer Source # 
Instance details

Defined in SDL.Time

Ord RetriggerTimer Source # 
Instance details

Defined in SDL.Time

type Rep RetriggerTimer Source # 
Instance details

Defined in SDL.Time

type Rep RetriggerTimer = D1 ('MetaData "RetriggerTimer" "SDL.Time" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "Reschedule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :+: C1 ('MetaCons "Cancel" 'PrefixI 'False) (U1 :: Type -> Type))

addTimer :: MonadIO m => Word32 -> TimerCallback -> m Timer Source #

Set up a callback function to be run on a separate thread after the specified number of milliseconds has elapsed.

See SDL_AddTimer for C documentation.

removeTimer :: MonadIO m => Timer -> m Bool Source #

Remove a Timer.

See SDL_RemoveTimer for C documentation.