1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147
|
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* KC Sivaramakrishnan, Indian Institute of Technology, Madras *)
(* *)
(* Copyright 2021 Indian Institute of Technology, Madras *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
[@@@alert unstable
"The Effect interface may change in incompatible ways in the future."
]
(** Effects.
See 'Language extensions/Effect handlers' section in the manual.
@since 5.0 *)
type 'a t = 'a eff = ..
(** The type of effects. *)
exception Unhandled : 'a t -> exn
(** [Unhandled e] is raised when effect [e] is performed and there is no
handler for it. *)
exception Continuation_already_resumed
(** Exception raised when a continuation is continued or discontinued more
than once. *)
external perform : 'a t -> 'a = "%perform"
(** [perform e] performs an effect [e].
@raise Unhandled if there is no handler for [e]. *)
module Deep : sig
(** Deep handlers *)
type nonrec ('a,'b) continuation = ('a,'b) continuation
(** [('a,'b) continuation] is a delimited continuation that expects a ['a]
value and returns a ['b] value. *)
val continue: ('a, 'b) continuation -> 'a -> 'b
(** [continue k x] resumes the continuation [k] by passing [x] to [k].
@raise Continuation_already_resumed if the continuation has already been
resumed. *)
val discontinue: ('a, 'b) continuation -> exn -> 'b
(** [discontinue k e] resumes the continuation [k] by raising the
exception [e] in [k].
@raise Continuation_already_resumed if the continuation has already been
resumed. *)
val discontinue_with_backtrace:
('a, 'b) continuation -> exn -> Printexc.raw_backtrace -> 'b
(** [discontinue_with_backtrace k e bt] resumes the continuation [k] by
raising the exception [e] in [k] using [bt] as the origin for the
exception.
@raise Continuation_already_resumed if the continuation has already been
resumed. *)
type ('a,'b) handler =
{ retc: 'a -> 'b;
exnc: exn -> 'b;
effc: 'c.'c t -> (('c,'b) continuation -> 'b) option }
(** [('a,'b) handler] is a handler record with three fields -- [retc]
is the value handler, [exnc] handles exceptions, and [effc] handles the
effects performed by the computation enclosed by the handler. *)
val match_with: ('c -> 'a) -> 'c -> ('a,'b) handler -> 'b
(** [match_with f v h] runs the computation [f v] in the handler [h]. *)
type 'a effect_handler =
{ effc: 'b. 'b t -> (('b, 'a) continuation -> 'a) option }
(** ['a effect_handler] is a deep handler with an identity value handler
[fun x -> x] and an exception handler that raises any exception
[fun e -> raise e]. *)
val try_with: ('b -> 'a) -> 'b -> 'a effect_handler -> 'a
(** [try_with f v h] runs the computation [f v] under the handler [h]. *)
external get_callstack :
('a,'b) continuation -> int -> Printexc.raw_backtrace =
"caml_get_continuation_callstack"
(** [get_callstack c n] returns a description of the top of the call stack on
the continuation [c], with at most [n] entries. *)
end
module Shallow : sig
(* Shallow handlers *)
type ('a,'b) continuation
(** [('a,'b) continuation] is a delimited continuation that expects a ['a]
value and returns a ['b] value. *)
val fiber : ('a -> 'b) -> ('a, 'b) continuation
(** [fiber f] constructs a continuation that runs the computation [f]. *)
type ('a,'b) handler =
{ retc: 'a -> 'b;
exnc: exn -> 'b;
effc: 'c.'c t -> (('c,'a) continuation -> 'b) option }
(** [('a,'b) handler] is a handler record with three fields -- [retc]
is the value handler, [exnc] handles exceptions, and [effc] handles the
effects performed by the computation enclosed by the handler. *)
val continue_with : ('c,'a) continuation -> 'c -> ('a,'b) handler -> 'b
(** [continue_with k v h] resumes the continuation [k] with value [v] with
the handler [h].
@raise Continuation_already_resumed if the continuation has already been
resumed.
*)
val discontinue_with : ('c,'a) continuation -> exn -> ('a,'b) handler -> 'b
(** [discontinue_with k e h] resumes the continuation [k] by raising the
exception [e] with the handler [h].
@raise Continuation_already_resumed if the continuation has already been
resumed.
*)
val discontinue_with_backtrace :
('a,'b) continuation -> exn -> Printexc.raw_backtrace ->
('b,'c) handler -> 'c
(** [discontinue_with k e bt h] resumes the continuation [k] by raising the
exception [e] with the handler [h] using the raw backtrace [bt] as the
origin of the exception.
@raise Continuation_already_resumed if the continuation has already been
resumed.
*)
external get_callstack :
('a,'b) continuation -> int -> Printexc.raw_backtrace =
"caml_get_continuation_callstack"
(** [get_callstack c n] returns a description of the top of the call stack on
the continuation [c], with at most [n] entries. *)
end
|