Library
Module
Module type
Parameter
Class
Class type
Miou is a simple scheduler for OCaml 5 that uses effects. It allows you to launch tasks (functions) concurrently and/or in parallel, as well as offering your application high availability to system events.
Since OCaml 5, it has been possible to use effects. An effect allows you to suspend the execution of a function and fall into a handler which, depending on the effect, would perform a specific operation that would continue the suspended function with the result of the operation.
For example, a Hello: unit Effect.t
effect can suspend using Effect.perform
. A pre-installed handler will then retrieve this effect, perform the operation (say, display "Hello"
), and unsuspend the function with the result of the operation (here, () : unit
).
type _ Effect.t += Hello : unit Effect.t
let handler =
let retc = Fun.id in
let exnc = raise in
let effc
: type c. c Effect.t -> ((c, 'a) continuation -> 'a) option
= function
| Hello ->
Some (fun k -> continue k (print_endline "Hello"))
| _ -> None in
{ retc; exnc; effc }
let my_function () =
Effect.perform Hello;
print_endline "World"
let () = match_with my_function () handler
To go back to familiar OCaml elements, an effect is like an exception in that it breaks the execution flow. The "handler" is the with ...
part of a try ... with ...
in OCaml, and its installation corresponds to the try ...
. Finally, and this is the fundamental difference with exceptions, there is the continuation which allows us to return to the point where the effect was launched.
exception Hello
let my_function () =
raise Hello;
print_endline "World"
let () =
try my_function ()
with Hello k ->
print_endline "Hello";
k ()
Miou defines several effects that allow the user to interact with Miou's "task manager". Miou's effects manager is installed using run
. So, if you want to use Miou, you should always start with run
:
val my_program : unit -> unit
let () = Miou.run my_program ()
Miou is a task manager. In other words, it manages a list of to-do tasks (which you can add to with async
/call
) and allows the user to manage these tasks. When a task is created, Miou gives the user a representation of the task: a promise t
.
From this promise, the user can:
Here's an example where a list of tasks are initiated and awaited. Interaction (task creation and awaiting) with Miou takes place via effects. Miou manages the execution order of these tasks and attempts to finish them all in order to terminate your program.
let digest filename =
Miou.async @@ fun () ->
(filename, Digest.file filename)
let my_program filenames =
(* 1) we create a list of tasks *)
let prms = List.map digest filenames in
(* 2) Miou manages the execution of these tasks *)
(* 3) we wait these tasks *)
let results = List.map Miou.await_exn prms in
(* 4) we print results *)
List.iter (fun (filename, hash) ->
Format.printf "%s: %s\n%!" filename (Digest.to_hex hash))
results
let () = Miou.run @@ fun () ->
my_program ["file01.ml"; "file02.ml"]
Miou suggests a little exercise to implement a task manager with effects. It explains the role of promises, creation and awaiting for a task (it does not, however, describe cancellation).
Since OCaml 5, it has been possible to run functions in parallel. These functions run on a domain that has its own minor heap - so allocating small amounts of data doesn't require synchronization with other domains. Miou provides a pool of domains to which the user can assign tasks to run in parallel.
# let dom = Stdlib.Domain.spawn my_parallel_computation ;;
# Stdlib.Domain.join dom ;;
For more details on parallelism and garbage collection, we recommend reading the OCaml manual.
Miou prepares the allocation of a certain number of domains in advance. These will be waiting for tasks. The call
function is used to assign a new task to one of these domains. The user can specify the number of domains Miou can allocate via the domains
argument to the run
function. We recommend using Domain.recommended_domain_count () - 1
domains.
After this brief introduction to the basics of Miou (i.e. the use of effects and domains and the definition of a task manager), Miou stands out from other schedulers through its design, which we'll describe here.
However, we need to define 3 terms that will be used throughout this description:
Domain
is a resource representing a processor available to execute a task)OCaml offers only a fundamentally cooperative model for executing these tasks. Indeed, there are no mechanisms in OCaml to force the suspension of a given task. However, a given task can suspend itself in order to cooperate with other tasks on a limited resource such as a particular domain.
Miou offers a way of creating tasks (see async
) that are more precisely called fibers. These fibers must cooperate with each other to share the domain on which they run. This means that a fiber should not have exclusive domain control when other fibers are waiting to be executed.
# Miou.run @@ fun () ->
let rec pr str n =
if n >= 0 then
begin Miou.yield (); (* cooperation *)
print_endline str;
pr str (pred n)
end in
let prm0 = Miou.async @@ fun () -> pr "Hello" 1 in
let prm1 = Miou.async @@ fun () -> pr "World" 1 in
Miou.await_exn prm0;
Miou.await_exn prm1 ;;
Hello
World
Hello
World
- : unit = ()
This task cooperation is achieved by yield
, which interrupts the current task to leave the domain to another waiting task.
The problem with cooperation is that it does not take into account the irruption of external elements such as system events. Miou's objective is to be able to interrupt your application as soon as these events occur: in other words, to preempt the interruption of your tasks when these events occur.
If it's important for us to interrupt your application as soon as these events are received, it's to increase the availability of your application to handle these events.
Let's take the example of a task making a long calculation. If an event such as the arrival of a TCP/IP connection were to occur at the same time as the calculation, we would consider the latter to be more important than the completion of the calculation. So we'd like to interrupt the calculation so that your application can handle this event as a priority.
let _, _ = Miou.run @@ fun () ->
let rec server () =
let socket = accept () in
let _ = Miou.call (handler socket) in
server () in
let prm0 = Miou.async server in
let prm1 = Miou.async my_long_computation in
Miou.both prm0 prm1 ;;
(* [my_long_computation] should have multiple cooperative points to let
the other task (our [server]) to accept incoming TCP/IP connexions. *)
In other words, your application is "more" available to handle events than to perform the calculations requested. This approach becomes interesting for services (such as an HTTP server) where the availability to handle such events is more important than prioritizing the calculation requested by a client.
And therein lies the crux of the problem: how do you preempt in a fundamentally cooperative system?
If we want to be in the best position to manage system events, we need to increase the points of cooperation that the fibers can emit. This is how Miou came up with a fundamental rule: an effect yields.
All effects (those defined by Miou as well as those defined by the user) reorder task execution. During this reordering, Miou can collect the system events that have just occurred. The objective is to do this as often as possible!
At this point, we need to make clear to our future users a crucial choice we made for Miou: we prefer a scheduler that's available for system events, rather than one that performs well in calculations.
Indeed, on the cooperation points presented above, Miou will systematically ask whether any system events have occurred. However, if your ambition is to do nothing but calculations, the latter will be "polluted" by these unnecessary points of cooperation. So, by default, Miou is less efficient than other schedulers.
One of Miou's objectives is to be used in a unikernel. As far as the latter is concerned, possible interactions can be very limited. So we decided to separate the scheduler (Miou
) from interactions with the underlying system (Miou_unix
for a UNIX system).
There is a way to do this:
Miou offers a way of creating what we call a suspension point. This can be created from a value syscall
(with a unique identifier) that the user can keep. This suspension point can be "unblocked" if the select
function given to Miou (via run
) informs it of the "continuation" of this suspension.
Let's take read()
as an example. This function, which interacts with the system, can "block" (for example, if you try to read from a socket). To avoid blocking (and leave it to the system), you can ask Miou to suspend just beforehand so that it can do other tasks, and inform Miou as soon as you know that this read()
will not block.
let global = Hashtbl.create 0x100
let miou_read fd buf off len =
let syscall = Miou.syscall () in
Hashtbl.add global fd syscall;
Miou.suspend syscall;
Unix.read fd buf off len
Here, we use a global table to remind us that the file-descriptor we're using is associated with a syscall
we've just created. The next objective is to define a select
function that will observe whether the added file-descriptor is ready to be read.
select()
function.Miou lets you inject a function to observe system events. This should appear each time tasks are rescheduled, as explained above with regard to application availability. This function should return any suspension points that can be unblocked.
let select ~poll:_ _cancelled_points =
let fds = Hashtbl.to_seq_keys global |> List.of_seq in
match Unix.select fds [] [] 0.1 with
| fds, _, _ ->
let signals = List.map (fun fd ->
let syscall = Hashtbl.find global fd in
let signal = Miou.signal syscall in
Hashtbl.remove global fd; signal)
fds in
signals
let run fn =
let events _domain =
{ Miou.select; interrupt= Fun.const () } in
Miou.run ~events fn
As you can see, the next step is to produce a run
function that uses our select
. This is what Miou_unix
proposes for the example. However, there are a number of unresolved issues:
We recommend reading the chapter on system events and its tutorial on sleepers
.
Users can manipulate their tasks via their promises (see t
). A promise is an OCaml value representing the task. It can be used to await
for or cancel
a task. However, certain rules apply to its use.
It is forbidden to forget your children. The creation of a task necessarily implies that the developer await
s or cancel
s the task afterwards:
# Miou.run @@ fun () -> Miou.async (Fun.const ()) ;;
Exception: Miou.Still_has_children.
You can only await for your direct children. Transferring a promise to another task so that it can await for it is illegal:
# Miou.run @@ fun () ->
let p = Miou.async (Fun.const ()) in
let q = Miou.async (fun () -> Miou.await_exn p) in
Miou.await_all [ p; q ] |> ignore
Exception: Miou.Not_a_child.
Task relationship clarifies what is involved in managing tasks and what they should transmit to each other. To answer this question, users will have to find their own mechanisms (Mutex
, Condition
, ipc, etc.) to share results between tasks that are not directly related.
Miou only allows you to await for or cancel a task. It is also impossible to detach a task. For more information on this subject, we recommend reading the Daemon and orphan tasks. section and our following rule: background tasks.
By extension, as soon as a task is finished, all its children are finished too. The same applies to cancellation. If you cancel a task, you also cancel its children.
There is, however, a pattern in which we'd like to put a task aside: in other words, forget about it for a while. Miou offers a specific API for this pattern, described here.
There may be a contention problem if you involve dom0
in the tasks to be run in parallel. There may in fact be a situation where dom0
is awaiting for dom1
, which is awaiting for dom0
.
Miou does not allow dom0
to be assigned a parallel task. These assertions in the code below are true all the time.
# Miou.run @@ fun () ->
let prm1 = Miou.call @@ fun () ->
let prm2 = Miou.call @@ fun () ->
Miou.Domain.self () in
Miou.await_exn prm2, Miou.Domain.self () in
let u, v = Miou.await_exn prm1 in
assert (Miou.Domain.Uid.to_int u <> 0);
assert (Miou.Domain.Uid.to_int v <> 0);
assert (u <> v);;
- : unit = ()
However, you can involve dom0
in the calculations with async
.
let () = Miou.run ~domains:3 @@ fun () ->
let prm = Miou.async server in
Miou.parallel server (List.init 3 (Fun.const ()))
|> List.iter (function Ok () -> () | Error exn -> raise exn);
Miou.await_exn prm
The above rule also limits the use of call
if you only have (or want) less than 2 domains. In fact, if you only have one domain, call
cannot launch tasks in parallel. In the situation where you only have 1 domains, it is possible to launch a task in parallel from dom0
but it is impossible to launch a task in parallel from this dom1
.
In both cases and in such a situation, an exception is thrown: No_domain_available
.
A suspension point is local to the domain. This means that only the domain in which it was created can unlock it. The events
value is created for each domain created by Miou.
The advantage of making suspension points local to domains is that the domain is solely responsible for these points and there are no inter-domain transfer mechanisms for managing system events. For the example, Domain.DLS
can be used for a table of current events in each domain.
let get, set =
let make () = Hashtbl.create () in
let dom = Stdlib.Domain.DLS.new_key make in
let get () = Stdlib.Domain.DLS.get dom in
let set value = Stdlib.Domain.DLS.set dom value in
get, set
let miou_read fd buf off len =
let syscall = Miou.syscall () in
let tbl = get () in
Hashtbl.add tbl fd syscall;
set tbl;
Miou.suspend syscall;
Unix.read fd buf off len
module Pqueue = Miou_pqueue
module Logs = Miou_logs
module Fmt = Miou_fmt
module Trigger = Miou_sync.Trigger
module Computation = Miou_sync.Computation
module Queue = Miou_queue
module Sequence : sig ... end
module Domain : sig ... end
module Promise : sig ... end
An exception which can be raised by call
if no domain is available to execute the task in parallel.
module Ownership : sig ... end
The prerogative of absolutely awaiting all of its direct children limits the user to considering certain anti-patterns. The best known is the background task: it consists of running a task that we would like to detach from the main task so that it can continue its life in autonomy. For OCaml/lwt
aficionados, this corresponds to Lwt.async
:
val detach : (unit -> unit t) -> unit
Not that we want to impose an authoritarian family approach between parent and children, but the fact remains that these orphaned tasks have resources that we need to manage and free-up (even in an abnormal situation). We consider detachment to be an anti-pattern, since it requires the developer to take particular care (compared to other promises) not to 'forget' resources that could lead to memory leaks.
Instead of letting the developer commit to using a function that might be problematic, Miou offers a completely different interface that consists of assisting the developer in a coherent (and consistent) approach to responding to a particular design that is not all that systematic.
So a promise can be associated with an orphans
. The latter will then collect the results of the associated promise tasks and give you back the promises (via care
) in a 'non-blocking' mode: applying await
to them will give you the results directly.
In this way, by creating promises associated with this orphans
value, we can at the same time "clean up" these background tasks, as this code shows:
let rec clean_up orphans =
match Miou.care orphans with
| None | Some None -> ()
| Some (Some prm) -> Miou.await_exn prm; clean_up orphans
let rec server orphans =
clean_up orphans;
ignore (Miou.call ~orphans handler);
server orphans
let () = Miou.run @@ fun () -> server (Miou.orphans ())
There is a step-by-step tutorial on how to create an echo server and how to create a daemon with Miou.
val orphans : unit -> 'a orphans
val length : _ orphans -> int
length orphans
returns the number of remaining tasks.
val async :
?give:Ownership.t list ->
?orphans:'a orphans ->
(unit -> 'a) ->
'a t
async fn
(for Call with Current Continuation) returns a promise t
representing the state of the task given as an argument. The task will be executed concurrently with the other tasks in the current domain.
val call :
?give:Ownership.t list ->
?orphans:'a orphans ->
(unit -> 'a) ->
'a t
call fn
returns a promise t
representing the state of the task given as an argument. The task will be run in parallel: the domain used to run the task is different from the domain with the promise. This assertion is always true:
let () = Miou.run @@ fun () ->
let p = Miou.call @@ fun () ->
let u = Miou.Domain.self () in
let q = Miou.call @@ fun () -> Miou.Domain.self () in
(u, Miou.await_exn q) in
let u, v = Miou.await_exn p in
assert (v <> u) ;;
Sequential calls to call
do not guarantee that different domains are always chosen. This code may be true.
let () = Miou.run @@ fun () ->
let p = Miou.call @@ fun () -> Miou.Domain.self () in
let q = Miou.call @@ fun () -> Miou.Domain.self () in
let u = Miou.await_exn p in
let v = Miou.await_exn q in
assert (u = v);
To ensure that tasks are properly allocated to all domains, you need to use parallel
.
NOTE: call
will never run a task on dom0 (the main domain). Only the other domains can manage tasks in parallel.
val parallel : ('a -> 'b) -> 'a list -> ('b, exn) result list
parallel fn lst
is the fork-join model: it is a way of setting up and executing parallel tasks, such that execution branches off in parallel at designated points in the program, to "join" (merge) at a subsequent point and resume sequential execution.
Let's take the example of a sequential merge-sort:
let sort ~compare (arr, lo, hi) =
if hi - lo >= 2 then begin
let mi = (lo + hi) / 2 in
sort ~compare (arr, lo, mi);
sort ~compare (arr, mi, hi);
merge ~compare arr lo mi hi
end
The 2 recursions work on 2 different spaces (from lo
to mi
and from mi
to hi
). We could parallelise their work such that:
let sort ~compare (arr, lo, hi) =
if hi - lo >= 2 then begin
let mi = (lo + hi) / 2 in
ignore (Miou.parallel (sort ~compare)
[ (arr, lo, mi); (arr, mi, hi) ]);
merge ~compare arr lo mi hi
end
Note that parallel
launches tasks (fork) and awaits for them (join). Conceptually, this corresponds to a call
on each elements of the given list and a await_all
on all of them, with tasks allocated equally to the domains.
NOTE: This function will never assign a task to dom0 - only the other domains can run tasks in parallel. To involve dom0
, it simply has to be the one that launches the parallelisation and performs the same task concurrently.
val server : unit -> unit
let () = Miou.run ~domains:3 @@ fun () ->
let p = Miou.async server in
Miou.parallel server (List.init 3 (Fun.const ()))
|> List.iter (function Ok () -> () | Error exn -> raise exn);
Miou.await_exn p
await prm
awaits for the task associated with the promise to finish. You can assume that after await
, the task has ended with an exception with the Error
case or normally with the Ok
case. In the case of an abnormal termination (the raising of an exception), the children of the promise are cancelled. For instance, this code is valid:
# Miou_unix.run @@ fun () ->
let p = Miou.async @@ fun () ->
let child_of_p = Miou.async @@ fun () -> Miou_unix.sleep 10. in
failwith "p";
Miou.await_exn child_of_p in
Miou.await p ;;
- (unit, exn) result = Error (Failure "p")
# (* [child_of_p] was cancelled and you don't sleep 10s. *)
Note that you should always await for your children (it's illegal to forget your children), as in the example above (even if an exception occurs). If a task does not await for its children, an uncatchable exception is raised by Miou:
# Miou.run @@ fun () ->
ignore (Miou.async (Fun.const ())) ;;
Exception: Miou.Still_has_children.
val await_exn : 'a t -> 'a
await_exn prm
is an alias for await
which reraises the exception in the Error
case.
await_one prms
awaits for a task to finish (by exception or normally). Despite await_first
, await_one
does not cancel all the others. The user must await
them then, otherwise Miou will assume they're still active and will raise Still_has_children
.
# Miou.run @@ fun () ->
Miou.await_one
[ Miou.async (Fun.const 1)
; Miou.async (Fun.const 2) ] ;;
Exception: Miou.Still_has_children
A valid code would be:
# Miou.run @@ fun () ->
let p = Miou.async (Fun.const 1) in
let q = Miou.async (Fun.const 2) in
match Miou.await_one [ p; q ] with
| 1 -> Miou.await_exn q
| 2 -> Miou.await_exn p
| _ -> assert false ;;
- : int = 1
If several tasks finish "at the same time" (as is the case in our example above), we prioritise the tasks that finished well and choose one at random.
await_first prms
awaits for a task to finish (by exception or normally) and cancels all the others. If several tasks finish "at the same time", normally completed tasks are preferred to failed ones. This function can be useful for timeouts:
# exception Timeout ;;
# Miou_unix.run @@ fun () ->
let p0 = Miou.async (Fun.const ()) in
let p1 = Miou.async @@ fun () -> Miou_unix.sleep 2.; raise Timeout in
Miou.await_first [ p0; p1 ] ;;
- : (unit, exn) result = Ok ()
await_all prms
awaits for all the tasks linked to the promises given. If one of the tasks raises an uncatchable exception, await_all
reraises the said exception. All tasks are awaited for, regardless of whether any fail.
Used when a task is cancelled by cancel
.
val cancel : 'a t -> unit
cancel prm
asynchronously cancels the given promise prm
. Miou allows the forgetting of a cancelled promise and the forgetting of its children. For instance, this code is valid (despite the second one):
# Miou.run @@ fun () ->
ignore (Miou.cancel (Miou.call (Fun.const ()))) ;;
- : unit = ()
# Miou.run @@ fun () ->
ignore (Miou.call (Fun.const ())) ;;
Exception: Miou.Still_has_children
Cancellation terminates all the children. After the cancellation, the promise and its children all stopped. Resolved children are also cancelled (their results are erased). Canceling a task that has already been solved changes the state of the task to abnormal termination Error Cancelled
.
# Miou.run @@ fun () ->
let p = Miou.async (Fun.const ()) in
Miou.await_exn p;
Miou.cancel p;
Miou.await_exn p ;;
Exception: Miou.Cancelled.
This case shows that, even if the task has been resolved internally, the cancellation also applies.
# Miou.run @@ fun () ->
let p = Miou.async @@ fun () -> print_endline "Resolved!" in
Miou.yield ();
Miou.cancel p;
Miou.await_exn p ;;
Resolved!
Exception: Miou.Cancelled.
Only the creator of a task can cancel
it (the relationship also applies to cancellation, otherwise Miou raises the exception Not_a_child
).
NOTE: Cancellation asynchronicity means that other concurrent tasks can run while the cancellation is in progress. In fact, in the case of an cancellation of a parallel task (see call
), the cancellation may take a certain amount of time (the time it takes for the domains to synchronise) which should not affect the opportunity for other concurrent tasks to run.
yield ()
reschedules tasks and give an opportunity to carry out the tasks that have been on hold the longest. For intance:
# Miou.run @@ fun () ->
let p = Miou.async @@ fun () -> print_endline "Hello" in
print_endline "World";
Miou.await_exn p ;;
World
Hello
- : unit = ()
# Miou.run @@ fun () ->
let p = Miou.async @@ fun () -> print_endline "Hello" in
Miou.yield ();
print_endline "World";
Miou.await_exn p
Hello
World
- : unit = ()
module Hook : sig ... end
Miou does not monitor system events. We arbitrarily leave this event monitoring to the user (so that Miou only requires OCaml to run). The advantage is that you can inject an event monitor from a specific system (such as a unikernel) if you want. However, Miou_unix
is available if you want to do input/output.
To facilitate the integration of an event monitor, Miou offers an API for creating "suspension points" (see suspend
). In other words, points where execution will be blocked for as long as you wish. These points can be unblocked as soon as the monitor gives Miou a "signal" to these points with signal
.
The user must specify a select
function (via the run
function and the events
type), which must correspond to system event monitoring (probably using Unix.select
). From these events, the monitor can decide which suspension point (thanks to its uid
) should be released. Miou will then call this function for each quanta consumed. This gives Miou a high degree of availability to consume and process system events.
Each domain has its own monitor so that the suspension and its continuation given by the monitor is always local to the domain (the domain managing the suspension is the only one allowed to execute the continuation). One events
is allocated per domain - it is given on which domain the event
value is assigned. In this way, the values (such as a table of active file-descriptors) required to monitor system events need not be domain-safe.
Sometimes, Miou only has suspension points. In other words, only system events are required to execute tasks (typically waiting for a TCP/IP connection). We say we're in a sleep state. In this case, Miou informs the monitor select
that it can wait indefinitely (with block:true
).
It can happen that a task executed by one domain is cancelled by another domain (if the first was created by call
). This cancellation of a task can also mean the cancellation of existing suspension points into the task. Miou must therefore be able to interrupt a domain (especially if the latter is in a sleep state).
Thus, the user must have a mechanism for stopping event monitoring, which must be given to Miou via the interrupt
field (see events
).
Finally, Miou informs the monitor of any points that have been cancelled, so that the associated events can no longer be monitored (this could involve cleaning up the table of active file-descritpors).
To help you understand all these related elements, the distribution offers a short tutorial on how to implement functions that can block a given time (such as Unix.sleep
): sleepers
.
The type of syscalls.
A syscall is an unique ID and function executed as soon as the suspension point is released. This suspension point is created using the suspend
function.
The type of signals.
A signal is a syscall that has been suspended (with suspend
) that we would like to resume. This is a value that must be given to Miou (via select
) in order to unblock the previously created suspend point.
The type of unique IDs of syscall
s.
val syscall : unit -> syscall
syscall ()
creates a syscall which permits the user to create a new suspension point via suspend
.
val suspend : syscall -> unit
signal syscall
creates a signal
value which can be used by Miou to unblock the suspension point associated with the given syscall.
val run :
?quanta:int ->
?g:Random.State.t ->
?domains:int ->
?events:(Domain.Uid.t -> events) ->
(unit -> 'a) ->
'a
val sys_signal : int -> Sys.signal_behavior -> Sys.signal_behavior
signal signal behavior
attaches a behavior
to a signal
:
Signal_default
aborts the programSignal_ignore
ignore the signalSignal_handle fn
calls fn
(in the dom0
)signal
is provided to be able to execute Miou's tasks when we receive a signal from the system. The dom0
takes the responsability to execute the given fn
.
val protect :
on_cancellation:(unit -> unit) ->
finally:(cancelled:bool -> unit) ->
(unit -> 'a) ->
'a
protect ~on_cancellation ~finally fn
invokes fn ()
and then finally ~cancelled
before fn ()
returns its value or an exception as Fun.protect
or an cancellation. In the case of an abnormal termination, the exception is re-raised after finally ~cancelled
. If finally
raises an exception, then the exception Fun.Finally_raised
is raised instead. In the case of a cancellation, it invokes finally ()
and then on_cancellation ()
before the deletion of fn ()
. If on_cancellation ()
raises an exception, then the exception On_cancellation_raised
is raised instead.
on_cancellation
must not use any effects. Using effects suspends execution and, in the case of cancellation, anything after the effect will never be executed.
finally
can use effects. protect
informs the user if finally
is invoked due to cancellation or not.
protect
can be used to enforce local invariants whether fn ()
returns normally or raises an exception or is cancelled. However, it does not protect against unexpected exceptions raised inside finally ~cancelled
and on_cancellation ()
such as Stdlib.Out_of_memory
, Stdlib.Stack_overflow
, or asynchronous exceptions raised by signal handlers (e.g. Sys.Break
).
module Mutex : sig ... end
module Condition : sig ... end
module Lazy : sig ... end