| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Plan.Core
Description
Prefer using the main module. If you manipulate the internals of Plan
to add fake steps, bad things might happen.
- data Plan s w m i o = Plan (Steps s w) (Star (Stream (Of Tick') m) i o)
- data Steps s w = Steps !(Seq (w, s, Mandatoriness, Steps s w)) w
- data Mandatoriness
- foldSteps :: ([(w, s, Mandatoriness, r)] -> w -> r) -> Steps s w -> r
- foldSteps' :: (Seq (w, s, Mandatoriness, r) -> w -> r) -> Steps s w -> r
- bimapSteps :: (s -> s') -> (w -> w') -> Plan s w m i o -> Plan s' w' m i o
- zoomSteps :: Monoid w' => ((w -> Identity w) -> w' -> Identity w') -> Plan s w m i o -> Plan s w' m i o
- hoistPlan :: Monad m => (forall x. m x -> n x) -> Plan s w m i o -> Plan s w n i o
- data Tick'
- getSteps :: Plan s w m i o -> Steps s w
- mandatoriness :: Steps s w -> Steps (Mandatoriness, s) w
- step :: (Monoid w, Monad m) => s -> Plan s w m i o -> Plan s w m i o
- skippable :: (Monoid w, Monad m) => s -> Plan s w m i o -> Plan s w m (Maybe i) ()
- foretell :: Monad m => w -> Plan s w m i ()
- plan :: (Monoid w, Monad m) => m o -> Plan s w m i o
- planIO :: (Monoid w, MonadIO m) => IO o -> Plan s w m i o
- kplan :: (Monoid w, Monad m) => (i -> m o) -> Plan s w m i o
- kplanIO :: (Monoid w, MonadIO m) => (i -> IO o) -> Plan s w m i o
- zipSteps' :: Forest a -> Steps r w -> Maybe (Steps (a, r) w)
- zipSteps :: Forest s' -> Plan s w m i o -> Maybe (Plan (s', s) w m i o)
- completedness :: Tick s t -> Tick (Maybe (Either t (t, Maybe t)), s) t
- contextCompletedness :: (t -> Either t (t, Maybe t)) -> Context s t -> Context (Maybe (Either t (t, Maybe t)), s) t
- adapt :: Timeline (Either t (t, t), s) t -> Timeline (Maybe (Either t (t, Maybe t)), s) t
- progressCompletedness :: t -> Progress s t -> (Progress (Maybe (Either t (t, Maybe t)), s) t, Maybe (Either t (t, Maybe t)))
- unliftPlan :: Monad m => Plan s w m () o -> m o
- unliftKPlan :: Monad m => Plan s w m i o -> i -> m o
- data Timeline s t = Timeline !(Seq (t, s, Either (Forest s) (Timeline s t))) t
- instants :: Timeline s t -> Timeline (Either t (t, t), s) t
- foldTimeline :: ([(t, s, Either (Forest s) r)] -> t -> r) -> Timeline s t -> r
- foldTimeline' :: (Seq (t, c, Either (Forest c) r) -> t -> r) -> Timeline c t -> r
- data Context s t = Context {}
- data Tick s t = Tick (NonEmpty (Context s t)) (Progress s t)
- data Progress s t
- onTick :: Monad m => (tick -> m ()) -> Stream (Of tick) m r -> m r
- runPlan :: Monad m => m t -> Plan s w m () o -> Stream (Of (Tick s t)) m (Timeline s t, o)
- runKPlan :: Monad m => m t -> Plan s w m i o -> i -> Stream (Of (Tick s t)) m (Timeline s t, o)
- data RunState s t = RunState !(Seq (t, s, Either (Forest s) (Timeline s t))) !(Forest s) ![Context s t]
- class Bitraversable l => Sylvan l where
Documentation
A computation that takes inputs of type i and produces outputs of type
o working in the underlying monad m. The Applicative instance cares
only about the outputs, the Arrow instance cares about both inputs and
outputs.
Parts of the computation can be labeled as steps with tags of type s.
Computations can have monoidal resource annotations of type w.
The structure of steps and the monoidal annotations can be inspected before
executing the Plan.
A Forest of steps tags of type s interspersed with monoidal
annotations of type w.
Constructors
| Steps !(Seq (w, s, Mandatoriness, Steps s w)) w |
Instances
| Bifunctor Steps Source # | |
| Bitraversable Steps Source # | |
| Bifoldable Steps Source # |
|
| Sylvan Steps Source # |
|
| Functor (Steps s) Source # | |
| Foldable (Steps s) Source # | |
| Traversable (Steps s) Source # | |
| (Eq s, Eq w) => Eq (Steps s w) Source # | |
| (Show s, Show w) => Show (Steps s w) Source # | |
| Monoid w => Monoid (Steps s w) Source # | |
data Mandatoriness Source #
Steps of Plans constructed in Applicative fashion are always
Mandatory. Only steps declared with skippable are optional.
Instances
Arguments
| :: ([(w, s, Mandatoriness, r)] -> w -> r) | A function that consumes a list of step tags of type |
| -> Steps s w | |
| -> r |
foldSteps' :: (Seq (w, s, Mandatoriness, r) -> w -> r) -> Steps s w -> r Source #
bimapSteps :: (s -> s') -> (w -> w') -> Plan s w m i o -> Plan s' w' m i o Source #
Adapt the Step value inside a Plan without extracting it.
zoomSteps :: Monoid w' => ((w -> Identity w) -> w' -> Identity w') -> Plan s w m i o -> Plan s w' m i o Source #
Use a lens setter to "zoom" the monoidal annotations of a Plan into a
wider monoidal context.
hoistPlan :: Monad m => (forall x. m x -> n x) -> Plan s w m i o -> Plan s w n i o Source #
Change the underlying monad of a Plan.
mandatoriness :: Steps s w -> Steps (Mandatoriness, s) w Source #
Decorate each step tag with its mandatoriness. Useful in combination with toForest.
step :: (Monoid w, Monad m) => s -> Plan s w m i o -> Plan s w m i o Source #
Declare a step by wrapping an existing plan (which may contain substeps).
skippable :: (Monoid w, Monad m) => s -> Plan s w m i o -> Plan s w m (Maybe i) () Source #
Declare an optional step by wrapping an existing arrow plan. The step will
only be executed when the input is Just.
This function only makes sense when using the Arrow instance of Plan,
because for Applicatives an effect cannot depend on previously obtained
values.
plan :: (Monoid w, Monad m) => m o -> Plan s w m i o Source #
Lift a monadic action to a Plan. The input type remains polymorphic.
kplan :: (Monoid w, Monad m) => (i -> m o) -> Plan s w m i o Source #
Lift a Kleisli arrow to a Plan.
zipSteps :: Forest s' -> Plan s w m i o -> Maybe (Plan (s', s) w m i o) Source #
Pair each step tag s inside a Plan with the corresponding element of the Forest.
If the forest doesn't have the same structure as the steps, the function
fails with Nothing.
This function can be useful to annotate each step tag with some information,
for example the time duration of the step in a previous execution of the
plan. See Timeline, instants, and toForest.
completedness :: Tick s t -> Tick (Maybe (Either t (t, Maybe t)), s) t Source #
A given step might not have been reached yet. It it has been reached, either it has been skipped at a certain time, or started at a certain time. If if has been started, maybe it has already finished, too.
This function can be used in combination with toForest and
drawForest to render the state of each step for a Tick.
contextCompletedness :: (t -> Either t (t, Maybe t)) -> Context s t -> Context (Maybe (Either t (t, Maybe t)), s) t Source #
progressCompletedness :: t -> Progress s t -> (Progress (Maybe (Either t (t, Maybe t)), s) t, Maybe (Either t (t, Maybe t))) Source #
unliftPlan :: Monad m => Plan s w m () o -> m o Source #
Forget that there is a plan, get the underlying monadic action.
unliftKPlan :: Monad m => Plan s w m i o -> i -> m o Source #
Forget that there is a plan, get the underlying Kleisli arrow.
A Forest of steps tags of type s interspersed with
measurements of type t.
Instances
| Bifunctor Timeline Source # | |
| Bitraversable Timeline Source # | |
| Bifoldable Timeline Source # | |
| Sylvan Timeline Source # |
|
| Functor (Timeline s) Source # | |
| Foldable (Timeline s) Source # | |
| Traversable (Timeline s) Source # | |
| Comonad (Timeline s) Source # |
|
| (Eq s, Eq t) => Eq (Timeline s t) Source # | |
| (Show s, Show t) => Show (Timeline s t) Source # | |
instants :: Timeline s t -> Timeline (Either t (t, t), s) t Source #
Decorate each step tag with either the time the step was skipped, or the
time it was started and finished. Useful in combination with toForest.
Arguments
| :: ([(t, s, Either (Forest s) r)] -> t -> r) | A function that consumes a list of step tags of type |
| -> Timeline s t | |
| -> r |
The execution of a Plan can make progress by skipping a step, starting a
step, or finishing a step.
Constructors
| Skipped (Forest s) | Provides the substeps that were skipped. |
| Started (Forest s) | Provides the substeps that will be executed next. |
| Finished (Timeline s t) | Provides a |
Instances
| Bifunctor Progress Source # | |
| Bitraversable Progress Source # | |
| Bifoldable Progress Source # | |
| Sylvan Progress Source # | |
| Functor (Progress s) Source # | |
| Foldable (Progress s) Source # | |
| Traversable (Progress s) Source # | |
| (Eq t, Eq s) => Eq (Progress s t) Source # | |
| (Show t, Show s) => Show (Progress s t) Source # | |
onTick :: Monad m => (tick -> m ()) -> Stream (Of tick) m r -> m r Source #
Specify a monadic callback for processing each Tick update.
Arguments
| :: Monad m | |
| => m t | Monadic measurement to be taken on each tick. |
| -> Plan s w m () o | Plan without input. |
| -> Stream (Of (Tick s t)) m (Timeline s t, o) |
Runs a plan that doesn't need input. It returns a Stream of Tick
updates that are emitted every time the execution advances through the
Steps.
For each Tick update, a monadic measurement of type t is taken. Usually
the measurement consists in getting the current time.
When the execution finishes, a Timeline with the measurements for each
Tick is returned, along with the result value.
Even if the plan didn't have any steps, the Timeline will contain a
measurement taken when the computation finished.
class Bitraversable l => Sylvan l where Source #
Instances of Sylvan are Forests with nodes of type n,
interspersed with annotations of type a, and perhaps some other extra
information.
They must satisfy
bifoldMap f (\_ -> mempty) s == foldMap (foldMap f) (toForest s)
Minimal complete definition
Methods
toForest :: l n a -> Forest n Source #
Forget about the annotations and return the underlying Forest.