This file is indexed.

/usr/x86_64-w64-mingw32/lib/ocaml/lazy.mli is in ocaml-mingw-w64-x86-64 4.01.0~20140328-1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

 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
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
(***********************************************************************)
(*                                                                     *)
(*                                OCaml                                *)
(*                                                                     *)
(*            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, with    *)
(*  the special exception on linking described in file ../LICENSE.     *)
(*                                                                     *)
(***********************************************************************)

(** Deferred computations. *)

type 'a t = 'a lazy_t;;
(** A value of type ['a Lazy.t] is a deferred computation, called
   a suspension, that has a result of type ['a].  The special
   expression syntax [lazy (expr)] makes a suspension of the
   computation of [expr], without computing [expr] itself yet.
   "Forcing" the suspension will then compute [expr] and return its
   result.

   Note: [lazy_t] is the built-in type constructor used by the compiler
   for the [lazy] keyword.  You should not use it directly.  Always use
   [Lazy.t] instead.

   Note: [Lazy.force] is not thread-safe.  If you use this module in
   a multi-threaded program, you will need to add some locks.

   Note: if the program is compiled with the [-rectypes] option,
   ill-founded recursive definitions of the form [let rec x = lazy x]
   or [let rec x = lazy(lazy(...(lazy x)))] are accepted by the type-checker
   and lead, when forced, to ill-formed values that trigger infinite
   loops in the garbage collector and other parts of the run-time system.
   Without the [-rectypes] option, such ill-founded recursive definitions
   are rejected by the type-checker.
*)


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
   same value again without recomputing it.  If it raised an exception,
   the same exception is raised again.
   Raise [Undefined] if the forcing of [x] tries to force [x] itself
   recursively.
*)

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.
    Raise [Undefined] if the forcing of [x] tries to force [x] itself
    recursively.
    If the computation of [x] raises an exception, it is unspecified
    whether [force_val x] raises the same exception or [Undefined].
*)

val from_fun : (unit -> 'a) -> 'a t;;
(** [from_fun f] is the same as [lazy (f ())] but slightly more efficient.
    @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 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;;
(** @deprecated synonym for [from_fun]. *)

val lazy_from_val : 'a -> 'a t;;
(** @deprecated synonym for [from_val]. *)

val lazy_is_val : 'a t -> bool;;
(** @deprecated synonym for [is_val]. *)