diff options
Diffstat (limited to 'parsing')
-rw-r--r-- | parsing/ast_helper.ml | 1 | ||||
-rw-r--r-- | parsing/ast_helper.mli | 1 | ||||
-rw-r--r-- | parsing/ast_mapper.ml | 10 | ||||
-rw-r--r-- | parsing/parser.mly | 9 | ||||
-rw-r--r-- | parsing/parsetree.mli | 2 | ||||
-rw-r--r-- | parsing/pprintast.ml | 14 | ||||
-rw-r--r-- | parsing/printast.ml | 1 |
7 files changed, 31 insertions, 7 deletions
diff --git a/parsing/ast_helper.ml b/parsing/ast_helper.ml index ed49f65a3..6657d5349 100644 --- a/parsing/ast_helper.ml +++ b/parsing/ast_helper.ml @@ -125,6 +125,7 @@ module Mty = struct let attr d a = {d with pmty_attributes = d.pmty_attributes @ [a]} let ident ?loc ?attrs a = mk ?loc ?attrs (Pmty_ident a) + let alias ?loc ?attrs a = mk ?loc ?attrs (Pmty_alias a) let signature ?loc ?attrs a = mk ?loc ?attrs (Pmty_signature a) let functor_ ?loc ?attrs a b c = mk ?loc ?attrs (Pmty_functor (a, b, c)) let with_ ?loc ?attrs a b = mk ?loc ?attrs (Pmty_with (a, b)) diff --git a/parsing/ast_helper.mli b/parsing/ast_helper.mli index 441e420d1..331b33b52 100644 --- a/parsing/ast_helper.mli +++ b/parsing/ast_helper.mli @@ -144,6 +144,7 @@ module Mty: val attr: module_type -> attribute -> module_type val ident: ?loc:loc -> ?attrs:attrs -> lid -> module_type + val alias: ?loc:loc -> ?attrs:attrs -> lid -> module_type val signature: ?loc:loc -> ?attrs:attrs -> signature -> module_type val functor_: ?loc:loc -> ?attrs:attrs -> str -> module_type option -> module_type -> module_type diff --git a/parsing/ast_mapper.ml b/parsing/ast_mapper.ml index dac9cbe28..4cf8b84d6 100644 --- a/parsing/ast_mapper.ml +++ b/parsing/ast_mapper.ml @@ -159,6 +159,7 @@ module MT = struct let attrs = sub.attributes sub attrs in match desc with | Pmty_ident s -> ident ~loc ~attrs (map_loc sub s) + | Pmty_alias s -> alias ~loc ~attrs (map_loc sub s) | Pmty_signature sg -> signature ~loc ~attrs (sub.signature sub sg) | Pmty_functor (s, mt1, mt2) -> functor_ ~loc ~attrs (map_loc sub s) @@ -427,15 +428,18 @@ let default_mapper = signature_item = MT.map_signature_item; module_type = MT.map; with_constraint = MT.map_with_constraint; - class_declaration = (fun this -> CE.class_infos this (this.class_expr this)); + class_declaration = + (fun this -> CE.class_infos this (this.class_expr this)); class_expr = CE.map; class_field = CE.map_field; class_structure = CE.map_structure; class_type = CT.map; class_type_field = CT.map_field; class_signature = CT.map_signature; - class_type_declaration = (fun this -> CE.class_infos this (this.class_type this)); - class_description = (fun this -> CE.class_infos this (this.class_type this)); + class_type_declaration = + (fun this -> CE.class_infos this (this.class_type this)); + class_description = + (fun this -> CE.class_infos this (this.class_type this)); type_declaration = T.map_type_declaration; type_kind = T.map_type_kind; typ = T.map; diff --git a/parsing/parser.mly b/parsing/parser.mly index 7f23730f3..19d1fd6db 100644 --- a/parsing/parser.mly +++ b/parsing/parser.mly @@ -676,6 +676,8 @@ module_type: { mkmty(Pmty_with($1, List.rev $3)) } | MODULE TYPE OF module_expr %prec below_LBRACKETAT { mkmty(Pmty_typeof $4) } + | LPAREN MODULE mod_longident RPAREN + { mkmty (Pmty_alias (mkrhs $3 3)) } | LPAREN module_type RPAREN { $2 } | LPAREN module_type error @@ -701,7 +703,8 @@ signature_item: VAL val_ident COLON core_type post_item_attributes { mksig(Psig_value (Val.mk (mkrhs $2 2) $4 ~attrs:$5 ~loc:(symbol_rloc()))) } - | EXTERNAL val_ident COLON core_type EQUAL primitive_declaration post_item_attributes + | EXTERNAL val_ident COLON core_type EQUAL primitive_declaration + post_item_attributes { mksig(Psig_value (Val.mk (mkrhs $2 2) $4 ~prim:$6 ~attrs:$7 ~loc:(symbol_rloc()))) } @@ -711,6 +714,10 @@ signature_item: { mksig(Psig_exception $2) } | MODULE UIDENT module_declaration post_item_attributes { mksig(Psig_module (Md.mk (mkrhs $2 2) $3 ~attrs:$4)) } + | MODULE UIDENT EQUAL mod_longident post_item_attributes + { mksig(Psig_module (Md.mk (mkrhs $2 2) + (Mty.alias ~loc:(rhs_loc 4) (mkrhs $4 4)) + ~attrs:$5)) } | MODULE REC module_rec_declarations { mksig(Psig_recmodule (List.rev $3)) } | MODULE TYPE ident post_item_attributes diff --git a/parsing/parsetree.mli b/parsing/parsetree.mli index 57f4ae7f3..410d6657a 100644 --- a/parsing/parsetree.mli +++ b/parsing/parsetree.mli @@ -551,6 +551,8 @@ and module_type_desc = (* module type of ME *) | Pmty_extension of extension (* [%id] *) + | Pmty_alias of Longident.t loc + (* (module M) *) and signature = signature_item list diff --git a/parsing/pprintast.ml b/parsing/pprintast.ml index 050c9fe1c..12b8fce6c 100644 --- a/parsing/pprintast.ml +++ b/parsing/pprintast.ml @@ -831,6 +831,8 @@ class printer ()= object(self:'self) match x.pmty_desc with | Pmty_ident li -> pp f "%a" self#longident_loc li; + | Pmty_alias li -> + pp f "(module %a)" self#longident_loc li; | Pmty_signature (s) -> pp f "@[<hv0>@[<hv2>sig@ %a@]@ end@]" (* "@[<hov>sig@ %a@ end@]" *) (self#list self#signature_item ) s (* FIXME wrong indentation*) @@ -875,7 +877,8 @@ class printer ()= object(self:'self) pp f "@[<2>%a@]" (fun f vd -> let intro = if vd.pval_prim = [] then "val" else "external" in - if (is_infix (fixity_of_string vd.pval_name.txt)) || List.mem vd.pval_name.txt.[0] prefix_symbols then + if (is_infix (fixity_of_string vd.pval_name.txt)) + || List.mem vd.pval_name.txt.[0] prefix_symbols then pp f "%s@ (@ %s@ )@ :@ " intro vd.pval_name.txt else pp f "%s@ %s@ :@ " intro vd.pval_name.txt; @@ -893,8 +896,13 @@ class printer ()= object(self:'self) (fun f l -> match l with |[] ->() |[x] -> pp f "@[<2>class %a@]" class_description x - |_ -> self#list ~first:"@[<v0>class @[<2>" ~sep:"@]@;and @[" ~last:"@]@]" - class_description f l) l + |_ -> + self#list ~first:"@[<v0>class @[<2>" ~sep:"@]@;and @[" + ~last:"@]@]" class_description f l) + l + | Psig_module {pmd_name; pmd_type={pmty_desc=Pmty_alias alias}} -> + pp f "@[<hov>module@ %s@ =@ %a@]" + pmd_name.txt self#longident_loc alias | Psig_module pmd -> pp f "@[<hov>module@ %s@ :@ %a@]" pmd.pmd_name.txt diff --git a/parsing/printast.ml b/parsing/printast.ml index 5f396e784..48bfe9f5b 100644 --- a/parsing/printast.ml +++ b/parsing/printast.ml @@ -572,6 +572,7 @@ and module_type i ppf x = let i = i+1 in match x.pmty_desc with | Pmty_ident li -> line i ppf "Pmty_ident %a\n" fmt_longident_loc li; + | Pmty_alias li -> line i ppf "Pmty_alias %a\n" fmt_longident_loc li; | Pmty_signature (s) -> line i ppf "Pmty_signature\n"; signature i ppf s; |