summaryrefslogtreecommitdiffstats
path: root/camlp4
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2013-04-16 08:59:09 +0000
committerAlain Frisch <alain@frisch.fr>2013-04-16 08:59:09 +0000
commitecb088015f66fc880c52e5c8b921e11330c5a1cd (patch)
treeb3b153a193c9b939c5a2be752aab98f180773b42 /camlp4
parentda659396416acc512df6529085f8984ef4d7208b (diff)
Rename Pcty_fun to Pcty_arrow (and idem in Types, Typedtree, Outcometree) to be coherent with Ptyp_arrow.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/extension_points@13536 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4')
-rw-r--r--camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml6
-rw-r--r--camlp4/Camlp4Top/Rprint.ml2
-rw-r--r--camlp4/boot/Camlp4.ml6
3 files changed, 7 insertions, 7 deletions
diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
index 8886a88bd..75bd975c0 100644
--- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
+++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
@@ -1095,11 +1095,11 @@ value varify_constructors var_names =
mkcty loc
(Pcty_constr (long_class_ident id) (List.map ctyp (list_of_opt_ctyp tl [])))
| CtFun loc (TyLab _ lab t) ct ->
- mkcty loc (Pcty_fun lab (ctyp t) (class_type ct))
+ mkcty loc (Pcty_arrow lab (ctyp t) (class_type ct))
| CtFun loc (TyOlb loc1 lab t) ct ->
let t = TyApp loc1 (predef_option loc1) t in
- mkcty loc (Pcty_fun ("?" ^ lab) (ctyp t) (class_type ct))
- | CtFun loc t ct -> mkcty loc (Pcty_fun "" (ctyp t) (class_type ct))
+ mkcty loc (Pcty_arrow ("?" ^ lab) (ctyp t) (class_type ct))
+ | CtFun loc t ct -> mkcty loc (Pcty_arrow "" (ctyp t) (class_type ct))
| CtSig loc t_o ctfl ->
let t =
match t_o with
diff --git a/camlp4/Camlp4Top/Rprint.ml b/camlp4/Camlp4Top/Rprint.ml
index 9e49aa0f5..0840c2892 100644
--- a/camlp4/Camlp4Top/Rprint.ml
+++ b/camlp4/Camlp4Top/Rprint.ml
@@ -329,7 +329,7 @@ value rec print_out_class_type ppf =
(print_typlist Toploop.print_out_type.val ",") tyl ]
in
fprintf ppf "@[%a%a@]" pr_tyl tyl print_ident id
- | Octy_fun lab ty cty ->
+ | Octy_arrow lab ty cty ->
fprintf ppf "@[%a[ %a ] ->@ %a@]" print_ty_label lab
Toploop.print_out_type.val ty print_out_class_type cty
| Octy_signature self_ty csil ->
diff --git a/camlp4/boot/Camlp4.ml b/camlp4/boot/Camlp4.ml
index 85257172d..db49cff1d 100644
--- a/camlp4/boot/Camlp4.ml
+++ b/camlp4/boot/Camlp4.ml
@@ -15483,14 +15483,14 @@ module Struct =
(Pcty_constr ((long_class_ident id),
(List.map ctyp (list_of_opt_ctyp tl []))))
| CtFun (loc, (TyLab (_, lab, t)), ct) ->
- mkcty loc (Pcty_fun (lab, (ctyp t), (class_type ct)))
+ mkcty loc (Pcty_arrow (lab, (ctyp t), (class_type ct)))
| CtFun (loc, (TyOlb (loc1, lab, t)), ct) ->
let t = TyApp (loc1, (predef_option loc1), t)
in
mkcty loc
- (Pcty_fun (("?" ^ lab), (ctyp t), (class_type ct)))
+ (Pcty_arrow (("?" ^ lab), (ctyp t), (class_type ct)))
| CtFun (loc, t, ct) ->
- mkcty loc (Pcty_fun ("", (ctyp t), (class_type ct)))
+ mkcty loc (Pcty_arrow ("", (ctyp t), (class_type ct)))
| CtSig (loc, t_o, ctfl) ->
let t =
(match t_o with | Ast.TyNil _ -> Ast.TyAny loc | t -> t) in