Skip to content

Commit

Permalink
lazy.mli: create documentation sections, make some explanations more …
Browse files Browse the repository at this point in the history
…precise
  • Loading branch information
gasche committed Jan 10, 2021
1 parent edd7c2c commit e730a2f
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 21 deletions.
1 change: 0 additions & 1 deletion stdlib/lazy.ml
Expand Up @@ -55,7 +55,6 @@ external make_forward : 'a -> 'a lazy_t = "caml_lazy_make_forward"

external force : 'a t -> 'a = "%lazy_force"

(* let force = force *)

let force_val = CamlinternalLazy.force_val

Expand Down
55 changes: 35 additions & 20 deletions stdlib/lazy.mli
Expand Up @@ -57,7 +57,6 @@ type 'a t = 'a CamlinternalLazy.t

exception Undefined

(* val force : 'a t -> 'a *)
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
Expand All @@ -67,6 +66,9 @@ external force : 'a t -> 'a = "%lazy_force"
recursively.
*)


(** {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.
Expand All @@ -87,36 +89,49 @@ val opportune_map : ('a -> 'b) -> 'a t -> 'b t
@since 4.13.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.
*)
(** {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 use dynamic tests
to optimize suspension creation in some cases.
@since 4.00.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.
[from_fun] should only be used if the function [f] is already defined.
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 from_val : 'a -> 'a t
(** [from_val v] returns an already-forced suspension of [v].
This is for special purposes only and should not be confused with
[lazy (v)].
@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.
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 *)
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.
*)


(** {1 Deprecated} **)

val lazy_from_fun : (unit -> 'a) -> 'a t
[@@ocaml.deprecated "Use Lazy.from_fun instead."]
Expand Down

0 comments on commit e730a2f

Please sign in to comment.