blob: 37baec476cf58f480970a8645d0ea5c97e44599e (
plain)
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
|
(***********************************************************************)
(* *)
(* Objective Caml *)
(* *)
(* 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 Library General Public License. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* Module [Lazy]: deferred computations *)
type 'a status =
| Delayed of (unit -> 'a)
| Value of 'a
| Exception of exn
;;
type 'a t = 'a status ref;;
let force l =
match !l with
| Value v -> v
| Exception e -> raise e
| Delayed f ->
try let v = f () in l := Value v; v
with e -> l := Exception e; raise e
;;
|