File: load_path.mli

package info (click to toggle)
ocaml 5.4.0-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 44,384 kB
  • sloc: ml: 370,196; ansic: 52,820; sh: 27,419; asm: 5,462; makefile: 3,684; python: 974; awk: 278; javascript: 273; perl: 59; fortran: 21; cs: 9
file content (120 lines) | stat: -rw-r--r-- 4,564 bytes parent folder | download | duplicates (7)
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
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*                   Jeremie Dimino, Jane Street Europe                   *)
(*                                                                        *)
(*   Copyright 2018 Jane Street Group LLC                                 *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(** Management of include directories.

    This module offers a high level interface to locating files in the load
    path, which is constructed from [-I] and [-H] command line flags and a few
    other parameters.

    It makes the assumption that the contents of include directories
    doesn't change during the execution of the compiler.
*)

val add_dir : hidden:bool -> string -> unit
(** Add a directory to the end of the load path (i.e. at lowest priority.) *)

val remove_dir : string -> unit
(** Remove a directory from the load path *)

val reset : unit -> unit
(** Remove all directories *)

module Dir : sig
  type t
  (** Represent one directory in the load path. *)

  val create : hidden:bool -> string -> t

  val path : t -> string

  val files : t -> string list
  (** All the files in that directory. This doesn't include files in
      sub-directories of this directory. *)

  val hidden : t -> bool
  (** If the modules in this directory should not be bound in the initial
      scope *)

  val find : t -> string -> string option
  (** [find dir fn] returns the full path to [fn] in [dir]. *)

  val find_normalized : t -> string -> string option
  (** As {!find}, but search also for uncapitalized name, i.e. if name is
      Foo.ml, either /path/Foo.ml or /path/foo.ml may be returned. *)
end

type auto_include_callback =
  (Dir.t -> string -> string option) -> string -> string
(** The type of callback functions on for [init ~auto_include] *)

val no_auto_include : auto_include_callback
(** No automatic directory inclusion: misses in the load path raise [Not_found]
    as normal. *)

val init :
  auto_include:auto_include_callback -> visible:string list ->
  hidden:string list -> unit
(** [init ~visible ~hidden] is the same as
    [reset ();
     List.iter add_dir (List.rev hidden);
     List.iter add_dir (List.rev visible)] *)

val auto_include_otherlibs :
  (string -> unit) -> auto_include_callback
(** [auto_include_otherlibs alert] is a callback function to be passed to
    {!Load_path.init} and automatically adds [-I +lib] to the load path after
    calling [alert lib]. *)

val get_path_list : unit -> string list
(** Return the list of directories passed to [add_dir] so far. *)

type paths =
  { visible : string list;
    hidden : string list }

val get_paths : unit -> paths
(** Return the directories passed to [add_dir] so far. *)

val find : string -> string
(** Locate a file in the load path. Raise [Not_found] if the file
    cannot be found. This function is optimized for the case where the
    filename is a basename, i.e. doesn't contain a directory
    separator. *)

val find_normalized : string -> string
(** Same as [find], but search also for normalized unit name (see
    {!Misc.normalized_unit_filename}), i.e. if name is [Foo.ml], allow
    [/path/Foo.ml] and [/path/foo.ml] to match. *)

type visibility = Visible | Hidden

val find_normalized_with_visibility : string -> string * visibility
(** Same as [find_normalized], but also reports whether the cmi was found in a
    -I directory (Visible) or a -H directory (Hidden) *)

val[@deprecated] add : Dir.t -> unit
(** Old name for {!append_dir} *)

val append_dir : Dir.t -> unit
(** [append_dir d] adds [d] to the end of the load path (i.e. at lowest
    priority. *)

val prepend_dir : Dir.t -> unit
(** [prepend_dir d] adds [d] to the start of the load path (i.e. at highest
    priority. *)

val get_visible : unit -> Dir.t list
(** Same as [get_paths ()], except that it returns a [Dir.t list], and doesn't
    include the -H paths. *)