package yocaml

  1. Overview
  2. Docs

Module Yocaml.TaskSource

Task is the main abstraction used to describe an action (a task that produces an effect) associated with dependencies and a DSL for composing tasks together.

Types

Sourcetype (-'a, 'b) t

A task is a particular type of function, which produces an effect, associated with a set of dependencies. That's why it's a type parameterised by an input and an output.

Building tasks

Sourceval make : ?has_dynamic_dependencies:bool -> Deps.t -> ('a -> 'b Eff.t) -> ('a, 'b) t

make deps eff Builds a task with a fixed set of dependencies and an action.

Sourceval from_effect : ?has_dynamic_dependencies:bool -> ('a -> 'b Eff.t) -> ('a, 'b) t

from_effect is make Deps.empty.

Sourceval lift : ?has_dynamic_dependencies:bool -> ('a -> 'b) -> ('a, 'b) t

lift f lift the function f into a task with an empty set of dependencies. Useful for transforming regular functions into tasks.

Sourceval id : ('a, 'a) t

Task is in fact a Strong Profonctor, and therefore an Arrow, hence the presence of an identity morphism, associated with an empty dependency set.

Composing tasks

Building a construction pipeline involves composing tasks and merging their set of dependencies.

Sourceval compose : ('b, 'c) t -> ('a, 'b) t -> ('a, 'c) t

compose t2 t1 merges dependencies from t1 and t2 and produce a new action that sequentially performs t1 following by t2.

Sourceval rcompose : ('a, 'b) t -> ('b, 'c) t -> ('a, 'c) t

rcompose t1 t2 merges dependencies from t1 and t2 and produce a new action that sequentially performs t1 following by t2.

Sourceval pre_compose : ('b -> 'c) -> ('a, 'b) t -> ('a, 'c) t

pre_compose f t is compose (lift f) t. It allows to composition between Task and regular function.

Sourceval post_compose : ('b, 'c) t -> ('a -> 'b) -> ('a, 'c) t

post_compose t f is compose t (lift f). It allows to composition between Task and regular function.

Sourceval pre_rcompose : ('a -> 'b) -> ('b, 'c) t -> ('a, 'c) t

pre_recompose f t is rcompose (lift f) t It allows to composition between Task and regular function.

Sourceval post_rcompose : ('a, 'b) t -> ('b -> 'c) -> ('a, 'c) t

post_recompose t f is rcompose t (lift f) It allows to composition between Task and regular function.

Profunctors operation

Since in t, 'a is contravariant and 'b is covariant, we can imagine its profunctorial nature.

Sourceval dimap : ('a -> 'b) -> ('c -> 'd) -> ('b, 'c) t -> ('a, 'd) t

dimap f g t contramap f on t and map g on t.

Sourceval lmap : ('a -> 'b) -> ('b, 'c) t -> ('a, 'c) t

lmap f t contramap f on t.

Sourceval rmap : ('b -> 'c) -> ('a, 'b) t -> ('a, 'c) t

rmap f t map f on t.

Choice operations

Profunctors with choice, to act on sum-types (using Either to describe generic sums).

Sourceval left : ('a, 'b) t -> (('a, 'c) Either.t, ('b, 'c) Either.t) t

left t expand the arrow to act only on the Left part of the sum.

Sourceval right : ('a, 'b) t -> (('c, 'a) Either.t, ('c, 'b) Either.t) t

right t expand the arrow to act only on the Right part of the sum.

Sourceval choose : ('a, 'b) t -> ('c, 'd) t -> (('a, 'c) Either.t, ('b, 'd) Either.t) t

Split the input between the two argument arrows, re-tagging and merging their outputs.

