schedule-0.2.0.0: Pure deterministic scheduled computations

Safe HaskellNone
LanguageHaskell2010

Data.Schedule.Internal

Synopsis

Documentation

newtype Task t Source #

A task that is currently or was part of a schedule.

t is the type of input parameter for each task, i.e. the task contents.

Constructors

Task (Delete Tick t) 
Instances
Eq (Task t) Source # 
Instance details

Defined in Data.Schedule.Internal

Methods

(==) :: Task t -> Task t -> Bool #

(/=) :: Task t -> Task t -> Bool #

Ord (Task t) Source # 
Instance details

Defined in Data.Schedule.Internal

Methods

compare :: Task t -> Task t -> Ordering #

(<) :: Task t -> Task t -> Bool #

(<=) :: Task t -> Task t -> Bool #

(>) :: Task t -> Task t -> Bool #

(>=) :: Task t -> Task t -> Bool #

max :: Task t -> Task t -> Task t #

min :: Task t -> Task t -> Task t #

Read (Task t) Source # 
Instance details

Defined in Data.Schedule.Internal

Show (Task t) Source # 
Instance details

Defined in Data.Schedule.Internal

Methods

showsPrec :: Int -> Task t -> ShowS #

show :: Task t -> String #

showList :: [Task t] -> ShowS #

Generic (Task t) Source # 
Instance details

Defined in Data.Schedule.Internal

Associated Types

type Rep (Task t) :: Type -> Type #

Methods

from :: Task t -> Rep (Task t) x #

to :: Rep (Task t) x -> Task t #

type Rep (Task t) Source # 
Instance details

Defined in Data.Schedule.Internal

