This file is indexed.

/usr/x86_64-w64-mingw32/lib/ocaml/dynlink.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
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
(***********************************************************************)
(*                                                                     *)
(*                                OCaml                                *)
(*                                                                     *)
(*            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 GNU Library General Public License, with    *)
(*  the special exception on linking described in file ../../LICENSE.  *)
(*                                                                     *)
(***********************************************************************)

(** Dynamic loading of object files. *)

val is_native: bool
(** [true] if the program is native,
    [false] if the program is bytecode. *)

(** {6 Dynamic loading of compiled files} *)

val loadfile : string -> unit
(** In bytecode: load the given bytecode object file ([.cmo] file) or
    bytecode library file ([.cma] file), and link it with the running
    program. In native code: load the given OCaml plugin file (usually
    [.cmxs]), and link it with the running
    program.
    All toplevel expressions in the loaded compilation units
    are evaluated. No facilities are provided to
    access value names defined by the unit. Therefore, the unit
    must register itself its entry points with the main program,
    e.g. by modifying tables of functions. *)

val loadfile_private : string -> unit
(** Same as [loadfile], except that the compilation units just loaded
    are hidden (cannot be referenced) from other modules dynamically
    loaded afterwards. *)

val adapt_filename : string -> string
(** In bytecode, the identity function. In native code, replace the last
    extension with [.cmxs]. *)

(** {6 Access control} *)

val allow_only: string list -> unit
(** [allow_only units] restricts the compilation units that dynamically-linked
    units can reference: it only allows references to the units named in
    list [units].  References to any other compilation unit will cause
    a [Unavailable_unit] error during [loadfile] or [loadfile_private].

    Initially (just after calling [init]), all compilation units composing
    the program currently running are available for reference from
    dynamically-linked units.  [allow_only] can be used to grant access
    to some of them only, e.g. to the units that compose the API for
    dynamically-linked code, and prevent access to all other units,
    e.g. private, internal modules of the running program. *)

val prohibit: string list -> unit
(** [prohibit units] prohibits dynamically-linked units from referencing
    the units named in list [units].  This can be used to prevent
    access to selected units, e.g. private, internal modules of
    the running program. *)

val default_available_units: unit -> unit
(** Reset the set of units that can be referenced from dynamically-linked
    code to its default value, that is, all units composing the currently
    running program. *)

val allow_unsafe_modules : bool -> unit
(** Govern whether unsafe object files are allowed to be
    dynamically linked. A compilation unit is 'unsafe' if it contains
    declarations of external functions, which can break type safety.
    By default, dynamic linking of unsafe object files is
    not allowed. In native code, this function does nothing; object files
    with external functions are always allowed to be dynamically linked. *)

(** {6 Deprecated, low-level API for access control} *)

(** @deprecated  The functions [add_interfaces], [add_available_units]
    and [clear_available_units] should not be used in new programs,
    since the default initialization of allowed units, along with the
    [allow_only] and [prohibit] function, provides a better, safer
    mechanism to control access to program units.  The three functions
    below are provided for backward compatibility only and are not
    available in native code. *)

val add_interfaces : string list -> string list -> unit
(** [add_interfaces units path] grants dynamically-linked object
    files access to the compilation  units named in list [units].
    The interfaces ([.cmi] files) for these units are searched in
    [path] (a list of directory names). *)

val add_available_units : (string * Digest.t) list -> unit
(** Same as {!Dynlink.add_interfaces}, but instead of searching [.cmi] files
    to find the unit interfaces, uses the interface digests given
    for each unit. This way, the [.cmi] interface files need not be
    available at run-time. The digests can be extracted from [.cmi]
    files using the [extract_crc] program installed in the
    OCaml standard library directory. *)

val clear_available_units : unit -> unit
(** Empty the list of compilation units accessible to dynamically-linked
    programs. *)

(** {6 Deprecated, initialization} *)

val init : unit -> unit
(** @deprecated Initialize the [Dynlink] library. This function is called
    automatically when needed. *)

(** {6 Error reporting} *)

type linking_error =
    Undefined_global of string
  | Unavailable_primitive of string
  | Uninitialized_global of string

type error =
    Not_a_bytecode_file of string
  | Inconsistent_import of string
  | Unavailable_unit of string
  | Unsafe_file
  | Linking_error of string * linking_error
  | Corrupted_interface of string
  | File_not_found of string
  | Cannot_open_dll of string
  | Inconsistent_implementation of string

exception Error of error
(** Errors in dynamic linking are reported by raising the [Error]
    exception with a description of the error. *)

val error_message : error -> string
(** Convert an error description to a printable message. *)


(**/**)

(** {6 Internal functions} *)

val digest_interface : string -> string list -> Digest.t