| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Plan
Contents
Description
This module exports the Plan Applicative.
>>>:{let example :: Plan String [Int] IO () () example = step "a" (step "b" (foretell [1] *> plan (threadDelay 1e6)) *> step "c" (foretell [2] *> plan (threadDelay 1e6))) *> step "d" (step "e" (foretell [3] *> plan (threadDelay 1e6)) *> step "f" (foretell [4] *> plan (threadDelay 1e6))) in bifoldMap id (foldMap Prelude.show) (getSteps example) :} "ab1c2de3f4"
Some possible use cases:
- Inspect the steps of an existing
PlanfromghciusinggetSteps,toForestanddrawForest, as a form of documentation. - If your script requires files that must be already present in the file
system, use
foretellto annotate eachPlanaction that requires a file, then get the global list of files usinggetStepsandfoldMap, and check that they all exist before running thePlanwithrunPlan. - Get progress updates for your script by declaring (possibly nested) steps
with
step, running thePlanwithrunPlan, and providing a notification callback withonTick, probably usingcompletedness,toForestanddrawForestto render the updates. - Run a
PlanwithrunPlan, useinstantsantoForeston the resultingTimelineto get the durations of each step, then usezipStepson the samePlanand run it again. Now whenever a step finishes we can know if it took more or less than in the previous execution.
Synopsis
- data Plan s w m i o
- plan :: (Semigroup w, Monoid w, Monad m) => m o -> Plan s w m i o
- plan' :: (Semigroup w, Monoid w, Monad m) => (i -> m o) -> Plan s w m i o
- planIO :: (Semigroup w, Monoid w, MonadIO m) => IO o -> Plan s w m i o
- planIO' :: (Semigroup w, Monoid w, MonadIO m) => (i -> IO o) -> Plan s w m i o
- 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 ()
- getSteps :: Plan s w m i o -> Steps s w
- data Steps s w
- mandatoriness :: Steps s w -> Steps (Mandatoriness, s) w
- data Mandatoriness
- foldSteps :: ([(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
- zipSteps :: Forest s' -> Plan s w m i o -> Maybe (Plan (s', 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
- unliftPlan :: Monad m => Plan s w m () o -> m o
- unliftPlan' :: Monad m => Plan s w m i o -> i -> m o
- runPlan :: Monad m => m t -> Plan s w m () o -> Stream (Of (Tick s t)) m (Timeline s t, o)
- runPlan' :: Monad m => m t -> Plan s w m i o -> i -> Stream (Of (Tick s t)) m (Timeline s t, o)
- onTick :: Monad m => (tick -> m ()) -> Stream (Of tick) m r -> m r
- data Tick s t = Tick (NonEmpty (Context s t)) (Progress s t)
- completedness :: Tick s t -> Tick (Maybe (Either t (t, Maybe t)), s) t
- data Context s t = Context {}
- data Progress s t
- data Timeline s 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
- class Bitraversable l => Sylvan l where
- bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d
- bifoldMap :: (Bifoldable p, Monoid m) => (a -> m) -> (b -> m) -> p a b -> m
- bitraverse :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- extract :: Comonad w => w a -> a
- hoist :: (MFunctor t, Monad m) => (forall a. m a -> n a) -> t m b -> t n b
- effects :: Monad m => Stream (Of a) m r -> m r
- kplan :: (Semigroup w, Monoid w, Monad m) => (i -> m o) -> Plan s w m i o
- kplanIO :: (Semigroup w, Monoid w, MonadIO m) => (i -> IO o) -> Plan s w m i o
- unliftKPlan :: Monad m => Plan s w m i o -> i -> m o
- runKPlan :: Monad m => m t -> Plan s w m i o -> i -> Stream (Of (Tick s t)) m (Timeline s t, o)
Constructing plans
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.
Instances
| (Semigroup w, Monoid w, Monad m) => Category (Plan s w m :: * -> * -> *) Source # | |
| (Semigroup w, Monoid w, Monad m) => Arrow (Plan s w m) Source # | |
Defined in Control.Plan.Core | |
| (Semigroup w, Monoid w, Monad m) => Profunctor (Plan s w m) Source # | |
Defined in Control.Plan.Core Methods dimap :: (a -> b) -> (c -> d) -> Plan s w m b c -> Plan s w m a d # lmap :: (a -> b) -> Plan s w m b c -> Plan s w m a c # rmap :: (b -> c) -> Plan s w m a b -> Plan s w m a c # (#.) :: Coercible c b => q b c -> Plan s w m a b -> Plan s w m a c # (.#) :: Coercible b a => Plan s w m b c -> q a b -> Plan s w m a c # | |
| Monad m => Functor (Plan s w m i) Source # | |
| (Semigroup w, Monoid w, Monad m) => Applicative (Plan s w m i) Source # | |
Defined in Control.Plan.Core | |
plan :: (Semigroup w, Monoid w, Monad m) => m o -> Plan s w m i o Source #
Lift a monadic action to a Plan. The input type i remains polymorphic, usually it will become ().
plan' :: (Semigroup w, Monoid w, Monad m) => (i -> m o) -> Plan s w m i o Source #
Lift a Kleisli arrow to a Plan.
Declaring steps and annotations
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.
>>>:{let example :: Plan String () IO () () example = proc () -> do i <- step "reading" (plan (readMaybe @Int <$> getLine)) -< () skippable "writing" (plan' print) -< i in putStr . drawForest . fmap (fmap show) . toForest . mandatoriness . getSteps $ example :} (Mandatory,"reading") (Skippable,"writing")
Analyzing plans
A Forest of steps tags of type s interspersed with monoidal
annotations of type w.
Instances
| Bitraversable Steps Source # | |
Defined in Control.Plan.Core Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Steps a b -> f (Steps c d) # | |
| Bifoldable Steps Source # |
|
| Bifunctor Steps Source # | |
| Sylvan Steps Source # |
|
| Functor (Steps s) Source # | |
| Foldable (Steps s) Source # | |
Defined in Control.Plan.Core Methods fold :: Monoid m => Steps s m -> m # foldMap :: Monoid m => (a -> m) -> Steps s a -> m # foldr :: (a -> b -> b) -> b -> Steps s a -> b # foldr' :: (a -> b -> b) -> b -> Steps s a -> b # foldl :: (b -> a -> b) -> b -> Steps s a -> b # foldl' :: (b -> a -> b) -> b -> Steps s a -> b # foldr1 :: (a -> a -> a) -> Steps s a -> a # foldl1 :: (a -> a -> a) -> Steps s a -> a # elem :: Eq a => a -> Steps s a -> Bool # maximum :: Ord a => Steps s a -> a # minimum :: Ord a => Steps s a -> a # | |
| Traversable (Steps s) Source # | |
| (Eq w, Eq s) => Eq (Steps s w) Source # | |
| (Show w, Show s) => Show (Steps s w) Source # | |
| Semigroup w => Semigroup (Steps s w) Source # | |
| (Semigroup w, Monoid w) => Monoid (Steps s w) Source # | |
mandatoriness :: Steps s w -> Steps (Mandatoriness, s) w Source #
Decorate each step tag with its mandatoriness. Useful in combination with toForest.
data Mandatoriness Source #
Instances
| Eq Mandatoriness Source # | |
Defined in Control.Plan.Core Methods (==) :: Mandatoriness -> Mandatoriness -> Bool # (/=) :: Mandatoriness -> Mandatoriness -> Bool # | |
| Ord Mandatoriness Source # | |
Defined in Control.Plan.Core Methods compare :: Mandatoriness -> Mandatoriness -> Ordering # (<) :: Mandatoriness -> Mandatoriness -> Bool # (<=) :: Mandatoriness -> Mandatoriness -> Bool # (>) :: Mandatoriness -> Mandatoriness -> Bool # (>=) :: Mandatoriness -> Mandatoriness -> Bool # max :: Mandatoriness -> Mandatoriness -> Mandatoriness # min :: Mandatoriness -> Mandatoriness -> Mandatoriness # | |
| Show Mandatoriness Source # | |
Defined in Control.Plan.Core Methods showsPrec :: Int -> Mandatoriness -> ShowS # show :: Mandatoriness -> String # showList :: [Mandatoriness] -> ShowS # | |
Arguments
| :: ([(w, s, Mandatoriness, r)] -> w -> r) | A function that consumes a list of step tags of type |
| -> Steps s w | |
| -> r |
Adapting plans
Sometimes, we might need to mix Plans for which step tags and annotations
are of different types. These functions help with that.
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.
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.
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.
Running plans
unliftPlan :: Monad m => Plan s w m () o -> m o Source #
Forget that there is a plan, get the underlying monadic action.
unliftPlan' :: Monad m => Plan s w m i o -> i -> m o Source #
Forget that there is a plan, get the underlying Kleisli arrow.
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.
onTick :: Monad m => (tick -> m ()) -> Stream (Of tick) m r -> m r Source #
Specify a monadic callback for processing each Tick update.
Represents some kind of progress through the Steps of a Plan while the
plan executes.
The ascending list of contexts provides the current position of the execution along the hierarchy of steps.
If the plan only has a linear sequence of steps, the list will have only one
Context.
Instances
| Bitraversable Tick Source # | |
Defined in Control.Plan.Core Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tick a b -> f (Tick c d) # | |
| Bifoldable Tick Source # | |
| Bifunctor Tick Source # | |
| Sylvan Tick Source # | |
| Functor (Tick s) Source # | |
| Foldable (Tick s) Source # | |
Defined in Control.Plan.Core Methods fold :: Monoid m => Tick s m -> m # foldMap :: Monoid m => (a -> m) -> Tick s a -> m # foldr :: (a -> b -> b) -> b -> Tick s a -> b # foldr' :: (a -> b -> b) -> b -> Tick s a -> b # foldl :: (b -> a -> b) -> b -> Tick s a -> b # foldl' :: (b -> a -> b) -> b -> Tick s a -> b # foldr1 :: (a -> a -> a) -> Tick s a -> a # foldl1 :: (a -> a -> a) -> Tick s a -> a # elem :: Eq a => a -> Tick s a -> Bool # maximum :: Ord a => Tick s a -> a # minimum :: Ord a => Tick s a -> a # | |
| Traversable (Tick s) Source # | |
| (Eq t, Eq s) => Eq (Tick s t) Source # | |
| (Show t, Show s) => Show (Tick s t) Source # | |
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.
Represents how far we are along a sequence of sibling steps.
For the already completed steps, a Timeline of measurements is provided. extract for the Timeline returns the starting measurement of the current step.
Instances
| Bifunctor Context Source # | |
| Functor (Context s) Source # | |
| Foldable (Context s) Source # | |
Defined in Control.Plan.Core Methods fold :: Monoid m => Context s m -> m # foldMap :: Monoid m => (a -> m) -> Context s a -> m # foldr :: (a -> b -> b) -> b -> Context s a -> b # foldr' :: (a -> b -> b) -> b -> Context s a -> b # foldl :: (b -> a -> b) -> b -> Context s a -> b # foldl' :: (b -> a -> b) -> b -> Context s a -> b # foldr1 :: (a -> a -> a) -> Context s a -> a # foldl1 :: (a -> a -> a) -> Context s a -> a # toList :: Context s a -> [a] # length :: Context s a -> Int # elem :: Eq a => a -> Context s a -> Bool # maximum :: Ord a => Context s a -> a # minimum :: Ord a => Context s a -> a # | |
| Traversable (Context s) Source # | |
Defined in Control.Plan.Core | |
| (Eq t, Eq s) => Eq (Context s t) Source # | |
| (Show t, Show s) => Show (Context s t) Source # | |
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
| Bitraversable Progress Source # | |
Defined in Control.Plan.Core Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Progress a b -> f (Progress c d) # | |
| Bifoldable Progress Source # | |
| Bifunctor Progress Source # | |
| Sylvan Progress Source # | |
| Functor (Progress s) Source # | |
| Foldable (Progress s) Source # | |
Defined in Control.Plan.Core Methods fold :: Monoid m => Progress s m -> m # foldMap :: Monoid m => (a -> m) -> Progress s a -> m # foldr :: (a -> b -> b) -> b -> Progress s a -> b # foldr' :: (a -> b -> b) -> b -> Progress s a -> b # foldl :: (b -> a -> b) -> b -> Progress s a -> b # foldl' :: (b -> a -> b) -> b -> Progress s a -> b # foldr1 :: (a -> a -> a) -> Progress s a -> a # foldl1 :: (a -> a -> a) -> Progress s a -> a # toList :: Progress s a -> [a] # null :: Progress s a -> Bool # length :: Progress s a -> Int # elem :: Eq a => a -> Progress s a -> Bool # maximum :: Ord a => Progress s a -> a # minimum :: Ord a => Progress s a -> a # | |
| Traversable (Progress s) Source # | |
Defined in Control.Plan.Core | |
| (Eq s, Eq t) => Eq (Progress s t) Source # | |
| (Show s, Show t) => Show (Progress s t) Source # | |
A Forest of steps tags of type s interspersed with
measurements of type t.
Instances
| Bitraversable Timeline Source # | |
Defined in Control.Plan.Core Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Timeline a b -> f (Timeline c d) # | |
| Bifoldable Timeline Source # | |
| Bifunctor Timeline Source # | |
| Sylvan Timeline Source # |
|
| Functor (Timeline s) Source # | |
| Foldable (Timeline s) Source # | |
Defined in Control.Plan.Core Methods fold :: Monoid m => Timeline s m -> m # foldMap :: Monoid m => (a -> m) -> Timeline s a -> m # foldr :: (a -> b -> b) -> b -> Timeline s a -> b # foldr' :: (a -> b -> b) -> b -> Timeline s a -> b # foldl :: (b -> a -> b) -> b -> Timeline s a -> b # foldl' :: (b -> a -> b) -> b -> Timeline s a -> b # foldr1 :: (a -> a -> a) -> Timeline s a -> a # foldl1 :: (a -> a -> a) -> Timeline s a -> a # toList :: Timeline s a -> [a] # null :: Timeline s a -> Bool # length :: Timeline s a -> Int # elem :: Eq a => a -> Timeline s a -> Bool # maximum :: Ord a => Timeline s a -> a # minimum :: Ord a => Timeline s a -> a # | |
| Traversable (Timeline s) Source # | |
Defined in Control.Plan.Core | |
| Comonad (Timeline s) Source # |
|
| (Eq t, Eq s) => Eq (Timeline s t) Source # | |
| (Show t, Show s) => 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 Sylvan typeclass
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.
Instances
| Sylvan Progress Source # | |
| Sylvan Tick Source # | |
| Sylvan Timeline Source # |
|
| Sylvan Steps Source # |
|
| Sylvan (Clown (Compose [] Tree) :: * -> * -> *) Source # | |
Re-exports
bifoldMap :: (Bifoldable p, Monoid m) => (a -> m) -> (b -> m) -> p a b -> m #
bitraverse :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) #
Evaluates the relevant functions at each element in the structure, running the action, and builds a new structure with the same shape, using the results produced from sequencing the actions.
bitraversef g ≡bisequenceA.bimapf g
For a version that ignores the results, see bitraverse_.
Since: base-4.10.0.0
Besides its usefulness with Timeline, extract lets you get the head of a
NonEmpty or the second element of a tuple.
hoist :: (MFunctor t, Monad m) => (forall a. m a -> n a) -> t m b -> t n b #
Lift a monad morphism from m to n into a monad morphism from
(t m) to (t n)
The first argument to hoist must be a monad morphism, even though the
type system does not enforce this
effects :: Monad m => Stream (Of a) m r -> m r #
Reduce a stream, performing its actions but ignoring its elements.
>>>rest <- S.effects $ S.splitAt 2 $ each [1..5]>>>S.print rest3 4 5
effects should be understood together with copy and is subject to the rules
S.effects . S.copy = id hoist S.effects . S.copy = id
The similar effects and copy operations in Data.ByteString.Streaming obey the same rules.
effects lets you ignore all the update notifications while running a plan,
when you are only interested in the final Timeline and the result.
Deprecated functions
kplan :: (Semigroup w, Monoid w, Monad m) => (i -> m o) -> Plan s w m i o Source #
Deprecated: Use plan' instead.
kplanIO :: (Semigroup w, Monoid w, MonadIO m) => (i -> IO o) -> Plan s w m i o Source #
Deprecated: Use planIO' instead.
unliftKPlan :: Monad m => Plan s w m i o -> i -> m o Source #
Deprecated: Use unliftPlan' instead.