Finish the match_case renaming and bootstrap

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7460 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Nicolas Pouillard 2006-06-30 07:24:45 +00:00
parent 2a68675a85
commit 1858d90145
10 changed files with 17 additions and 17 deletions

View File

@ -446,7 +446,7 @@ module type S = sig
value wcAnd_of_list : list with_constr -> with_constr;
value meApp_of_list : list module_expr -> module_expr;
value mbAnd_of_list : list module_binding -> module_binding;
value asOr_of_list : list match_case -> match_case;
value mcOr_of_list : list match_case -> match_case;
value idAcc_of_list : list ident -> ident;
value idApp_of_list : list ident -> ident;
value exSem_of_list : list expr -> expr;

View File

@ -179,13 +179,13 @@ module Make (Loc : Sig.Loc.S)
let _loc = loc_of_ident i in
<:ident< $i$ $idApp_of_list is$ >> ];
value rec asOr_of_list =
value rec mcOr_of_list =
fun
[ [] -> <:match_case@ghost<>>
| [x] -> x
| [x::xs] ->
let _loc = loc_of_match_case x in
<:match_case< $x$ | $asOr_of_list xs$ >> ];
<:match_case< $x$ | $mcOr_of_list xs$ >> ];
value rec mbAnd_of_list =
fun

View File

@ -534,12 +534,12 @@ module Make (Loc : Sig.Loc.S) : Sig.Camlp4Ast.S with module Loc = Loc =
| [ i ] -> i
| [ i :: is ] ->
let _loc = loc_of_ident i in Ast.IdApp _loc i (idApp_of_list is) ];
value rec asOr_of_list =
value rec mcOr_of_list =
fun
[ [] -> Ast.McNil ghost
| [ x ] -> x
| [ x :: xs ] ->
let _loc = loc_of_match_case x in Ast.McOr _loc x (asOr_of_list xs) ];
let _loc = loc_of_match_case x in Ast.McOr _loc x (mcOr_of_list xs) ];
value rec mbAnd_of_list =
fun
[ [] -> Ast.MbNil ghost

View File

@ -43,17 +43,17 @@ module Make (AstFilters : Camlp4.Sig.AstFilters.S) = struct
raise exc
} ] >>;
value rec map_match_rule =
value rec map_match_case =
fun
[ <:match_case@_loc< $m1$ | $m2$ >> ->
<:match_case< $map_match_rule m1$ | $map_match_rule m2$ >>
<:match_case< $map_match_case m1$ | $map_match_case m2$ >>
| <:match_case@_loc< $p$ when $w$ -> $e$ >> ->
<:match_case@_loc< $p$ when $w$ -> $add_debug_expr e$ >>
| m -> m ]
and map_expr =
fun
[ <:expr@_loc< fun [ $m$ ] >> -> <:expr< fun [ $map_match_rule m$ ] >>
[ <:expr@_loc< fun [ $m$ ] >> -> <:expr< fun [ $map_match_case m$ ] >>
| x -> x ];
register_str_item_filter (new Ast.c_expr map_expr)#str_item;

View File

@ -187,10 +187,10 @@ module Make (AstFilters : Camlp4.Sig.AstFilters.S) = struct
patt_of_constructor t2 (patt_of_constructor t1 (i, acc))
| _ -> (succ i, <:patt< $acc$ $lid:xi i$ >>) ]
and match_rule_of_sum_type =
and match_case_of_sum_type =
fun
[ <:ctyp< $t1$ | $t2$ >> ->
<:match_case< $match_rule_of_sum_type t1$ | $match_rule_of_sum_type t2$ >>
<:match_case< $match_case_of_sum_type t1$ | $match_case_of_sum_type t2$ >>
| <:ctyp< $uid:s$ of $t$ >> ->
<:match_case< $pat:snd (patt_of_constructor t (0, <:patt< $uid:s$ >>))$
-> $snd (expr_of_constructor t (0, <:expr< $uid:s$ >>))$ >>
@ -217,7 +217,7 @@ module Make (AstFilters : Camlp4.Sig.AstFilters.S) = struct
and fun_of_ctyp =
fun
[ <:ctyp< [ $t$ ] >> ->
<:expr< fun [ $match_rule_of_sum_type t$ ] >>
<:expr< fun [ $match_case_of_sum_type t$ ] >>
| <:ctyp< { $t$ } >> ->
<:expr< fun { $record_patt_of_type t$ } -> { $record_binding_of_type t$ } >>
| <:ctyp< ( $tup:t$ ) >> -> mk_tuple expr_of_ty t

View File

@ -38,17 +38,17 @@ module Make (AstFilters : Camlp4.Sig.AstFilters.S) = struct
else ();
$e$ } >>;
value rec map_match_rule =
value rec map_match_case =
fun
[ <:match_case@_loc< $m1$ | $m2$ >> ->
<:match_case< $map_match_rule m1$ | $map_match_rule m2$ >>
<:match_case< $map_match_case m1$ | $map_match_case m2$ >>
| <:match_case@_loc< $p$ when $w$ -> $e$ >> ->
<:match_case@_loc< $p$ when $w$ -> $add_debug_expr e$ >>
| m -> m ]
and map_expr =
fun
[ <:expr@_loc< fun [ $m$ ] >> -> <:expr< fun [ $map_match_rule m$ ] >>
[ <:expr@_loc< fun [ $m$ ] >> -> <:expr< fun [ $map_match_case m$ ] >>
| x -> x ];
register_str_item_filter (new Ast.c_expr map_expr)#str_item;

View File

@ -594,7 +594,7 @@ module Make (Syntax : Sig.Camlp4Syntax.S) = struct
| i = a_UIDENT; "."; j = SELF -> <:ident< $uid:i$.$j$ >> ] ]
;
match_case:
[ [ l = LIST1 match_case0 SEP "|" -> Ast.asOr_of_list l ] ]
[ [ l = LIST1 match_case0 SEP "|" -> Ast.mcOr_of_list l ] ]
;
(* Patterns *)
patt:

View File

@ -105,7 +105,7 @@ module Make (Syntax : Sig.Camlp4Syntax.S)
| "listident" -> <:expr< Ast.idAcc_of_list $e$ >>
| "listctypand" -> <:expr< Ast.tyAnd_of_list $e$ >>
| "listwith_constr" -> <:expr< Ast.wcAnd_of_list $e$ >>
| "listmatch_case" -> <:expr< Ast.asOr_of_list $e$ >>
| "listmatch_case" -> <:expr< Ast.mcOr_of_list $e$ >>
| "listpatt;" -> <:expr< Ast.paSem_of_list $e$ >>
| "antisig_item" -> <:expr< Ast.SgAnt $mloc _loc$ $e$ >>
| "antistr_item" -> <:expr< Ast.StAnt $mloc _loc$ $e$ >>

View File

@ -654,7 +654,7 @@ Old (no more supported) syntax:
| ":>"; t = ctyp; "="; e = expr -> <:expr< ($e$ :> $t$) >> ] ]
;
match_case:
[ [ l = LIST0 match_case0 SEP "|" -> Ast.asOr_of_list l ] ]
[ [ l = LIST0 match_case0 SEP "|" -> Ast.mcOr_of_list l ] ]
;
match_case0:
[ [ `ANTIQUOT ("match_case"|"list" as n) s ->

Binary file not shown.