]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/stdlib/camlinternalLazy.mli
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / stdlib / camlinternalLazy.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Damien Doligez, projet Para, INRIA Rocquencourt          *)
6 (*                                                                     *)
7 (*  Copyright 1997 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the GNU Library General Public License, with    *)
10 (*  the special exception on linking described in file ../LICENSE.     *)
11 (*                                                                     *)
12 (***********************************************************************)
13
14 (* $Id: camlinternalLazy.mli 8974 2008-08-01 16:57:10Z mauny $ *)
15
16 (* Internals of forcing lazy values *)
17
18 exception Undefined;;
19
20 val force_lazy_block : 'a lazy_t -> 'a ;;
21
22 val force_val_lazy_block : 'a lazy_t -> 'a ;;
23
24 val force : 'a lazy_t -> 'a ;;
25 val force_val : 'a lazy_t -> 'a ;;