Skip to content

Commit 7c77ac2

Browse files
committed
ocamldep: expand few names
1 parent 12ac507 commit 7c77ac2

File tree

1 file changed

+15
-15
lines changed

1 file changed

+15
-15
lines changed

parsing/depend.ml

+15-15
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,7 @@ let add_parent bv lid =
8787

8888
let add = add_parent
8989

90-
let addmodule bv lid = add_path bv lid.txt
90+
let add_module_path bv lid = add_path bv lid.txt
9191

9292
let handle_extension ext =
9393
match (fst ext).txt with
@@ -266,7 +266,7 @@ let rec add_expr bv exp =
266266
| Pexp_object { pcstr_self = pat; pcstr_fields = fieldl } ->
267267
let bv = add_pattern bv pat in List.iter (add_class_field bv) fieldl
268268
| Pexp_newtype (_, e) -> add_expr bv e
269-
| Pexp_pack m -> add_module bv m
269+
| Pexp_pack m -> add_module_expr bv m
270270
| Pexp_open (_ovf, m, e) ->
271271
let bv = open_module bv m.txt in add_expr bv e
272272
| Pexp_extension (({ txt = ("ocaml.extension_constructor"|
@@ -296,7 +296,7 @@ and add_bindings recf bv pel =
296296
and add_modtype bv mty =
297297
match mty.pmty_desc with
298298
Pmty_ident l -> add bv l
299-
| Pmty_alias l -> addmodule bv l
299+
| Pmty_alias l -> add_module_path bv l
300300
| Pmty_signature s -> add_signature bv s
301301
| Pmty_functor(id, mty1, mty2) ->
302302
Misc.may (add_modtype bv) mty1;
@@ -306,24 +306,24 @@ and add_modtype bv mty =
306306
List.iter
307307
(function
308308
| Pwith_type (_, td) -> add_type_declaration bv td
309-
| Pwith_module (_, lid) -> addmodule bv lid
309+
| Pwith_module (_, lid) -> add_module_path bv lid
310310
| Pwith_typesubst (_, td) -> add_type_declaration bv td
311-
| Pwith_modsubst (_, lid) -> addmodule bv lid
311+
| Pwith_modsubst (_, lid) -> add_module_path bv lid
312312
)
313313
cstrl
314-
| Pmty_typeof m -> add_module bv m
314+
| Pmty_typeof m -> add_module_expr bv m
315315
| Pmty_extension e -> handle_extension e
316316

317317
and add_module_alias bv l =
318318
(* If we are in delayed dependencies mode, we delay the dependencies
319319
induced by "Lident s" *)
320-
(if !Clflags.transparent_modules then add_parent else addmodule) bv l;
320+
(if !Clflags.transparent_modules then add_parent else add_module_path) bv l;
321321
try
322322
lookup_map l.txt bv
323323
with Not_found ->
324324
match l.txt with
325325
Lident s -> make_leaf s
326-
| _ -> addmodule bv l; bound (* cannot delay *)
326+
| _ -> add_module_path bv l; bound (* cannot delay *)
327327

328328
and add_modtype_binding bv mty =
329329
match mty.pmty_desc with
@@ -391,19 +391,19 @@ and add_module_binding bv modl =
391391
Pmod_ident l -> add_module_alias bv l
392392
| Pmod_structure s ->
393393
make_node (snd @@ add_structure_binding bv s)
394-
| _ -> add_module bv modl; bound
394+
| _ -> add_module_expr bv modl; bound
395395

396-
and add_module bv modl =
396+
and add_module_expr bv modl =
397397
match modl.pmod_desc with
398-
Pmod_ident l -> addmodule bv l
398+
Pmod_ident l -> add_module_path bv l
399399
| Pmod_structure s -> ignore (add_structure bv s)
400400
| Pmod_functor(id, mty, modl) ->
401401
Misc.may (add_modtype bv) mty;
402-
add_module (StringMap.add id.txt bound bv) modl
402+
add_module_expr (StringMap.add id.txt bound bv) modl
403403
| Pmod_apply(mod1, mod2) ->
404-
add_module bv mod1; add_module bv mod2
404+
add_module_expr bv mod1; add_module_expr bv mod2
405405
| Pmod_constraint(modl, mty) ->
406-
add_module bv modl; add_modtype bv mty
406+
add_module_expr bv modl; add_modtype bv mty
407407
| Pmod_unpack(e) ->
408408
add_expr bv e
409409
| Pmod_extension e ->
@@ -442,7 +442,7 @@ and add_struct_item (bv, m) item : _ StringMap.t * _ StringMap.t =
442442
in
443443
let bv' = add bv and m = add m in
444444
List.iter
445-
(fun x -> add_module bv' x.pmb_expr)
445+
(fun x -> add_module_expr bv' x.pmb_expr)
446446
bindings;
447447
(bv', m)
448448
| Pstr_modtype x ->

0 commit comments

Comments
 (0)