Sourceval fan_in : ('a, 'c) t -> ('b, 'c) t -> (('a, 'b) Either.t, 'c) t

Split the input between the two argument arrows, merging their outputs.

Strong operations

Profunctors with strength, to act on product-types (using ('a * 'b) to describe generic products).

Sourceval first : ('a, 'b) t -> ('a * 'c, 'b * 'c) t

first t expand the arrow to act only on the first part of the product.

Sourceval second : ('a, 'b) t -> ('c * 'a, 'c * 'b) t

second t expand the arrow to act only on the second part of the product.

Sourceval uncurry : ('a, 'b -> 'c) t -> ('a * 'b, 'c) t

Uncurry an arrow.

Sourceval split : ('a, 'b) t -> ('c, 'd) t -> ('a * 'c, 'b * 'd) t

Split the input between the two argument arrows and combine their output.

Sourceval fan_out : ('a, 'b) t -> ('a, 'c) t -> ('a, 'b * 'c) t

Send the input to both argument arrows and combine their output.

Application operations

Implement function application capabilities using Arrow Apply.

Sourceval apply : (('a, 'b) t * 'a, 'b) t

Application of a task to a given input.

Covariant API

Removing the contravariant component of the profunctor, we have a covariant component that can be treated as a regular Functor. This makes it possible to have linking operators and to make the API potentially less conflicting.

Sourcetype 'a ct = (unit, 'a) t

Just a type alias for reducing signatures verbosity

Sourceval map : ('a -> 'b) -> 'a ct -> 'b ct

Regular mapping on a task. Since t is also a Functor.

Sourceval pure : 'a -> 'a ct

Lift a regular value into a task.

Sourceval ap : ('a -> 'b) ct -> 'a ct -> 'b ct

Regular apply on a task. Since t is also an Applicative.

Sourceval zip : 'a ct -> 'b ct -> ('a * 'b) ct

Monoidal product between two applicatives.

Sourceval replace : 'a -> 'b ct -> 'a ct

replace x e replace the value of e by x.

Sourceval void : 'a ct -> unit ct

void e replace the value of e by unit.

Sourceval select : ('a, 'b) Either.t ct -> ('a -> 'b) ct -> 'b ct

select e f apply f if e is Left. It allow to skip effect using Right.

Sourceval branch : ('a, 'b) Either.t ct -> ('a -> 'c) ct -> ('b -> 'c) ct -> 'c ct

branch x f g if x is Left, it performs f, otherwise it performs g.

Sourceval map2 : ('a -> 'b -> 'c) -> 'a ct -> 'b ct -> 'c ct

Lift a 2-ary function.

Sourceval map3 : ('a -> 'b -> 'c -> 'd) -> 'a ct -> 'b ct -> 'c ct -> 'd ct

Lift a 3-ary function.

Sourceval map4 : ('a -> 'b -> 'c -> 'd -> 'e) -> 'a ct -> 'b ct -> 'c ct -> 'd ct -> 'e ct

Lift a 4-ary function.

Sourceval map5 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f) -> 'a ct -> 'b ct -> 'c ct -> 'd ct -> 'e ct -> 'f ct

Lift a 5-ary function.

Sourceval map6 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f -> 'g) -> 'a ct -> 'b ct -> 'c ct -> 'd ct -> 'e ct -> 'f ct -> 'g ct

Lift a 6-ary function.

Sourceval map7 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f -> 'g -> 'h) -> 'a ct -> 'b ct -> 'c ct -> 'd ct -> 'e ct -> 'f ct -> 'g ct -> 'h ct

Lift a 7-ary function.

Sourceval map8 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f -> 'g -> 'h -> 'i) -> 'a ct -> 'b ct -> 'c ct -> 'd ct -> 'e ct -> 'f ct -> 'g ct -> 'h ct -> 'i ct

Lift a 8-ary function.

Infix operators

Sourcemodule Infix : sig ... end
Sourceval (||>) : 'a -> ('a -> 'b) -> 'b

x ||> f is f x.

Sourceval (<<<) : ('b, 'c) t -> ('a, 'b) t -> ('a, 'c) t

t2 <<< t1 is compose t2 t1.

Sourceval (>>>) : ('a, 'b) t -> ('b, 'c) t -> ('a, 'c) t

t1 >>> t2 is rcompose t1 t2.

Sourceval (<+<) : ('b, 'c * Deps.t) t -> ('a, 'b * Deps.t) t -> ('a, 'c * Deps.t) t

a <+< b compose b and a and concat dynamic dependencies set.

Sourceval (>+>) : ('a, 'b * Deps.t) t -> ('b, 'c * Deps.t) t -> ('a, 'c * Deps.t) t

a >+> b compose a and b and concat dynamic dependencies set.

Sourceval (|<<) : ('b -> 'c) -> ('a, 'b) t -> ('a, 'c) t

f ^<< t1 is pre_compose f t1.

Sourceval (<<|) : ('b, 'c) t -> ('a -> 'b) -> ('a, 'c) t

t1 <<| f is post_compose t1 f.

Sourceval (*<<) : ('b -> 'c Eff.t) -> ('a, 'b) t -> ('a, 'c) t

f *<< t1 is compose (make Deps.empty f) t1.

Sourceval (<<*) : ('b, 'c) t -> ('a -> 'b Eff.t) -> ('a, 'c) t

t1 <<* f is compose t1 (make Deps.empty f).

Sourceval (|>>) : ('a -> 'b) -> ('b, 'c) t -> ('a, 'c) t

f |>> t1 is pre_rcompose f t1.

Sourceval (>>|) : ('a, 'b) t -> ('b -> 'c) -> ('a, 'c) t

t1 >>| f is post_rcompose t1 f.

Sourceval (*>>) : ('a -> 'b Eff.t) -> ('b, 'c) t -> ('a, 'c) t

f *>> t1 is compose (make Deps.empty f) t1.

Sourceval (>>*) : ('a, 'b) t -> ('b -> 'c Eff.t) -> ('a, 'c) t

t1 >>* f is compose t1 (make Deps.empty f).

Sourceval (+++) : ('a, 'b) t -> ('c, 'd) t -> (('a, 'c) Either.t, ('b, 'd) Either.t) t

t1 +++ t2 is choose t1 t2.

Sourceval (|||) : ('a, 'c) t -> ('b, 'c) t -> (('a, 'b) Either.t, 'c) t

t1 ||| t2 is fan_in t1 t2.

Sourceval (***) : ('a, 'b) t -> ('c, 'd) t -> ('a * 'c, 'b * 'd) t

t1 *** t2 is split t1 t2.

Sourceval (&&&) : ('a, 'b) t -> ('a, 'c) t -> ('a, 'b * 'c) t

t1 &&& t2 is fan_out t1 t2.

Sourceval (<$>) : ('a -> 'b) -> 'a ct -> 'b ct

f <$> t is map f t.

Sourceval (<*>) : ('a -> 'b) ct -> 'a ct -> 'b ct

ft <*> t is apply ft t.

Sourceval (<*?) : ('a, 'b) Either.t ct -> ('a -> 'b) ct -> 'b ct

c <*? f is select c f

Binding operators

Sourcemodule Syntax : sig ... end
Sourceval (let+) : 'a ct -> ('a -> 'b) -> 'b ct

let+ x = t in f x is f <$> f.

Sourceval (and+) : 'a ct -> 'b ct -> ('a * 'b) ct

let+ x = t1 and+ y = t2 in f x y is f <$> t1 <*> t2.

Utils

Sourceval has_dynamic_dependencies : (_, _) t -> bool

has_dynamic_dependencies t returns true if task has dynamic dependencies, false otherwise.

Sourceval dependencies_of : (_, _) t -> Deps.t

dependencies_of t returns the dependencies set of a task.

Sourceval action_of : ('a, 'b) t -> 'a -> 'b Eff.t

action_of t returns the effectful function of a task.

Sourceval destruct : ('a, 'b) t -> Deps.t * ('a -> 'b Eff.t) * bool

destruct t returns the triple of a dependencies set and an effectful callback and if the task is associated to dynamic dependencies. destruct is dependencies_of t, action_of t, has_dynamic_dependencies t

Sourceval no_dynamic_deps : ('a, 'b) t -> ('a, 'b * Deps.t) t

no_dynamic_deps makes an arrow static (does not attach it to any dynamic dependency set).

Sourceval drop_first : unit -> ('a * 'b, 'b) t

drop_first t discards the first element returned by a task.

Sourceval drop_second : unit -> ('a * 'b, 'a) t

drop_second t discards the second element returned by a task.

Sourceval empty_body : unit -> ('a, 'a * string) t

An arrow that attach an empty body

Sourceval const : 'a -> ('b, 'a) t

const x is an arrow that discard the previous output to replace-it by k.

Sourceval with_dynamic_dependencies : Path.t list -> ('a, 'a * Deps.t) t

with_dynamic_dependencies dependenices_list allows to add a set of dynamic dependencies to a task. Even the set of dependencies looks static, it is mostly used for attaching dependencies like folders.

Helpers for dealing with static and dynamic dependencies

The API can change considerably when processing tasks with or without dynamic dependencies, so we are exposing two modules to simplify this processing.

Sourcemodule Static : sig ... end

Utilities for dealing with tasks without dynamic dependencies.

Sourcemodule Dynamic : sig ... end

Utilities for dealing with tasks with dynamic dependencies.

OCaml

Innovation. Community. Security.