From b4d4bd4a9858654ea232ce64bb3d6fb57906032c Mon Sep 17 00:00:00 2001 From: octachron Date: Tue, 10 Oct 2017 22:31:05 +0200 Subject: [PATCH] ocamldep: expand few names --- parsing/depend.ml | 30 +++++++++++++++--------------- 1 file changed, 15 insertions(+), 15 deletions(-) diff --git a/parsing/depend.ml b/parsing/depend.ml index a6b4e8528..9e872fbc4 100644 --- a/parsing/depend.ml +++ b/parsing/depend.ml @@ -87,7 +87,7 @@ let add_parent bv lid = let add = add_parent -let addmodule bv lid = add_path bv lid.txt +let add_module_path bv lid = add_path bv lid.txt let handle_extension ext = match (fst ext).txt with @@ -266,7 +266,7 @@ let rec add_expr bv exp = | Pexp_object { pcstr_self = pat; pcstr_fields = fieldl } -> let bv = add_pattern bv pat in List.iter (add_class_field bv) fieldl | Pexp_newtype (_, e) -> add_expr bv e - | Pexp_pack m -> add_module bv m + | Pexp_pack m -> add_module_expr bv m | Pexp_open (_ovf, m, e) -> let bv = open_module bv m.txt in add_expr bv e | Pexp_extension (({ txt = ("ocaml.extension_constructor"| @@ -296,7 +296,7 @@ and add_bindings recf bv pel = and add_modtype bv mty = match mty.pmty_desc with Pmty_ident l -> add bv l - | Pmty_alias l -> addmodule bv l + | Pmty_alias l -> add_module_path bv l | Pmty_signature s -> add_signature bv s | Pmty_functor(id, mty1, mty2) -> Misc.may (add_modtype bv) mty1; @@ -306,24 +306,24 @@ and add_modtype bv mty = List.iter (function | Pwith_type (_, td) -> add_type_declaration bv td - | Pwith_module (_, lid) -> addmodule bv lid + | Pwith_module (_, lid) -> add_module_path bv lid | Pwith_typesubst (_, td) -> add_type_declaration bv td - | Pwith_modsubst (_, lid) -> addmodule bv lid + | Pwith_modsubst (_, lid) -> add_module_path bv lid ) cstrl - | Pmty_typeof m -> add_module bv m + | Pmty_typeof m -> add_module_expr bv m | Pmty_extension e -> handle_extension e and add_module_alias bv l = (* If we are in delayed dependencies mode, we delay the dependencies induced by "Lident s" *) - (if !Clflags.transparent_modules then add_parent else addmodule) bv l; + (if !Clflags.transparent_modules then add_parent else add_module_path) bv l; try lookup_map l.txt bv with Not_found -> match l.txt with Lident s -> make_leaf s - | _ -> addmodule bv l; bound (* cannot delay *) + | _ -> add_module_path bv l; bound (* cannot delay *) and add_modtype_binding bv mty = match mty.pmty_desc with @@ -391,19 +391,19 @@ and add_module_binding bv modl = Pmod_ident l -> add_module_alias bv l | Pmod_structure s -> make_node (snd @@ add_structure_binding bv s) - | _ -> add_module bv modl; bound + | _ -> add_module_expr bv modl; bound -and add_module bv modl = +and add_module_expr bv modl = match modl.pmod_desc with - Pmod_ident l -> addmodule bv l + Pmod_ident l -> add_module_path bv l | Pmod_structure s -> ignore (add_structure bv s) | Pmod_functor(id, mty, modl) -> Misc.may (add_modtype bv) mty; - add_module (StringMap.add id.txt bound bv) modl + add_module_expr (StringMap.add id.txt bound bv) modl | Pmod_apply(mod1, mod2) -> - add_module bv mod1; add_module bv mod2 + add_module_expr bv mod1; add_module_expr bv mod2 | Pmod_constraint(modl, mty) -> - add_module bv modl; add_modtype bv mty + add_module_expr bv modl; add_modtype bv mty | Pmod_unpack(e) -> add_expr bv e | Pmod_extension e -> @@ -442,7 +442,7 @@ and add_struct_item (bv, m) item : _ StringMap.t * _ StringMap.t = in let bv' = add bv and m = add m in List.iter - (fun x -> add_module bv' x.pmb_expr) + (fun x -> add_module_expr bv' x.pmb_expr) bindings; (bv', m) | Pstr_modtype x ->