Skip to content

Commit

Permalink
Lazy.map : ('a -> 'b) -> 'a Lazy.t -> 'b Lazy.t
Browse files Browse the repository at this point in the history
  • Loading branch information
gasche committed Dec 31, 2020
1 parent 9f53c6b commit eb07eb9
Show file tree
Hide file tree
Showing 4 changed files with 49 additions and 5 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,9 @@ Working version
- #9582: Add Array.{find_opt,find_map,split,combine}.
(Nicolás Ojeda Bär, review by Daniel Bünzli and Gabriel Scherer)

- #10097: Lazy.map: ('a -> 'b) -> 'a Lazy.t -> 'b Lazy.t
(Gabriel Scherer, review by Nicolás Ojeda Bär)

### Other libraries:

* #10084: Unix.open_process_args* functions now look up the program in the PATH.
Expand Down
4 changes: 4 additions & 0 deletions stdlib/lazy.ml
Original file line number Diff line number Diff line change
Expand Up @@ -81,3 +81,7 @@ let lazy_from_fun = from_fun
let lazy_from_val = from_val

let lazy_is_val = is_val


let map f x =
lazy (f (force x))
23 changes: 18 additions & 5 deletions stdlib/lazy.mli
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ type 'a t = 'a CamlinternalLazy.t
are rejected by the type-checker.
*)

(** {1 Basic primitives} *)

exception Undefined

Expand All @@ -67,6 +68,23 @@ external force : 'a t -> 'a = "%lazy_force"
recursively.
*)

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 map : ('a -> 'b) -> 'a t -> 'b t
(** [map f x] returns a suspension that, when forced,
forces [x] and applies [f] to its value.
@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 correctly. *)

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]
Expand All @@ -93,11 +111,6 @@ val from_val : 'a -> 'a t
[lazy (v)].
@since 4.00.0 *)

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 lazy_from_fun : (unit -> 'a) -> 'a t
[@@ocaml.deprecated "Use Lazy.from_fun instead."]
(** @deprecated synonym for [from_fun]. *)
Expand Down
24 changes: 24 additions & 0 deletions testsuite/tests/lib-lazy/test.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
(* TEST
* expect
*)

(* expect-tests currently do not collect I/O,
so we emulate I/O by collecting output in a "log" *)
let logger () =
let log = ref [] in
let show_log v = List.rev !log, v in
let log v = log := v :: !log in
log, show_log

let _ =
let log, show_log = logger () in
let x = lazy (log "x"; 41) in
let y =
log "map";
Lazy.map (fun n -> log "y"; n+1) x in
show_log (Lazy.force y)
;;
[%%expect{|
val logger : unit -> ('a -> unit) * ('b -> 'a list * 'b) = <fun>
- : string list * int = (["map"; "x"; "y"], 42)
|}]

0 comments on commit eb07eb9

Please sign in to comment.