diff options
author | Daniel de Rauglaudre <daniel.de_rauglaudre@inria.fr> | 2001-10-02 13:56:17 +0000 |
---|---|---|
committer | Daniel de Rauglaudre <daniel.de_rauglaudre@inria.fr> | 2001-10-02 13:56:17 +0000 |
commit | c64ae7844aaea340e7299ebcee9267e5167be257 (patch) | |
tree | a12b64de8392e538b2283e757d614470971024b1 | |
parent | 147be549acd7f5a99bc5d0924bc0ed55539b01da (diff) |
-
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3831 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | camlp4/camlp4/ast2pt.ml | 21 | ||||
-rw-r--r-- | camlp4/camlp4/mLast.mli | 15 | ||||
-rw-r--r-- | camlp4/camlp4/reloc.ml | 16 | ||||
-rw-r--r-- | camlp4/etc/pr_depend.ml | 3 | ||||
-rw-r--r-- | camlp4/etc/pr_o.ml | 15 | ||||
-rw-r--r-- | camlp4/etc/pr_r.ml | 17 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/ast2pt.ml | 11 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/mLast.mli | 5 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/reloc.ml | 5 |
9 files changed, 25 insertions, 83 deletions
diff --git a/camlp4/camlp4/ast2pt.ml b/camlp4/camlp4/ast2pt.ml index 0c361bdbd..7a6fa51d7 100644 --- a/camlp4/camlp4/ast2pt.ml +++ b/camlp4/camlp4/ast2pt.ml @@ -171,9 +171,7 @@ value rec ctyp = | Some None -> (False, None) | Some (Some sl) -> (True, Some sl) ] in - mktyp loc (Ptyp_variant catl clos sl) - | TyXnd loc c _ -> - error loc ("type \"" ^ c ^ "\" (extension) not allowed here") ] + mktyp loc (Ptyp_variant catl clos sl) ] and meth_list loc fl v = match fl with [ [] -> if v then [mkfield loc Pfield_var] else [] @@ -381,9 +379,7 @@ value rec patt = | PaUid loc s -> let ca = not no_constructors_arity.val in mkpat loc (Ppat_construct (lident (conv_con s)) None ca) - | PaVrn loc s -> mkpat loc (Ppat_variant s None) - | PaXnd loc c _ -> - error loc ("pattern \"" ^ c ^ "\" (extension) not allowed here") ] + | PaVrn loc s -> mkpat loc (Ppat_variant s None) ] and mklabpat (lab, p) = (patt_label_long_id lab, patt p); value rec expr_fa al = @@ -547,9 +543,7 @@ value rec expr = | ExVrn loc s -> mkexp loc (Pexp_variant s None) | ExWhi loc e1 el -> let e2 = ExSeq loc el in - mkexp loc (Pexp_while (expr e1) (expr e2)) - | ExXnd loc c _ -> - error loc ("expression \"" ^ c ^ "\" (extension) not allowed here") ] + mkexp loc (Pexp_while (expr e1) (expr e2)) ] and label_expr = fun [ ExLab loc lab e -> (lab, expr e) @@ -658,9 +652,7 @@ and class_type = | None -> TyAny loc ] in let cil = List.fold_right class_sig_item ctfl [] in - mkcty loc (Pcty_signature (ctyp t, cil)) - | CtXnd loc c _ -> - error loc ("class type \"" ^ c ^ "\" (extension) not allowed here") ] + mkcty loc (Pcty_signature (ctyp t, cil)) ] and class_sig_item c l = match c with [ CgCtr loc t1 t2 -> [Pctf_cstr (ctyp t1, ctyp t2, mkloc loc) :: l] @@ -700,10 +692,7 @@ and class_expr = let cil = List.fold_right class_str_item cfl [] in mkpcl loc (Pcl_structure (patt p, cil)) | CeTyc loc ce ct -> - mkpcl loc (Pcl_constraint (class_expr ce) (class_type ct)) - | CeXnd loc c _ -> - error loc - ("class expression \"" ^ c ^ "\" (extension) not allowed here") ] + mkpcl loc (Pcl_constraint (class_expr ce) (class_type ct)) ] and class_str_item c l = match c with [ CrCtr loc t1 t2 -> [Pcf_cstr (ctyp t1, ctyp t2, mkloc loc) :: l] diff --git a/camlp4/camlp4/mLast.mli b/camlp4/camlp4/mLast.mli index 1d445d8f4..24a50b2db 100644 --- a/camlp4/camlp4/mLast.mli +++ b/camlp4/camlp4/mLast.mli @@ -33,8 +33,7 @@ type ctyp = | TySum of loc and list (string * list ctyp) | TyTup of loc and list ctyp | TyUid of loc and string - | TyVrn of loc and list row_field and option (option (list string)) - | TyXnd of loc and string and ctyp ] + | TyVrn of loc and list row_field and option (option (list string)) ] and row_field = [ RfTag of string and bool and list ctyp | RfInh of ctyp ] @@ -69,8 +68,7 @@ type patt = | PaTyc of loc and patt and ctyp | PaTyp of loc and list string | PaUid of loc and string - | PaVrn of loc and string - | PaXnd of loc and string and patt ] + | PaVrn of loc and string ] and expr = [ ExAcc of loc and expr and expr | ExAnt of loc and expr @@ -103,8 +101,7 @@ and expr = | ExTyc of loc and expr and ctyp | ExUid of loc and string | ExVrn of loc and string - | ExWhi of loc and expr and list expr - | ExXnd of loc and string and expr ] + | ExWhi of loc and expr and list expr ] and module_type = [ MtAcc of loc and module_type and module_type | MtApp of loc and module_type and module_type @@ -155,8 +152,7 @@ and type_decl = and class_type = [ CtCon of loc and list string and list ctyp | CtFun of loc and ctyp and class_type - | CtSig of loc and option ctyp and list class_sig_item - | CtXnd of loc and string and class_type ] + | CtSig of loc and option ctyp and list class_sig_item ] and class_sig_item = [ CgCtr of loc and ctyp and ctyp | CgDcl of loc and list class_sig_item @@ -170,8 +166,7 @@ and class_expr = | CeFun of loc and patt and class_expr | CeLet of loc and bool and list (patt * expr) and class_expr | CeStr of loc and option patt and list class_str_item - | CeTyc of loc and class_expr and class_type - | CeXnd of loc and string and class_expr ] + | CeTyc of loc and class_expr and class_type ] and class_str_item = [ CrCtr of loc and ctyp and ctyp | CrDcl of loc and list class_str_item diff --git a/camlp4/camlp4/reloc.ml b/camlp4/camlp4/reloc.ml index ae11ae577..388d1bbd9 100644 --- a/camlp4/camlp4/reloc.ml +++ b/camlp4/camlp4/reloc.ml @@ -43,8 +43,8 @@ value rec ctyp floc sh = (List.map (fun (x1, x2) -> (x1, List.map self x2)) x1) | TyTup loc x1 -> TyTup (floc loc) (List.map self x1) | TyUid loc x1 -> TyUid (floc loc) x1 - | TyVrn loc x1 x2 -> TyVrn (floc loc) (List.map (row_field floc sh) x1) x2 - | TyXnd loc x1 x2 -> TyXnd (floc loc) x1 (self x2) ] + | TyVrn loc x1 x2 -> + TyVrn (floc loc) (List.map (row_field floc sh) x1) x2 ] and row_field floc sh = fun [ RfTag x1 x2 x3 -> RfTag x1 x2 (List.map (ctyp floc sh) x3) @@ -85,8 +85,7 @@ value rec patt floc sh = | PaTyc loc x1 x2 -> PaTyc (floc loc) (self x1) (ctyp floc sh x2) | PaTyp loc x1 -> PaTyp (floc loc) x1 | PaUid loc x1 -> PaUid (floc loc) x1 - | PaVrn loc x1 -> PaVrn (floc loc) x1 - | PaXnd loc x1 x2 -> PaXnd (floc loc) x1 (self x2) ] + | PaVrn loc x1 -> PaVrn (floc loc) x1 ] and expr floc sh = self where rec self = fun @@ -147,8 +146,7 @@ and expr floc sh = | ExTyc loc x1 x2 -> ExTyc (floc loc) (self x1) (ctyp floc sh x2) | ExUid loc x1 -> ExUid (floc loc) x1 | ExVrn loc x1 -> ExVrn (floc loc) x1 - | ExWhi loc x1 x2 -> ExWhi (floc loc) (self x1) (List.map self x2) - | ExXnd loc x1 x2 -> ExXnd (floc loc) x1 (self x2) ] + | ExWhi loc x1 x2 -> ExWhi (floc loc) (self x1) (List.map self x2) ] and module_type floc sh = self where rec self = fun @@ -233,8 +231,7 @@ and class_type floc sh = | CtFun loc x1 x2 -> CtFun (floc loc) (ctyp floc sh x1) (self x2) | CtSig loc x1 x2 -> CtSig (floc loc) (option_map (ctyp floc sh) x1) - (List.map (class_sig_item floc sh) x2) - | CtXnd loc x1 x2 -> CtXnd (floc loc) x1 (self x2) ] + (List.map (class_sig_item floc sh) x2) ] and class_sig_item floc sh = self where rec self = fun @@ -258,8 +255,7 @@ and class_expr floc sh = | CeStr loc x1 x2 -> CeStr (floc loc) (option_map (patt floc sh) x1) (List.map (class_str_item floc sh) x2) - | CeTyc loc x1 x2 -> CeTyc (floc loc) (self x1) (class_type floc sh x2) - | CeXnd loc x1 x2 -> CeXnd (floc loc) x1 (self x2) ] + | CeTyc loc x1 x2 -> CeTyc (floc loc) (self x1) (class_type floc sh x2) ] and class_str_item floc sh = self where rec self = fun diff --git a/camlp4/etc/pr_depend.ml b/camlp4/etc/pr_depend.ml index 0a8773532..29b97d15e 100644 --- a/camlp4/etc/pr_depend.ml +++ b/camlp4/etc/pr_depend.ml @@ -52,7 +52,6 @@ value rec ctyp = | TySum _ cdl -> list constr_decl cdl | TyTup _ tl -> list ctyp tl | TyVrn _ sbtll _ -> list variant sbtll - | TyXnd _ _ t -> ctyp t | x -> not_impl "ctyp" x ] and constr_decl (_, tl) = list ctyp tl and label_decl (_, _, t) = ctyp t @@ -88,7 +87,6 @@ value rec patt = | PaTyc _ p t -> do { patt p; ctyp t; } | PaUid _ _ -> () | PaVrn _ _ -> () - | PaXnd _ _ p -> patt p | x -> not_impl "patt" x ] and patt_module = fun @@ -129,7 +127,6 @@ value rec expr = | ExUid _ _ -> () | ExVrn _ _ -> () | ExWhi _ e el -> do { expr e; list expr el; } - | ExXnd _ _ e -> expr e | x -> not_impl "expr" x ] and expr_module = fun diff --git a/camlp4/etc/pr_o.ml b/camlp4/etc/pr_o.ml index 385f16918..58a49f904 100644 --- a/camlp4/etc/pr_o.ml +++ b/camlp4/etc/pr_o.ml @@ -296,7 +296,6 @@ simple_ctyp_f.val := listws (fun x _ k -> HOVbox [: curr x "" k :]) (S RO ",") tl "" [: `S RO ")" :]; curr t "" k :] ] - | MLast.TyXnd _ c t -> [: `next t "" [: :]; `S LR ("Xnd_" ^ c) :] | t -> [: `next t "" k :] ]); level (fun x -> HOVbox x) (fun curr next t _ k -> @@ -341,8 +340,7 @@ simple_ctyp_f.val := | <:ctyp< $_$ -> $_$ >> | <:ctyp< $_$ $_$ >> | <:ctyp< $_$ == $_$ >> | <:ctyp< $_$ . $_$ >> | <:ctyp< ($list:_$) >> | <:ctyp< $_$ as $_$ >> | - <:ctyp< ~ $_$ : $_$ >> | <:ctyp< ? $_$ : $_$ >> | - MLast.TyXnd _ _ _ as t -> + <:ctyp< ~ $_$ : $_$ >> | <:ctyp< ? $_$ : $_$ >> as t -> [: `S LO "("; `ctyp t "" [: `HVbox [: `S RO ")"; k :] :] :] | MLast.TyCls _ id -> [: `S LO "#"; `class_longident id "" k :] | MLast.TyObj _ [] False -> [: `S LR "<>"; k :] @@ -1306,8 +1304,6 @@ pr_expr.pr_levels := | _ -> [: curr x "" [: :]; `next y "" k :] ] | MLast.ExNew _ sl -> fun curr next dg k -> [: `S LR "new"; `class_longident sl "" k :] - | MLast.ExXnd _ c e -> - fun curr next dg k -> [: `S LR ("Xnd_" ^ c); `next e "" k :] | e -> fun curr next dg k -> [: `next e dg k :] ]}; {pr_label = "dot"; pr_box _ x = HOVbox x; pr_rules = @@ -1430,8 +1426,8 @@ pr_expr.pr_levels := <:expr< for $_$ = $_$ $to:_$ $_$ do { $list:_$ } >> | <:expr< while $_$ do { $list:_$ } >> | <:expr< ($list: _$) >> | <:expr< $_$ . $_$ >> | <:expr< $_$ . ( $_$ ) >> | - <:expr< $_$ . [ $_$ ] >> | <:expr< $_$ := $_$ >> | MLast.ExNew _ _ | - MLast.ExXnd _ _ _ as e -> + <:expr< $_$ . [ $_$ ] >> | <:expr< $_$ := $_$ >> | + MLast.ExNew _ _ as e -> fun curr next dg k -> [: `S LO "("; `expr e "" [: `HVbox [: `S RO ")"; k :] :] :] | e -> fun curr next dg k -> [: `next e "" k :] ]}]; @@ -1503,8 +1499,6 @@ pr_patt.pr_levels := listws (fun x _ k -> HOVbox [: curr x "" k :]) (S RO ",") al "" [: `S RO ")"; k :] :] :] | _ -> [: curr x "" [: :]; `next y "" k :] ] - | MLast.PaXnd _ c p -> - fun curr next dg k -> [: `S LR ("Xnd_" ^ c); `next p "" k :] | p -> fun curr next dg k -> [: `next p "" k :] ]}; {pr_label = ""; pr_box _ x = HOVbox x; pr_rules = @@ -1582,8 +1576,7 @@ pr_patt.pr_levels := `expr e "" [: `S RO ")"; k :] :] | <:patt< _ >> -> fun curr next dg k -> [: `S LR "_"; k :] | <:patt< $_$ $_$ >> | <:patt< ($_$ as $_$) >> | <:patt< $_$ | $_$ >> | - <:patt< ($list:_$) >> | <:patt< $_$ .. $_$ >> | - MLast.PaXnd _ _ _ as p -> + <:patt< ($list:_$) >> | <:patt< $_$ .. $_$ >> as p -> fun curr next dg k -> [: `S LO "("; `patt p "" [: `HVbox [: `S RO ")"; k :] :] :] | p -> fun curr next dg k -> [: `next p "" k :] ]}]; diff --git a/camlp4/etc/pr_r.ml b/camlp4/etc/pr_r.ml index d032b6175..5d601aa8b 100644 --- a/camlp4/etc/pr_r.ml +++ b/camlp4/etc/pr_r.ml @@ -220,7 +220,6 @@ ctyp_f.val := (fun curr next t k -> match t with [ <:ctyp< $t1$ $t2$ >> -> [: curr t1 [: :]; `next t2 k :] - | MLast.TyXnd _ c t -> [: `S LR ("Xnd_" ^ c); `next t k :] | t -> [: `next t k :] ]); level (fun _ x -> HOVbox x) (fun curr next t k -> @@ -277,7 +276,7 @@ ctyp_f.val := | <:ctyp< $_$ -> $_$ >> | <:ctyp< $_$ $_$ >> | <:ctyp< $_$ == $_$ >> | <:ctyp< $_$ . $_$ >> | <:ctyp< $_$ as $_$ >> | <:ctyp< ? $_$ : $_$ >> | - <:ctyp< ~ $_$ : $_$ >> | MLast.TyXnd _ _ _ -> + <:ctyp< ~ $_$ : $_$ >> -> [: `S LO "("; `ctyp t [: `HVbox [: `S RO ")"; k :] :] :] | MLast.TyCls _ id -> [: `S LO "#"; `class_longident id k :] | MLast.TyObj _ [] False -> [: `S LR "<>"; k :] @@ -327,8 +326,7 @@ value rec get_defined_ident = | <:patt< ~ $_$ : $p$ >> -> get_defined_ident p | <:patt< ? $_$ : $p$ >> -> get_defined_ident p | <:patt< ? $_$ : ($p$ = $e$) >> -> get_defined_ident p - | MLast.PaAnt _ p -> get_defined_ident p - | MLast.PaXnd _ _ p -> get_defined_ident p ] + | MLast.PaAnt _ p -> get_defined_ident p ] ; value un_irrefut_patt p = @@ -1191,8 +1189,6 @@ pr_expr.pr_levels := fun curr next _ k -> [: curr x "" [: :]; `next y "" k :] | MLast.ExNew _ sl -> fun curr next _ k -> [: `S LR "new"; `class_longident sl k :] - | MLast.ExXnd _ c e -> - fun curr next _ k -> [: `S LR ("Xnd_" ^ c); `next e "" k :] | e -> fun curr next _ k -> [: `next e "" k :] ]}; {pr_label = "dot"; pr_box _ x = HOVbox x; pr_rules = @@ -1299,8 +1295,7 @@ pr_expr.pr_levels := <:expr< if $_$ then $_$ else $_$ >> | <:expr< do { $list:_$ } >> | <:expr< for $_$ = $_$ $to:_$ $_$ do { $list:_$ } >> | <:expr< while $_$ do { $list:_$ } >> | - <:expr< let $rec:_$ $list:_$ in $_$ >> | MLast.ExNew _ _ | - MLast.ExXnd _ _ _ as e -> + <:expr< let $rec:_$ $list:_$ in $_$ >> | MLast.ExNew _ _ as e -> fun curr next _ k -> [: `S LO "("; `expr e [: `HVbox [: `S RO ")"; k :] :] :] | e -> fun curr next _ k -> [: `next e "" k :] ]}]; @@ -1325,8 +1320,6 @@ pr_patt.pr_levels := fun curr next _ k -> [: `next p "" k :] | <:patt< $x$ $y$ >> -> fun curr next _ k -> [: curr x "" [: :]; `next y "" k :] - | MLast.PaXnd _ c p -> - fun curr next _ k -> [: `S LR ("Xnd_" ^ c); `next p "" k :] | p -> fun curr next _ k -> [: `next p "" k :] ]}; {pr_label = ""; pr_box _ x = HOVbox x; pr_rules = @@ -1415,8 +1408,8 @@ pr_patt.pr_levels := [: `S LO ("?" ^ i ^ ":"); `S LO "("; `patt p [: `S LR "=" :]; `expr e [: `S RO ")"; k :] :] | <:patt< _ >> -> fun curr next _ k -> [: `S LR "_"; k :] - | <:patt< $_$ $_$ >> | <:patt< $_$ .. $_$ >> | <:patt< $_$ | $_$ >> | - MLast.PaXnd _ _ _ as p -> + | <:patt< $_$ $_$ >> | <:patt< $_$ .. $_$ >> + | <:patt< $_$ | $_$ >> as p -> fun curr next _ k -> [: `S LO "("; `patt p [: `HVbox [: `S RO ")"; k :] :] :] | p -> fun curr next _ k -> [: `next p "" k :] ]}]; diff --git a/camlp4/ocaml_src/camlp4/ast2pt.ml b/camlp4/ocaml_src/camlp4/ast2pt.ml index 836fc8696..76562bca8 100644 --- a/camlp4/ocaml_src/camlp4/ast2pt.ml +++ b/camlp4/ocaml_src/camlp4/ast2pt.ml @@ -171,8 +171,6 @@ let rec ctyp = | Some (Some sl) -> true, Some sl in mktyp loc (Ptyp_variant (catl, clos, sl)) - | TyXnd (loc, c, _) -> - error loc ("type \"" ^ c ^ "\" (extension) not allowed here") and meth_list loc fl v = match fl with [] -> if v then [mkfield loc Pfield_var] else [] @@ -385,8 +383,6 @@ let rec patt = let ca = not !no_constructors_arity in mkpat loc (Ppat_construct (lident (conv_con s), None, ca)) | PaVrn (loc, s) -> mkpat loc (Ppat_variant (s, None)) - | PaXnd (loc, c, _) -> - error loc ("pattern \"" ^ c ^ "\" (extension) not allowed here") and mklabpat (lab, p) = patt_label_long_id lab, patt p;; let rec expr_fa al = @@ -561,8 +557,6 @@ let rec expr = | ExVrn (loc, s) -> mkexp loc (Pexp_variant (s, None)) | ExWhi (loc, e1, el) -> let e2 = ExSeq (loc, el) in mkexp loc (Pexp_while (expr e1, expr e2)) - | ExXnd (loc, c, _) -> - error loc ("expression \"" ^ c ^ "\" (extension) not allowed here") and label_expr = function ExLab (loc, lab, e) -> lab, expr e @@ -668,8 +662,6 @@ and class_type = in let cil = List.fold_right class_sig_item ctfl [] in mkcty loc (Pcty_signature (ctyp t, cil)) - | CtXnd (loc, c, _) -> - error loc ("class type \"" ^ c ^ "\" (extension) not allowed here") and class_sig_item c l = match c with CgCtr (loc, t1, t2) -> Pctf_cstr (ctyp t1, ctyp t2, mkloc loc) :: l @@ -710,9 +702,6 @@ and class_expr = mkpcl loc (Pcl_structure (patt p, cil)) | CeTyc (loc, ce, ct) -> mkpcl loc (Pcl_constraint (class_expr ce, class_type ct)) - | CeXnd (loc, c, _) -> - error loc - ("class expression \"" ^ c ^ "\" (extension) not allowed here") and class_str_item c l = match c with CrCtr (loc, t1, t2) -> Pcf_cstr (ctyp t1, ctyp t2, mkloc loc) :: l diff --git a/camlp4/ocaml_src/camlp4/mLast.mli b/camlp4/ocaml_src/camlp4/mLast.mli index 2424439aa..17877811d 100644 --- a/camlp4/ocaml_src/camlp4/mLast.mli +++ b/camlp4/ocaml_src/camlp4/mLast.mli @@ -34,7 +34,6 @@ type ctyp = | TyTup of loc * ctyp list | TyUid of loc * string | TyVrn of loc * row_field list * string list option option - | TyXnd of loc * string * ctyp and row_field = RfTag of string * bool * ctyp list | RfInh of ctyp ;; @@ -68,7 +67,6 @@ type patt = | PaTyp of loc * string list | PaUid of loc * string | PaVrn of loc * string - | PaXnd of loc * string * patt and expr = ExAcc of loc * expr * expr | ExAnt of loc * expr @@ -102,7 +100,6 @@ and expr = | ExUid of loc * string | ExVrn of loc * string | ExWhi of loc * expr * expr list - | ExXnd of loc * string * expr and module_type = MtAcc of loc * module_type * module_type | MtApp of loc * module_type * module_type @@ -154,7 +151,6 @@ and class_type = CtCon of loc * string list * ctyp list | CtFun of loc * ctyp * class_type | CtSig of loc * ctyp option * class_sig_item list - | CtXnd of loc * string * class_type and class_sig_item = CgCtr of loc * ctyp * ctyp | CgDcl of loc * class_sig_item list @@ -169,7 +165,6 @@ and class_expr = | CeLet of loc * bool * (patt * expr) list * class_expr | CeStr of loc * patt option * class_str_item list | CeTyc of loc * class_expr * class_type - | CeXnd of loc * string * class_expr and class_str_item = CrCtr of loc * ctyp * ctyp | CrDcl of loc * class_str_item list diff --git a/camlp4/ocaml_src/camlp4/reloc.ml b/camlp4/ocaml_src/camlp4/reloc.ml index 0176b3686..81f1217ca 100644 --- a/camlp4/ocaml_src/camlp4/reloc.ml +++ b/camlp4/ocaml_src/camlp4/reloc.ml @@ -44,7 +44,6 @@ let rec ctyp floc sh = | TyUid (loc, x1) -> TyUid (floc loc, x1) | TyVrn (loc, x1, x2) -> TyVrn (floc loc, List.map (row_field floc sh) x1, x2) - | TyXnd (loc, x1, x2) -> TyXnd (floc loc, x1, self x2) in self and row_field floc sh = @@ -86,7 +85,6 @@ let rec patt floc sh = | PaTyp (loc, x1) -> PaTyp (floc loc, x1) | PaUid (loc, x1) -> PaUid (floc loc, x1) | PaVrn (loc, x1) -> PaVrn (floc loc, x1) - | PaXnd (loc, x1, x2) -> PaXnd (floc loc, x1, self x2) in self and expr floc sh = @@ -154,7 +152,6 @@ and expr floc sh = | ExUid (loc, x1) -> ExUid (floc loc, x1) | ExVrn (loc, x1) -> ExVrn (floc loc, x1) | ExWhi (loc, x1, x2) -> ExWhi (floc loc, self x1, List.map self x2) - | ExXnd (loc, x1, x2) -> ExXnd (floc loc, x1, self x2) in self and module_type floc sh = @@ -256,7 +253,6 @@ and class_type floc sh = CtSig (floc loc, option_map (ctyp floc sh) x1, List.map (class_sig_item floc sh) x2) - | CtXnd (loc, x1, x2) -> CtXnd (floc loc, x1, self x2) in self and class_sig_item floc sh = @@ -289,7 +285,6 @@ and class_expr floc sh = (floc loc, option_map (patt floc sh) x1, List.map (class_str_item floc sh) x2) | CeTyc (loc, x1, x2) -> CeTyc (floc loc, self x1, class_type floc sh x2) - | CeXnd (loc, x1, x2) -> CeXnd (floc loc, x1, self x2) in self and class_str_item floc sh = |