looper-0.0.0.2

Safe HaskellNone
LanguageHaskell2010

Looper

Synopsis

Documentation

data LooperDef m Source #

A looper definition

Constructors

LooperDef 

Fields

Instances
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

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 LooperFlags Source #

A structure to parse command-line flags for a looper into

Instances
Eq LooperFlags Source # 
Instance details

Defined in Looper

Show LooperFlags Source # 
Instance details

Defined in Looper

Generic LooperFlags Source # 
Instance details

Defined in Looper

Associated Types

type Rep LooperFlags :: Type -> Type #

type Rep LooperFlags Source # 
Instance details

Defined in Looper

type Rep LooperFlags = D1 (MetaData "LooperFlags" "Looper" "looper-0.0.0.2-BjOKUISjKlOE4oO2B9h0mR" False) (C1 (MetaCons "LooperFlags" PrefixI True) (S1 (MetaSel (Just "looperFlagEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "looperFlagPhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "looperFlagPeriod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))

getLooperFlags Source #

Arguments

:: String

The name of the looper (best to make this all-lowercase)

-> Parser LooperFlags 

An optparse applicative parser for LooperFlags

data LooperEnvironment Source #

A structure to parse environment variables for a looper into

Instances
Eq LooperEnvironment Source # 
Instance details

Defined in Looper

Show LooperEnvironment Source # 
Instance details

Defined in Looper

Generic LooperEnvironment Source # 
Instance details

Defined in Looper

Associated Types

type Rep LooperEnvironment :: Type -> Type #

type Rep LooperEnvironment Source # 
Instance details

Defined in Looper

type Rep LooperEnvironment = D1 (MetaData "LooperEnvironment" "Looper" "looper-0.0.0.2-BjOKUISjKlOE4oO2B9h0mR" False) (C1 (MetaCons "LooperEnvironment" PrefixI True) (S1 (MetaSel (Just "looperEnvEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "looperEnvPhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "looperEnvPeriod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))

getLooperEnvironment Source #

Arguments

:: String

Prefix for each variable (best to make this all-caps)

-> String

Name of the looper (best to make this all-caps too)

-> IO LooperEnvironment 

Get a LooperEnvironment from the environment

readLooperEnvironment Source #

Arguments

:: String

Prefix for each variable (best to make this all-caps)

-> String

Name of the looper (best to make this all-caps too)

-> [(String, String)] 
-> LooperEnvironment 

Get a LooperEnvironment from a pure environment

data LooperConfiguration Source #

A structure to configuration for a looper into

Instances
Eq LooperConfiguration Source # 
Instance details

Defined in Looper

Show LooperConfiguration Source # 
Instance details

Defined in Looper

Generic LooperConfiguration Source # 
Instance details

Defined in Looper

Associated Types

type Rep LooperConfiguration :: Type -> Type #

FromJSON LooperConfiguration Source #

You can parse Data.Aeson's JSON or Data.Yaml's YAML to parse a LooperConfiguration. You can also use Data.Yaml.Config.

Instance details

Defined in Looper

type Rep LooperConfiguration Source # 
Instance details

Defined in Looper

type Rep LooperConfiguration = D1 (MetaData "LooperConfiguration" "Looper" "looper-0.0.0.2-BjOKUISjKlOE4oO2B9h0mR" False) (C1 (MetaCons "LooperConfiguration" PrefixI True) (S1 (MetaSel (Just "looperConfEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "looperConfPhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "looperConfPeriod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))

data LooperSettings Source #

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

Instances
Eq LooperSettings Source # 
Instance details

Defined in Looper

Show LooperSettings Source # 
Instance details

Defined in Looper

Generic LooperSettings Source # 
Instance details

Defined in Looper

Associated Types

type Rep LooperSettings :: Type -> Type #

type Rep LooperSettings Source # 
Instance details

Defined in Looper

type Rep LooperSettings = D1 (MetaData "LooperSettings" "Looper" "looper-0.0.0.2-BjOKUISjKlOE4oO2B9h0mR" 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 m 
=> (LooperDef m -> m ())

Custom runner

-> [LooperDef m]

Loopers

-> m () 

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 m 
=> m ()

Overrun handler

-> (LooperDef m -> m ())

Runner

-> [LooperDef m]

Loopers

-> m () 

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.

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))