This file is indexed.

/usr/lib/ocaml/compiler-libs/typing/typetexp.mli is in ocaml-compiler-libs 3.12.1-2ubuntu2.

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
(***********************************************************************)
(*                                                                     *)
(*                           Objective Caml                            *)
(*                                                                     *)
(*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
(*                                                                     *)
(*  Copyright 1996 Institut National de Recherche en Informatique et   *)
(*  en Automatique.  All rights reserved.  This file is distributed    *)
(*  under the terms of the Q Public License version 1.0.               *)
(*                                                                     *)
(***********************************************************************)

(* $Id: typetexp.mli 10422 2010-05-18 17:25:02Z frisch $ *)

(* Typechecking of type expressions for the core language *)

open Format;;

val transl_simple_type:
        Env.t -> bool -> Parsetree.core_type -> Types.type_expr
val transl_simple_type_univars:
        Env.t -> Parsetree.core_type -> Types.type_expr
val transl_simple_type_delayed:
        Env.t -> Parsetree.core_type -> Types.type_expr * (unit -> unit)
        (* Translate a type, but leave type variables unbound. Returns
           the type and a function that binds the type variable. *)
val transl_type_scheme:
        Env.t -> Parsetree.core_type -> Types.type_expr
val reset_type_variables: unit -> unit
val enter_type_variable: bool -> Location.t -> string -> Types.type_expr
val type_variable: Location.t -> string -> Types.type_expr

type variable_context
val narrow: unit -> variable_context
val widen: variable_context -> unit

exception Already_bound

type error =
    Unbound_type_variable of string
  | Unbound_type_constructor of Longident.t
  | Unbound_type_constructor_2 of Path.t
  | Type_arity_mismatch of Longident.t * int * int
  | Bound_type_variable of string
  | Recursive_type
  | Unbound_row_variable of Longident.t
  | Type_mismatch of (Types.type_expr * Types.type_expr) list
  | Alias_type_mismatch of (Types.type_expr * Types.type_expr) list
  | Present_has_conjunction of string
  | Present_has_no_type of string
  | Constructor_mismatch of Types.type_expr * Types.type_expr
  | Not_a_variant of Types.type_expr
  | Variant_tags of string * string
  | Invalid_variable_name of string
  | Cannot_quantify of string * Types.type_expr
  | Multiple_constraints_on_type of string
  | Repeated_method_label of string
  | Unbound_value of Longident.t
  | Unbound_constructor of Longident.t
  | Unbound_label of Longident.t
  | Unbound_module of Longident.t
  | Unbound_class of Longident.t
  | Unbound_modtype of Longident.t
  | Unbound_cltype of Longident.t
  | Ill_typed_functor_application of Longident.t

exception Error of Location.t * error

val report_error: formatter -> error -> unit

(* Support for first-class modules. *)
val transl_modtype_longident: (Location.t -> Env.t -> Longident.t -> Path.t) ref  (* from Typemod *)
val transl_modtype: (Env.t -> Parsetree.module_type -> Types.module_type) ref (* from Typemod *)
val create_package_mty: Location.t -> Env.t -> Parsetree.package_type -> (string * Parsetree.core_type) list * Parsetree.module_type

val find_type: Env.t -> Location.t -> Longident.t -> Path.t * Types.type_declaration
val find_constructor: Env.t -> Location.t -> Longident.t -> Types.constructor_description
val find_label: Env.t -> Location.t -> Longident.t -> Types.label_description
val find_value: Env.t -> Location.t -> Longident.t -> Path.t * Types.value_description
val find_class:  Env.t -> Location.t -> Longident.t -> Path.t * Types.class_declaration
val find_module: Env.t -> Location.t -> Longident.t -> Path.t * Types.module_type
val find_modtype: Env.t -> Location.t -> Longident.t -> Path.t * Types.modtype_declaration
val find_cltype: Env.t -> Location.t -> Longident.t -> Path.t * Types.cltype_declaration