summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2014-05-02 07:07:09 +0000
committerJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2014-05-02 07:07:09 +0000
commitb78b19975ab8d9e4959b92e2b5a0661d97b0cdde (patch)
tree5cc641768ca414029f1ee3d47b030688356b3469
parent95104b392443a02c733c3354db7062761e5a1a9c (diff)
* Do not require cmi file to be present if module alias is not accessed
(using -trans-mod) * Add warning 49 for that case; use same warning in place of deprecated for Env.scrape_alias git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14724 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--typing/env.ml13
-rw-r--r--utils/warnings.ml13
-rw-r--r--utils/warnings.mli1
3 files changed, 17 insertions, 10 deletions
diff --git a/typing/env.ml b/typing/env.ml
index 7e904fc9f..4517143b6 100644
--- a/typing/env.ml
+++ b/typing/env.ml
@@ -639,7 +639,11 @@ and lookup_module lid env : Path.t =
p
with Not_found ->
if s = !current_unit then raise Not_found;
- ignore (find_pers_struct ~check:false s);
+ if !Clflags.transparent_modules then
+ try ignore (find_in_path_uncap !load_path (s ^ ".cmi"))
+ with Not_found ->
+ Location.prerr_warning Location.none (Warnings.No_cmi_file s)
+ else ignore (find_pers_struct ~check:false s);
Pident(Ident.create_persistent s)
end
| Ldot(l, s) ->
@@ -1021,8 +1025,7 @@ let rec scrape_alias env ?path mty =
scrape_alias env (find_module path env).md_type ~path
with Not_found ->
Location.prerr_warning Location.none
- (Warnings.Deprecated
- ("module " ^ Path.name path ^ " cannot be accessed"));
+ (Warnings.No_cmi_file (Path.name path));
mty
end
| mty, Some path ->
@@ -1337,9 +1340,7 @@ and store_exception ~check slot id path decl env renv =
(fun () ->
if not env.in_signature && not used.cu_positive then
Location.prerr_warning loc
- (Warnings.Unused_exception
- (c, used.cu_pattern)
- )
+ (Warnings.Unused_exception (c, used.cu_pattern))
)
end;
end;
diff --git a/utils/warnings.ml b/utils/warnings.ml
index 58d275396..e2fa20232 100644
--- a/utils/warnings.ml
+++ b/utils/warnings.ml
@@ -66,6 +66,7 @@ type t =
| Bad_env_variable of string * string (* 46 *)
| Attribute_payload of string * string (* 47 *)
| Eliminated_optional_arguments of string list (* 48 *)
+ | No_cmi_file of string (* 49 *)
;;
(* If you remove a warning, leave a hole in the numbering. NEVER change
@@ -123,9 +124,10 @@ let number = function
| Bad_env_variable _ -> 46
| Attribute_payload _ -> 47
| Eliminated_optional_arguments _ -> 48
+ | No_cmi_file _ -> 49
;;
-let last_warning_number = 48
+let last_warning_number = 49
(* Must be the max number returned by the [number] function. *)
let letter = function
@@ -366,6 +368,8 @@ let message = function
Printf.sprintf "implicit elimination of optional argument%s %s"
(if List.length sl = 1 then "" else "s")
(String.concat ", " sl)
+ | No_cmi_file s ->
+ "no cmi file was found in path for module " ^ s
;;
let nerrors = ref 0;;
@@ -457,9 +461,10 @@ let descriptions =
43, "Nonoptional label applied as optional.";
44, "Open statement shadows an already defined identifier.";
45, "Open statement shadows an already defined label or constructor.";
- 46, "Illegal environment variable";
- 47, "Illegal attribute payload";
- 48, "Implicit elimination of optional arguments";
+ 46, "Illegal environment variable.";
+ 47, "Illegal attribute payload.";
+ 48, "Implicit elimination of optional arguments.";
+ 49, "Absent cmi file when looking up module alias.";
]
;;
diff --git a/utils/warnings.mli b/utils/warnings.mli
index 05bf66bde..a26291e46 100644
--- a/utils/warnings.mli
+++ b/utils/warnings.mli
@@ -61,6 +61,7 @@ type t =
| Bad_env_variable of string * string (* 46 *)
| Attribute_payload of string * string (* 47 *)
| Eliminated_optional_arguments of string list (* 48 *)
+ | No_cmi_file of string (* 49 *)
;;
val parse_options : bool -> string -> unit;;