File: unit_info.mli

package info (click to toggle)
ocaml 5.3.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 43,124 kB
  • sloc: ml: 355,439; ansic: 51,636; sh: 25,098; asm: 5,413; makefile: 3,673; python: 919; javascript: 273; awk: 253; perl: 59; fortran: 21; cs: 9
file content (172 lines) | stat: -rw-r--r-- 6,629 bytes parent folder | download | duplicates (3)
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
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*             Florian Angeletti, projet Cambium, Inria Paris             *)
(*                                                                        *)
(*   Copyright 2023 Institut National de Recherche en Informatique et     *)
(*     en Automatique.                                                    *)
(*                                                                        *)
(*   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.          *)
(*                                                                        *)
(**************************************************************************)

(** This module centralize the handling of compilation files and their metadata.

  Maybe more importantly, this module provides functions for deriving module
  names from strings or filenames.
*)

(** {1:modname_from_strings Module name convention and computation} *)

type intf_or_impl = Intf | Impl
type modname = string
type filename = string
type file_prefix = string

type error = Invalid_encoding of filename
exception Error of error

(** [modulize s] capitalizes the first letter of [s]. *)
val modulize: string -> modname

(** [normalize s] uncapitalizes the first letter of [s]. *)
val normalize: string -> string

(** [lax_modname_from_source filename] is [modulize stem] where [stem] is the
    basename of the filename [filename] stripped from all its extensions.
    For instance, [modname_from_source "/pa.th/x.ml.pp"] is ["X"]. *)
val lax_modname_from_source: filename -> modname

(** Same as {!lax_modname_from_source} but raises an {!error.Invalid_encoding}
    error on filename with invalid utf8 encoding. *)
val strict_modname_from_source: filename -> modname

(** {2:module_name_validation Module name validation function}*)

(** [is_unit_name name] is true only if [name] can be used as a
    valid module name. *)
val is_unit_name : modname -> bool


(** {1:unit_info Metadata for compilation unit} *)

type t
(**  Metadata for a compilation unit:
    - the module name associated to the unit
    - the filename prefix (dirname + basename with all extensions stripped)
      for compilation artifacts
    - the input source file
    For instance, when calling [ocamlopt dir/x.mli -o target/y.cmi],
    - the input source file is [dir/x.mli]
    - the module name is [Y]
    - the prefix is [target/y]
*)

(** [source_file u] is the source file of [u]. *)
val source_file: t -> filename

(** [prefix u] is the filename prefix of the unit. *)
val prefix: t -> file_prefix

(** [modname u] or [artifact_modname a] is the module name of the unit
    or compilation artifact.*)
val modname: t -> modname

(** [kind u] is the kind (interface or implementation) of the unit. *)
val kind: t -> intf_or_impl

(** [check_unit_name u] prints a warning if the derived module name [modname u]
    should not be used as a module name as specified
    by {!is_unit_name}[ ~strict:true]. *)
val check_unit_name : t -> unit

(** [make ~check ~source_file kind prefix] associates both the
    [source_file] and the module name {!modname_from_source}[ target_prefix] to
    the prefix filesystem path [prefix].

   If [check_modname=true], this function emits a warning if the derived module
   name is not valid according to {!check_unit_name}.
*)
val make:
    ?check_modname:bool -> source_file:filename ->
    intf_or_impl -> file_prefix -> t

(** {1:artifact_function Build artifacts }*)
module Artifact: sig
  type t
(**  Metadata for a single compilation artifact:
    - the module name associated to the artifact
    - the filesystem path
    - the input source file if it exists
*)

   (** [source_file a] is the source file of [a] if it exists. *)
   val source_file: t -> filename option

  (** [prefix a] is the filename prefix of the compilation artifact. *)
   val prefix: t ->  file_prefix

   (** [filename u] is the filesystem path for a compilation artifact. *)
   val filename: t -> filename

   (** [modname a] is the module name of the compilation artifact.*)
   val modname: t -> modname

   (** [from_filename filename] reconstructs the module name
       [modname_from_source filename] associated to the artifact [filename]. *)
   val from_filename: filename -> t

end

(** {1:info_build_artifacts Derived build artifact metadata} *)

(** Those functions derive a specific [artifact] metadata from an [unit]
    metadata.*)
val cmi: t -> Artifact.t
val cmo: t -> Artifact.t
val cmx: t -> Artifact.t
val obj: t -> Artifact.t
val cmt: t -> Artifact.t
val cmti: t -> Artifact.t
val annot: t -> Artifact.t

(** The functions below change the type of an artifact by updating the
    extension of its filename.
    Those functions purposefully do not cover all artifact kinds because we want
    to track which artifacts are assumed to be bundled together. *)
val companion_obj: Artifact.t -> Artifact.t
val companion_cmt: Artifact.t -> Artifact.t

val companion_cmi: Artifact.t -> Artifact.t
(** Beware that [companion_cmi a] strips all extensions from the
 filename of [a] before adding the [".cmi"] suffix contrarily to
 the other functions which only remove the rightmost extension.
 In other words, the companion cmi of a file [something.d.cmo] is
 [something.cmi] and not [something.d.cmi].
*)

(** {1:ml_mli_cmi_interaction Mli and cmi derived from implementation files } *)

(** The compilation of module implementation changes in presence of mli and cmi
    files, the function belows help to handle this. *)

(** [mli_from_source u] is the interface source filename associated to the unit
    [u]. The actual suffix depends on {!Config.interface_suffix}.
*)
val mli_from_source: t -> filename

(** [mli_from_artifact t] is the name of the interface source file derived from
    the artifact [t]. This variant is necessary when handling artifacts derived
    from an unknown source files (e.g. packed modules). *)
val mli_from_artifact: Artifact.t -> filename

(** Check if the artifact is a cmi *)
val is_cmi: Artifact.t -> bool

(** [find_normalized_cmi u] finds in the load_path a file matching the module
    name [modname u].
    @raise Not_found if no such cmi exists *)
val find_normalized_cmi: t -> Artifact.t