looper-0.3.0.1
Safe HaskellSafe-Inferred
LanguageHaskell2010

Looper

Synopsis

Documentation

data LooperDef m Source #

A looper definition

Constructors

LooperDef 

Fields

Instances

Instances details
Generic (LooperDef m) Source # 
Instance details

Defined in Looper

Associated Types

type Rep (LooperDef m) :: Type -> Type #

Methods

from :: LooperDef m -> Rep (LooperDef m) x #

to :: Rep (LooperDef m) x -> LooperDef m #

type Rep (LooperDef m) Source # 
Instance details

Defined in Looper

type Rep (LooperDef m) = D1 ('MetaData "LooperDef" "Looper" "looper-0.3.0.1-3kRKxaZEpiJ19X8DpfMDXP" 'False) (C1 ('MetaCons "LooperDef" 'PrefixI 'True) ((S1 ('MetaSel ('Just "looperDefName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "looperDefEnabled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "looperDefPeriod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime) :*: (S1 ('MetaSel ('Just "looperDefPhase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime) :*: S1 ('MetaSel ('Just "looperDefFunc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m ()))))))

milliseconds :: Double -> NominalDiffTime Source #

Construct a NominalDiffTime from a number of milliseconds

Note that scheduling can easily get in the way of accuracy at this level of granularity.

seconds :: Double -> NominalDiffTime Source #

Construct a NominalDiffTime from a number of seconds

minutes :: Double -> NominalDiffTime Source #

Construct a NominalDiffTime from a number of minutes

hours :: Double -> NominalDiffTime Source #

Construct a NominalDiffTime from a number of hours

data LooperSettings Source #

Settings that you might want to pass into a looper using mkLooperDef

Instances

Instances details
Generic LooperSettings Source # 
Instance details

Defined in Looper

Associated Types

type Rep LooperSettings :: Type -> Type #

Show LooperSettings Source # 
Instance details

Defined in Looper

Eq LooperSettings Source # 
Instance details

Defined in Looper

type Rep LooperSettings Source # 
Instance details

Defined in Looper

type Rep LooperSettings = D1 ('MetaData "LooperSettings" "Looper" "looper-0.3.0.1-3kRKxaZEpiJ19X8DpfMDXP" 'False) (C1 ('MetaCons "LooperSettings" 'PrefixI 'True) (S1 ('MetaSel ('Just "looperSetEnabled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "looperSetPhase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime) :*: S1 ('MetaSel ('Just "looperSetPeriod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime))))

mkLooperDef Source #

Arguments

:: Text

Name

-> LooperSettings 
-> m ()

The function to loop

-> LooperDef m 

runLoopers :: MonadUnliftIO m => [LooperDef m] -> m () Source #

Simply run loopers

runLoopers = runLoopersIgnoreOverrun looperDefFunc

see runLoopersIgnoreOverrun

Note that this function will loop forever, you need to wrap it using async yourself.

runLoopersIgnoreOverrun Source #

Arguments

:: MonadUnliftIO n 
=> (LooperDef m -> n ())

Custom runner

-> [LooperDef m]

Loopers

-> n () 

Run loopers with a custom runner, ignoring any overruns

runLoopersIgnoreOverrun = runLoopersRaw (pure ())

see runLoopersRaw

Note that this function will loop forever, you need to wrap it using async yourself.

runLoopersRaw Source #

Arguments

:: MonadUnliftIO n 
=> (LooperDef m -> n ())

Overrun handler

-> (LooperDef m -> n ())

Runner

-> [LooperDef m]

Loopers

-> n () 

Run loopers, with a custom runner and overrun handler

  • The overrun handler is run when the looper function takes longer than its period. You can use this to log a warning, for example.
  • The runner function is used to run the looper function You can use looperDefFunc :: LooperDef m -> m () to run a LooperDef, and you can wrap this function in some custom logic before you pass it into runLoopersRaw In this manner you can add logging or metrics, for example.

Note that this function will loop forever, you need to wrap it using async yourself.

runLooperDef Source #

Arguments

:: MonadUnliftIO n 
=> (LooperDef m -> n ())

Overrun handler

-> (LooperDef m -> n ())

Runner

-> LooperDef m

Loopers

-> Maybe (n void) 

waitNominalDiffTime :: MonadIO m => NominalDiffTime -> m () Source #

Wait for a given NominalDiffTime

This takes care of the conversion to microseconds to pass to threadDelay for you.

waitNominalDiffTime ndt = liftIO $ threadDelay $ round (toRational ndt * (1000 * 1000))