summaryrefslogtreecommitdiffstats
path: root/camlp4/Camlp4/Struct
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2013-03-04 17:39:07 +0000
committerAlain Frisch <alain@frisch.fr>2013-03-04 17:39:07 +0000
commit8461db39f198ac6c898a9c873129d023092486da (patch)
tree3128274b8da71e7a6845815d7de5ec66f34e031c /camlp4/Camlp4/Struct
parenta5059464fee285ba0b73253ed873c5df92a633b2 (diff)
Attributes on module/module type/recursive module declarations in interfaces.
Module: [^^id expr] [^^id expr] ... module X : S [@@id expr] [@@id expr] ... Module types: [^^id expr] [^^id expr] ... module type X = S [@@id expr] [@@id expr] ... Recursive modules: module rec [^^id expr] [^^id expr] X1 : S1 [@@id expr] [@@id expr] ... and [^^id expr] [^^id expr] X1 : S1 [@@id expr] [@@id expr] ... git-svn-id: http://caml.inria.fr/svn/ocaml/branches/extension_points@13344 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4/Camlp4/Struct')
-rw-r--r--camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml6
1 files changed, 3 insertions, 3 deletions
diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
index 308d44d44..f21d55b62 100644
--- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
+++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
@@ -1002,7 +1002,7 @@ value varify_constructors var_names =
| SgExc _ _ -> assert False (*FIXME*)
| SgExt loc n t sl -> [mksig loc (Psig_value (with_loc n loc) (mkvalue_desc loc t (list_of_meta_list sl))) :: l]
| SgInc loc mt -> [mksig loc (Psig_include (module_type mt) []) :: l]
- | SgMod loc n mt -> [mksig loc (Psig_module (with_loc n loc) (module_type mt)) :: l]
+ | SgMod loc n mt -> [mksig loc (Psig_module {pmd_name=with_loc n loc; pmd_type=module_type mt; pmd_attributes=[]}) :: l]
| SgRecMod loc mb ->
[mksig loc (Psig_recmodule (module_sig_binding mb [])) :: l]
| SgMty loc n mt ->
@@ -1011,7 +1011,7 @@ value varify_constructors var_names =
[ MtQuo _ _ -> Pmodtype_abstract
| _ -> Pmodtype_manifest (module_type mt) ]
in
- [mksig loc (Psig_modtype (with_loc n loc) si) :: l]
+ [mksig loc (Psig_modtype (with_loc n loc) si []) :: l]
| SgOpn loc id ->
[mksig loc (Psig_open (long_uident id) []) :: l]
| SgTyp loc tdl -> [mksig loc (Psig_type (mktype_decl tdl [])) :: l]
@@ -1022,7 +1022,7 @@ value varify_constructors var_names =
[ <:module_binding< $x$ and $y$ >> ->
module_sig_binding x (module_sig_binding y acc)
| <:module_binding@loc< $s$ : $mt$ >> ->
- [(with_loc s loc, module_type mt) :: acc]
+ [{pmd_name=with_loc s loc; pmd_type=module_type mt; pmd_attributes=[]} :: acc]
| _ -> assert False ]
and module_str_binding x acc =
match x with