forked from ocaml-multicore/ocaml-multicore
-
Notifications
You must be signed in to change notification settings - Fork 0
/
lazy.mli
155 lines (119 loc) · 6.03 KB
/
lazy.mli
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
148
149
150
151
152
153
154
155
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
(* *)
(* Copyright 1997 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
(** Deferred computations. *)
type 'a t = 'a CamlinternalLazy.t
(** A value of type ['a Lazy.t] is a deferred computation, called a suspension,
that has a result of type ['a]. The special expression syntax [lazy (expr)]
makes a suspension of the computation of [expr], without computing
[expr] itself yet. "Forcing" the suspension will then compute [expr] and
return its result. Matching a suspension with the special pattern syntax
[lazy(pattern)] also computes the underlying expression and tries to bind
it to [pattern]:
{[
let lazy_option_map f x =
match x with
| lazy (Some x) -> Some (Lazy.force f x)
| _ -> None
]}
Note: If lazy patterns appear in multiple cases in a pattern-matching, lazy
expressions may be forced even outside of the case ultimately selected by
the pattern matching. In the example above, the suspension [x] is always
computed.
Note: [lazy_t] is the built-in type constructor used by the compiler for the
[lazy] keyword. You should not use it directly. Always use [Lazy.t]
instead.
Note: [Lazy.force] is not concurrency-safe. If you use this module with
multiple fibers, systhreads or domains, then you will need to add some
locks. The module however ensures memory-safety, and hence, concurrently
accessing this module will not lead to a crash but the behaviour is
unspecified.
Note: if the program is compiled with the [-rectypes] option,
ill-founded recursive definitions of the form [let rec x = lazy x]
or [let rec x = lazy(lazy(...(lazy x)))] are accepted by the type-checker
and lead, when forced, to ill-formed values that trigger infinite
loops in the garbage collector and other parts of the run-time system.
Without the [-rectypes] option, such ill-founded recursive definitions
are rejected by the type-checker.
*)
exception Undefined
(** Raised when forcing a suspension concurrently from multiple fibers,
systhreads or domains, or when the suspension tries to force itself
recursively.
*)
external force : 'a t -> 'a = "%lazy_force"
(** [force x] forces the suspension [x] and returns its result. If [x] has
already been forced, [Lazy.force x] returns the same value again without
recomputing it. If it raised an exception, the same exception is raised
again.
@raise Undefined (see {!Undefined}).
*)
(** {1 Iterators} *)
val map : ('a -> 'b) -> 'a t -> 'b t
(** [map f x] returns a suspension that, when forced,
forces [x] and applies [f] to its value.
It is equivalent to [lazy (f (Lazy.force x))].
@since 4.13.0
*)
(** {1 Reasoning on already-forced suspensions} *)
val is_val : 'a t -> bool
(** [is_val x] returns [true] if [x] has already been forced and
did not raise an exception.
@since 4.00.0 *)
val from_val : 'a -> 'a t
(** [from_val v] evaluates [v] first (as any function would) and returns
an already-forced suspension of its result.
It is the same as [let x = v in lazy x], but uses dynamic tests
to optimize suspension creation in some cases.
@since 4.00.0 *)
val map_val : ('a -> 'b) -> 'a t -> 'b t
(** [map_val f x] applies [f] directly if [x] is already forced,
otherwise it behaves as [map f x].
When [x] is already forced, this behavior saves the construction of
a suspension, but on the other hand it performs more work eagerly
that may not be useful if you never force the function result.
If [f] raises an exception, it will be raised immediately when
[is_val x], or raised only when forcing the thunk otherwise.
If [map_val f x] does not raise an exception, then
[is_val (map_val f x)] is equal to [is_val x].
@since 4.13.0 *)
(** {1 Advanced}
The following definitions are for advanced uses only; they require
familiary with the lazy compilation scheme to be used appropriately. *)
val from_fun : (unit -> 'a) -> 'a t
(** [from_fun f] is the same as [lazy (f ())] but slightly more efficient.
It should only be used if the function [f] is already defined.
In particular it is always less efficient to write
[from_fun (fun () -> expr)] than [lazy expr].
@since 4.00.0 *)
val force_val : 'a t -> 'a
(** [force_val x] forces the suspension [x] and returns its result. If [x]
has already been forced, [force_val x] returns the same value again
without recomputing it.
If the computation of [x] raises an exception, it is unspecified
whether [force_val x] raises the same exception or {!Undefined}.
@raise Undefined if the forcing of [x] tries to force [x] itself
recursively.
@raise Undefined (see {!Undefined}).
*)
(** {1 Deprecated} *)
val lazy_from_fun : (unit -> 'a) -> 'a t
[@@ocaml.deprecated "Use Lazy.from_fun instead."]
(** @deprecated synonym for [from_fun]. *)
val lazy_from_val : 'a -> 'a t
[@@ocaml.deprecated "Use Lazy.from_val instead."]
(** @deprecated synonym for [from_val]. *)
val lazy_is_val : 'a t -> bool
[@@ocaml.deprecated "Use Lazy.is_val instead."]
(** @deprecated synonym for [is_val]. *)