type Rep (Task t) = D1 (MetaData "Task" "Data.Schedule.Internal" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" True) (C1 (MetaCons "Task" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Delete Tick t))))

data TaskStatus t Source #

The current status of a task as returned by taskStatus.

Constructors

TaskNotPending

The task is not pending - either it was already run, or cancelled.

TaskPending !Tick !t

The task is due to run at some future tick.

TaskRunning !t

The task is running right now.

Instances
Eq t => Eq (TaskStatus t) Source # 
Instance details

Defined in Data.Schedule.Internal

Methods

(==) :: TaskStatus t -> TaskStatus t -> Bool #

(/=) :: TaskStatus t -> TaskStatus t -> Bool #

Ord t => Ord (TaskStatus t) Source # 
Instance details

Defined in Data.Schedule.Internal

Read t => Read (TaskStatus t) Source # 
Instance details

Defined in Data.Schedule.Internal

Show t => Show (TaskStatus t) Source # 
Instance details

Defined in Data.Schedule.Internal

Generic (TaskStatus t) Source # 
Instance details

Defined in Data.Schedule.Internal

Associated Types

type Rep (TaskStatus t) :: Type -> Type #

Methods

from :: TaskStatus t -> Rep (TaskStatus t) x #

to :: Rep (TaskStatus t) x -> TaskStatus t #

type Rep (TaskStatus t) Source # 
Instance details

Defined in Data.Schedule.Internal

type Rep (TaskStatus t) = D1 (MetaData "TaskStatus" "Data.Schedule.Internal" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "TaskNotPending" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TaskPending" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Tick) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) :+: C1 (MetaCons "TaskRunning" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t))))

data Schedule t Source #

The state of all scheduled pending tasks.

t is the type of task-params.

Constructors

Schedule 

Fields

Instances
Eq t => Eq (Schedule t) Source # 
Instance details

Defined in Data.Schedule.Internal

Methods

(==) :: Schedule t -> Schedule t -> Bool #

(/=) :: Schedule t -> Schedule t -> Bool #

Read t => Read (Schedule t) Source # 
Instance details

Defined in Data.Schedule.Internal

Show t => Show (Schedule t) Source # 
Instance details

Defined in Data.Schedule.Internal

Methods

showsPrec :: Int -> Schedule t -> ShowS #

show :: Schedule t -> String #

showList :: [Schedule t] -> ShowS #

Generic (Schedule t) Source # 
Instance details

Defined in Data.Schedule.Internal

Associated Types

type Rep (Schedule t) :: Type -> Type #

Methods

from :: Schedule t -> Rep (Schedule t) x #

to :: Rep (Schedule t) x -> Schedule t #

type Rep (Schedule t) Source # 
Instance details

Defined in Data.Schedule.Internal

type Rep (Schedule t) = D1 (MetaData "Schedule" "Data.Schedule.Internal" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "Schedule" PrefixI True) ((S1 (MetaSel (Just "now") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Tick) :*: S1 (MetaSel (Just "tasks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RMMap Tick t))) :*: (S1 (MetaSel (Just "pending") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set (Task t))) :*: S1 (MetaSel (Just "running") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Task t, t))))))

checkValidity :: Schedule t -> Maybe Text Source #

Check the schedule that its internal invariants all hold.

You must run this on every instance obtained not via the API functions here. For example, you must run this on instances obtained via deserialisation, which in general cannot check the complex invariants maintained by the API functions. Also, for all Tasks you obtain via a similarly non-standard method, including by deserialisation of a parent data structure, you must run checkTask schedule task.

Nothing means the check passed; Just errmsg gives a failure reason.

Note: this does not guard against all malicious behaviour, but it does guard against violation (either malicious or accidental) of the runtime invariants assumed by this data structure.

checkTask :: Schedule t -> Task t -> Bool Source #

Check that an existing task is consistent with the current state of the structure, i.e. it is not a task that could be generated in the future.

tickNow :: Schedule t -> Tick Source #

Get the current tick, whose tasks have not all run yet.

From the perspective of the pure computation that is running this schedule, you should treat this as the current "logical time", even if an impure clock is telling you that the "environment time" is in the future.

tickPrev :: Schedule t -> Tick Source #

Get the previous tick, whose tasks have all already run.

ticksToIdle :: Schedule t -> Maybe TickDelta Source #

Get the number of ticks until the next scheduled task.

This may be used by an impure runtime environment to set an actual timeout; see Control.Clock for a starting point.

after :: TickDelta -> t -> Schedule t -> (Task t, Schedule t) Source #

Schedule a task to run after a given number of ticks.

This is relative to tickNow; a 0 delta schedules the task to be run at the end of the current tick, i.e. as soon as possible but not immediately.

If your task params needs to refer to the task itself, you may achieve this by using the standard Haskell "tying the knot" technique, e.g.:

>>> data TPar = TPar !(Task TPar) deriving (Show, Eq)
>>> s = newSchedule
>>> let (t, s') = after 1 (TPar t) s -- @t@ on LHS & RHS, tying the knot
>>> t
Task (Delete 1 (RHandle {getHandle = 0}))
>>> taskStatus t s
TaskNotPending
>>> taskStatus t s'
TaskPending 1 (TPar (Task (Delete 1 (RHandle {getHandle = 0}))))
>>> taskStatus t s' == TaskPending 1 (TPar t)
True

cancel :: Task t -> Schedule t -> (Maybe t, Schedule t) Source #

Cancel a task. Result is Nothing if task was not already pending.

cancel_ :: Task t -> Schedule t -> ((), Schedule t) Source #

Cancel a task, discarding the result.

renew :: TickDelta -> Task t -> Schedule t -> (Maybe (Task t), Schedule t) Source #

Reschedule a pending task to instead run after a given number of ticks.

If the task was not already pending, do nothing. If you need to reschedule a task unconditionally even if it was already cancelled or run, use both cancel_ and after in combination.

popOrTick :: HasCallStack => Schedule t -> (Maybe (Task t, t), Schedule t) Source #

Pop the next task to be run in this tick. If there are no more tasks remaining, then advance to the next tick.

acquireTask :: HasCallStack => (Task t, t) -> Schedule t -> Schedule t Source #

Lock the schedule before running a particular task.

This prevents popOrTick from being called, or other tasks from running. It is not re-entrant; only one task is supposed to run at once.

releaseTask :: HasCallStack => Task t -> Schedule t -> Schedule t Source #

Unlock the schedule after running a particular task.

This allows popOrTick to be called again and other tasks to run. It is not re-entrant; only one task is supposed to run at once.