diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml index e2008e70d..9146fa25d 100644 --- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml +++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml @@ -319,9 +319,9 @@ module Make (Ast : Sig.Camlp4Ast) = struct | _ -> assert False (*FIXME*) ]; value mkvariant = fun - [ <:ctyp@loc< $uid:s$ >> -> (conv_con s, [], None, mkloc loc) + [ <:ctyp@loc< $uid:s$ >> -> (conv_con s, [], mkloc loc) | <:ctyp@loc< $uid:s$ of $t$ >> -> - (conv_con s, List.map ctyp (list_of_ctyp t []), None, mkloc loc) + (conv_con s, List.map ctyp (list_of_ctyp t []), mkloc loc) | _ -> assert False (*FIXME*) ]; value rec type_decl tl cl loc m pflag = fun @@ -381,14 +381,6 @@ module Make (Ast : Sig.Camlp4Ast) = struct | <:ctyp< '$s$ >> -> [(s, (False, False)) :: acc] | _ -> assert False ]; - value rec optional_type_parameters t acc = - match t with - [ <:ctyp< $t1$ $t2$ >> -> optional_type_parameters t1 (optional_type_parameters t2 acc) - | <:ctyp< +'$s$ >> -> [(Some s, (True, False)) :: acc] - | <:ctyp< -'$s$ >> -> [(Some s, (False, True)) :: acc] - | <:ctyp< '$s$ >> -> [(Some s, (False, False)) :: acc] - | _ -> assert False ]; - value rec class_parameters t acc = match t with [ <:ctyp< $t1$, $t2$ >> -> class_parameters t1 (class_parameters t2 acc) @@ -401,7 +393,7 @@ module Make (Ast : Sig.Camlp4Ast) = struct match t with [ <:ctyp< $t1$ $t2$ >> -> type_parameters_and_type_name t1 - (optional_type_parameters t2 acc) + (type_parameters t2 acc) | <:ctyp< $id:i$ >> -> (ident i, acc) | _ -> assert False ]; @@ -853,7 +845,7 @@ module Make (Ast : Sig.Camlp4Ast) = struct (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 type_parameters tl []) cl td) :: acc] | _ -> assert False ] and module_type = fun diff --git a/camlp4/Camlp4Top/Rprint.ml b/camlp4/Camlp4Top/Rprint.ml index 6d1adac07..978397d89 100644 --- a/camlp4/Camlp4Top/Rprint.ml +++ b/camlp4/Camlp4Top/Rprint.ml @@ -234,14 +234,10 @@ and print_simple_out_type ppf = fprintf ppf "@[<1>(%a)@]" print_out_type ty ] in print_tkind ppf -and print_out_constr ppf (name, tyl, ret) = - match (tyl,ret) with - [ ([], None) -> fprintf ppf "%s" name - | ([], Some r) -> fprintf ppf "@[<2>%s:@ %a@]" name print_out_type r - | (_,Some r) -> - fprintf ppf "@[<2>%s:@ %a -> %a@]" name - (print_typlist print_out_type " and") tyl print_out_type r - | (_,None) -> +and print_out_constr ppf (name, tyl) = + match tyl with + [ [] -> fprintf ppf "%s" name + | _ -> fprintf ppf "@[<2>%s of@ %a@]" name (print_typlist print_out_type " and") tyl ] and print_out_label ppf (name, mut, arg) = @@ -372,7 +368,7 @@ and print_out_sig_item ppf = (if vir_flag then " virtual" else "") print_out_class_params params name Toploop.print_out_class_type.val clt | Osig_exception id tyl -> - fprintf ppf "@[<2>exception %a@]" print_out_constr (id, tyl,None) + fprintf ppf "@[<2>exception %a@]" print_out_constr (id, tyl) | Osig_modtype name Omty_abstract -> fprintf ppf "@[<2>module type %s@]" name | Osig_modtype name mty -> diff --git a/camlp4/boot/Camlp4.ml b/camlp4/boot/Camlp4.ml index 2d361fe66..8d65f3446 100644 --- a/camlp4/boot/Camlp4.ml +++ b/camlp4/boot/Camlp4.ml @@ -14547,9 +14547,9 @@ module Struct = let mkvariant = function | Ast.TyId (loc, (Ast.IdUid (_, s))) -> - ((conv_con s), [], None, (mkloc loc)) + ((conv_con s), [], (mkloc loc)) | Ast.TyOf (loc, (Ast.TyId (_, (Ast.IdUid (_, s)))), t) -> - ((conv_con s), (List.map ctyp (list_of_ctyp t [])), None, + ((conv_con s), (List.map ctyp (list_of_ctyp t [])), (mkloc loc)) | _ -> assert false @@ -14616,16 +14616,6 @@ module Struct = | Ast.TyQuM (_, s) -> (s, (false, true)) :: acc | Ast.TyQuo (_, s) -> (s, (false, false)) :: acc | _ -> assert false - - let rec optional_type_parameters t acc = - match t with - | Ast.TyApp (_, t1, t2) -> - optional_type_parameters t1 (optional_type_parameters t2 acc) - | Ast.TyQuP (_, s) -> (Some s, (true, false)) :: acc - | Ast.TyQuM (_, s) -> (Some s, (false, true)) :: acc - | Ast.TyQuo (_, s) -> (Some s, (false, false)) :: acc - | _ -> assert false - let rec class_parameters t acc = match t with @@ -14639,7 +14629,7 @@ module Struct = let rec type_parameters_and_type_name t acc = match t with | Ast.TyApp (_, t1, t2) -> - type_parameters_and_type_name t1 (optional_type_parameters t2 acc) + type_parameters_and_type_name t1 (type_parameters t2 acc) | Ast.TyId (_, i) -> ((ident i), acc) | _ -> assert false @@ -15209,7 +15199,7 @@ module Struct = cl in (c, - (type_decl (List.fold_right optional_type_parameters tl []) cl td)) :: + (type_decl (List.fold_right type_parameters tl []) cl td)) :: acc | _ -> assert false and module_type =