1997-10-14 06:29:58 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
|
|
|
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1997-10-22 06:26:05 -07:00
|
|
|
(* Copyright 1997 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1997-10-14 06:29:58 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
|
|
|
(* Module [Lazy]: deferred computations *)
|
|
|
|
|
|
|
|
type 'a status =
|
|
|
|
| Delayed of (unit -> 'a)
|
|
|
|
| Value of 'a
|
|
|
|
| Exception of exn
|
|
|
|
;;
|
|
|
|
|
1997-10-22 06:26:05 -07:00
|
|
|
type 'a t = 'a status ref;;
|
1997-10-14 06:29:58 -07:00
|
|
|
|
2000-01-07 11:18:34 -08:00
|
|
|
exception Undefined;;
|
|
|
|
|
1997-10-14 06:29:58 -07:00
|
|
|
let force l =
|
|
|
|
match !l with
|
|
|
|
| Value v -> v
|
|
|
|
| Exception e -> raise e
|
|
|
|
| Delayed f ->
|
2000-01-07 11:18:34 -08:00
|
|
|
l := Exception Undefined;
|
1997-10-14 06:29:58 -07:00
|
|
|
try let v = f () in l := Value v; v
|
|
|
|
with e -> l := Exception e; raise e
|
|
|
|
;;
|