diff options
author | Alain Frisch <alain@frisch.fr> | 2013-04-16 08:59:09 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2013-04-16 08:59:09 +0000 |
commit | ecb088015f66fc880c52e5c8b921e11330c5a1cd (patch) | |
tree | b3b153a193c9b939c5a2be752aab98f180773b42 /ocamldoc | |
parent | da659396416acc512df6529085f8984ef4d7208b (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 'ocamldoc')
-rw-r--r-- | ocamldoc/odoc_ast.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_env.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_print.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_sig.ml | 10 | ||||
-rw-r--r-- | ocamldoc/odoc_str.ml | 2 |
5 files changed, 11 insertions, 11 deletions
diff --git a/ocamldoc/odoc_ast.ml b/ocamldoc/odoc_ast.ml index fb4192920..bef106f77 100644 --- a/ocamldoc/odoc_ast.ml +++ b/ocamldoc/odoc_ast.ml @@ -200,7 +200,7 @@ module Typedtree_search = let rec iter = function Types.Cty_constr (_, _, cty) -> iter cty | Types.Cty_signature s -> s - | Types.Cty_fun (_,_, cty) -> iter cty + | Types.Cty_arrow (_,_, cty) -> iter cty in fun ct_decl -> iter ct_decl.Types.clty_type diff --git a/ocamldoc/odoc_env.ml b/ocamldoc/odoc_env.ml index f4d1b7ce1..d6a595bd7 100644 --- a/ocamldoc/odoc_env.ml +++ b/ocamldoc/odoc_env.ml @@ -238,9 +238,9 @@ let subst_class_type env t = | Types.Cty_signature cs -> (* on ne s'occupe pas des vals et methods *) t - | Types.Cty_fun (l, texp, ct) -> + | Types.Cty_arrow (l, texp, ct) -> let new_texp = subst_type env texp in let new_ct = iter ct in - Types.Cty_fun (l, new_texp, new_ct) + Types.Cty_arrow (l, new_texp, new_ct) in iter t diff --git a/ocamldoc/odoc_print.ml b/ocamldoc/odoc_print.ml index a62832fdb..d09bc9324 100644 --- a/ocamldoc/odoc_print.ml +++ b/ocamldoc/odoc_print.ml @@ -90,9 +90,9 @@ let simpl_class_type t = Types.cty_concr = Types.Concr.empty ; Types.cty_inher = [] } - | Types.Cty_fun (l, texp, ct) -> + | Types.Cty_arrow (l, texp, ct) -> let new_ct = iter ct in - Types.Cty_fun (l, texp, new_ct) + Types.Cty_arrow (l, texp, new_ct) in iter t diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml index 7600e7272..c8a4e4aed 100644 --- a/ocamldoc/odoc_sig.ml +++ b/ocamldoc/odoc_sig.ml @@ -450,7 +450,7 @@ module Analyser = ic | Parsetree.Pcty_signature _ - | Parsetree.Pcty_fun _ -> + | Parsetree.Pcty_arrow _ -> (* we don't have a name for the class signature, so we call it "object ... end" *) { ic_name = Odoc_messages.object_end ; @@ -1235,7 +1235,7 @@ module Analyser = in ([], Class_structure (inher_l, ele)) - | (Parsetree.Pcty_fun (parse_label, _, pclass_type), Types.Cty_fun (label, type_expr, class_type)) -> + | (Parsetree.Pcty_arrow (parse_label, _, pclass_type), Types.Cty_arrow (label, type_expr, class_type)) -> (* label = string. Dans les signatures, pas de nom de parametres a l'interieur des tuples *) (* si label = "", pas de label. ici on a l'information pour savoir si on a un label explicite. *) if parse_label = label then @@ -1252,7 +1252,7 @@ module Analyser = ) else ( - raise (Failure "Parsetree.Pcty_fun (parse_label, _, pclass_type), labels differents") + raise (Failure "Parsetree.Pcty_arrow (parse_label, _, pclass_type), labels differents") ) | _ -> @@ -1286,8 +1286,8 @@ module Analyser = in Class_signature (inher_l, ele) - | (Parsetree.Pcty_fun (parse_label, _, pclass_type), Types.Cty_fun (label, type_expr, class_type)) -> - raise (Failure "analyse_class_type_kind : Parsetree.Pcty_fun (...) with Types.Cty_fun (...)") + | (Parsetree.Pcty_arrow (parse_label, _, pclass_type), Types.Cty_arrow (label, type_expr, class_type)) -> + raise (Failure "analyse_class_type_kind : Parsetree.Pcty_arrow (...) with Types.Cty_arrow (...)") (* | (Parsetree.Pcty_constr (longident, _) (*of Longident.t * core_type list *), Types.Cty_signature class_signature) -> diff --git a/ocamldoc/odoc_str.ml b/ocamldoc/odoc_str.ml index 5f3a8e9e7..b36ad9596 100644 --- a/ocamldoc/odoc_str.ml +++ b/ocamldoc/odoc_str.ml @@ -125,7 +125,7 @@ let string_of_class_type_param_list l = let string_of_class_params c = let b = Buffer.create 256 in let rec iter = function - Types.Cty_fun (label, t, ctype) -> + Types.Cty_arrow (label, t, ctype) -> let parent = is_arrow_type t in Printf.bprintf b "%s%s%s%s -> " ( |