diff options
author | Jérémie Dimino <jeremie@dimino.org> | 2011-12-20 17:40:23 +0000 |
---|---|---|
committer | Jérémie Dimino <jeremie@dimino.org> | 2011-12-20 17:40:23 +0000 |
commit | 8c16e88983a7788bc78a2bcf702b2b615852289a (patch) | |
tree | 0dcd935055e3f682561b9117ceb55a8f40ef964f | |
parent | dfcbd7fc56f0749ebe8bfcccac3323dab1bc5d8e (diff) |
PR#5374: be consistent for locations of type declarations between Camlp4 and the OCaml parser
Camlp4 used only the location of the rhs of type declarations, while
OCaml used the location of the whole type declaration. The location of
abstract types was then wrong when using Camlp4.
Thanks to furuse for his contribution.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11903 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml | 6 |
1 files changed, 3 insertions, 3 deletions
diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml index b1e1e4216..9e3a83ddb 100644 --- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml +++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml @@ -352,7 +352,7 @@ module Make (Ast : Sig.Camlp4Ast) = struct mktype loc tl cl Ptype_abstract (mkprivate' pflag) m ] ; - value type_decl tl cl t = type_decl tl cl (loc_of_ctyp t) None False t; + value type_decl tl cl t loc = type_decl tl cl loc None False t; value mkvalue_desc t p = {pval_type = ctyp t; pval_prim = p}; @@ -936,7 +936,7 @@ value varify_constructors var_names = match x with [ <:ctyp< $x$ and $y$ >> -> mktype_decl x (mktype_decl y acc) - | Ast.TyDcl _ c tl td cl -> + | Ast.TyDcl loc c tl td cl -> let cl = List.map (fun (t1, t2) -> @@ -944,7 +944,7 @@ value varify_constructors var_names = (ctyp t1, ctyp t2, mkloc loc)) cl in - [(c, type_decl (List.fold_right optional_type_parameters tl []) cl td) :: acc] + [(c, type_decl (List.fold_right optional_type_parameters tl []) cl td loc) :: acc] | _ -> assert False ] and module_type = fun |