git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4270 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
cd4cf33ff7
commit
42f6091cd2
|
@ -222,7 +222,7 @@
|
|||
((list (Satom _ Alid "rec") :: sel) (, True sel))
|
||||
((_) (, False sel))))
|
||||
(lbs (value_binding_se sel)))
|
||||
<:str_item< value $opt:r$ $list:lbs$ >>))
|
||||
<:str_item< value $rec:r$ $list:lbs$ >>))
|
||||
((Sexpr loc _)
|
||||
(let ((e (expr_se se)))
|
||||
<:str_item< $exp:e$ >>))))
|
||||
|
@ -277,7 +277,7 @@
|
|||
((list (Sexpr _ sel1) :: sel2)
|
||||
(let* ((lbs (List.map let_binding_se sel1))
|
||||
(e (progn_se loc sel2)))
|
||||
<:expr< let $opt:r$ $list:lbs$ in $e$ >>))
|
||||
<:expr< let $rec:r$ $list:lbs$ in $e$ >>))
|
||||
((list se :: _) (error se "let_binding"))
|
||||
((_) (error_loc loc "let_binding")))))
|
||||
((Sexpr loc (list (Satom _ Alid "let*") :: sel))
|
||||
|
|
|
@ -222,7 +222,7 @@ and str_item_se se =
|
|||
| _ -> (False, sel) ]
|
||||
in
|
||||
let lbs = value_binding_se sel in
|
||||
<:str_item< value $opt:r$ $list:lbs$ >>
|
||||
<:str_item< value $rec:r$ $list:lbs$ >>
|
||||
| Sexpr loc _ ->
|
||||
let e = expr_se se in
|
||||
<:str_item< $exp:e$ >> ]
|
||||
|
@ -272,7 +272,7 @@ and expr_se =
|
|||
[ [Sexpr _ sel1 :: sel2] ->
|
||||
let lbs = List.map let_binding_se sel1 in
|
||||
let e = progn_se loc sel2 in
|
||||
<:expr< let $opt:r$ $list:lbs$ in $e$ >>
|
||||
<:expr< let $rec:r$ $list:lbs$ in $e$ >>
|
||||
| [se :: _] -> error se "let_binding"
|
||||
| _ -> error_loc loc "let_binding" ]
|
||||
| Sexpr loc [Satom _ Alid "let*" :: sel] ->
|
||||
|
|
|
@ -428,12 +428,12 @@ EXTEND
|
|||
<:str_item< type $list:tdl$ >>
|
||||
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
|
||||
x = expr ->
|
||||
let e = <:expr< let $opt:o2b r$ $list:l$ in $x$ >> in
|
||||
let e = <:expr< let $rec:o2b r$ $list:l$ in $x$ >> in
|
||||
<:str_item< $exp:e$ >>
|
||||
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and" ->
|
||||
match l with
|
||||
[ [(<:patt< _ >>, e)] -> <:str_item< $exp:e$ >>
|
||||
| _ -> <:str_item< value $opt:o2b r$ $list:l$ >> ]
|
||||
| _ -> <:str_item< value $rec:o2b r$ $list:l$ >> ]
|
||||
| "let"; "module"; m = UIDENT; mb = module_binding; "in"; e = expr ->
|
||||
<:str_item< let module $m$ = $mb$ in $e$ >>
|
||||
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
||||
|
@ -512,7 +512,7 @@ EXTEND
|
|||
| "expr1"
|
||||
[ "let"; o = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
|
||||
x = expr LEVEL "top" ->
|
||||
<:expr< let $opt:o2b o$ $list:l$ in $x$ >>
|
||||
<:expr< let $rec:o2b o$ $list:l$ in $x$ >>
|
||||
| "let"; "module"; m = UIDENT; mb = module_binding; "in";
|
||||
e = expr LEVEL "top" ->
|
||||
<:expr< let module $m$ = $mb$ in $e$ >>
|
||||
|
|
|
@ -923,12 +923,12 @@ EXTEND
|
|||
<:str_item< type $list:tdl$ >>
|
||||
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
|
||||
x = expr ->
|
||||
let e = <:expr< let $opt:o2b r$ $list:l$ in $x$ >> in
|
||||
let e = <:expr< let $rec:o2b r$ $list:l$ in $x$ >> in
|
||||
<:str_item< $exp:e$ >>
|
||||
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and" ->
|
||||
match l with
|
||||
[ [(<:patt< _ >>, e)] -> <:str_item< $exp:e$ >>
|
||||
| _ -> <:str_item< value $opt:o2b r$ $list:l$ >> ]
|
||||
| _ -> <:str_item< value $rec:o2b r$ $list:l$ >> ]
|
||||
| "let"; "module"; m = UIDENT; mb = module_binding; "in"; e = expr ->
|
||||
<:str_item< let module $m$ = $mb$ in $e$ >>
|
||||
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
||||
|
@ -1006,7 +1006,7 @@ EXTEND
|
|||
| "expr1"
|
||||
[ "let"; o = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
|
||||
x = expr LEVEL "top" ->
|
||||
<:expr< let $opt:o2b o$ $list:l$ in $x$ >>
|
||||
<:expr< let $rec:o2b o$ $list:l$ in $x$ >>
|
||||
| "let"; "module"; m = UIDENT; mb = module_binding; "in";
|
||||
e = expr LEVEL "top" ->
|
||||
<:expr< let module $m$ = $mb$ in $e$ >>
|
||||
|
@ -1782,8 +1782,8 @@ value rec subst v e =
|
|||
| <:expr< $chr:_$ >> -> e
|
||||
| <:expr< $str:_$ >> -> e
|
||||
| <:expr< $_$ . $_$ >> -> e
|
||||
| <:expr< let $opt:rf$ $list:pel$ in $e$ >> ->
|
||||
<:expr< let $opt:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
|
||||
| <:expr< let $rec:rf$ $list:pel$ in $e$ >> ->
|
||||
<:expr< let $rec:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
|
||||
| <:expr< $e1$ $e2$ >> -> <:expr< $subst v e1$ $subst v e2$ >>
|
||||
| <:expr< ( $list:el$ ) >> -> <:expr< ( $list:List.map (subst v) el$ ) >>
|
||||
| _ -> raise Not_found ]
|
||||
|
|
|
@ -93,8 +93,8 @@ value rec subst v e =
|
|||
| <:expr< $chr:_$ >> -> e
|
||||
| <:expr< $str:_$ >> -> e
|
||||
| <:expr< $_$ . $_$ >> -> e
|
||||
| <:expr< let $opt:rf$ $list:pel$ in $e$ >> ->
|
||||
<:expr< let $opt:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
|
||||
| <:expr< let $rec:rf$ $list:pel$ in $e$ >> ->
|
||||
<:expr< let $rec:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
|
||||
| <:expr< $e1$ $e2$ >> -> <:expr< $subst v e1$ $subst v e2$ >>
|
||||
| <:expr< ( $list:el$ ) >> -> <:expr< ( $list:List.map (subst v) el$ ) >>
|
||||
| _ -> raise Not_found ]
|
||||
|
|
|
@ -36,7 +36,7 @@ EXTEND
|
|||
[ [e] -> e
|
||||
| _ -> <:expr< do { $list:el$ } >> ]
|
||||
in
|
||||
[<:expr< let $opt:o2b o$ $list:l$ in $e$ >>]
|
||||
[<:expr< let $rec:o2b o$ $list:l$ in $e$ >>]
|
||||
| e = expr; ";"; el = SELF ->
|
||||
let e = let loc = MLast.loc_of_expr e in <:expr< ($e$ : unit) >> in
|
||||
[e :: el]
|
||||
|
|
|
@ -318,10 +318,19 @@ value rec symbol s k =
|
|||
`simple_symbol sep k :]
|
||||
| _ -> assert False ]
|
||||
| Srules
|
||||
[([(Some <:patt< a >>, Snterm <:expr< anti_opt >>)], Some <:expr< a >>);
|
||||
[([(Some <:patt< a >>, Stoken ("ANTIQUOT", _))],
|
||||
Some <:expr< antiquot $str:_$ loc a >>);
|
||||
([(Some <:patt< o >>, (Sopt s))], Some <:expr< Option o >>)]
|
||||
when not no_slist.val
|
||||
->
|
||||
let s =
|
||||
match s with
|
||||
[ Srules
|
||||
[([(Some <:patt< x >>, Stoken ("", s))], Some <:expr< Str x >>)]
|
||||
->
|
||||
Stoken ("", s)
|
||||
| _ -> s ]
|
||||
in
|
||||
HVbox [: `S LR "SOPT"; `simple_symbol s k :]
|
||||
| Srules rl ->
|
||||
let rl = simplify_rules rl in
|
||||
|
|
|
@ -986,7 +986,7 @@ pr_str_item.pr_levels :=
|
|||
fun curr next dg k -> [: `S LR "include"; `module_expr me "" k :]
|
||||
| <:str_item< type $list:tdl$ >> ->
|
||||
fun curr next dg k -> [: `type_list [: `S LR "type" :] tdl "" k :]
|
||||
| <:str_item< value $opt:rf$ $list:pel$ >> ->
|
||||
| <:str_item< value $rec:rf$ $list:pel$ >> ->
|
||||
fun curr next dg k ->
|
||||
[: `bind_list
|
||||
[: `S LR "let"; if rf then [: `S LR "rec" :] else [: :] :]
|
||||
|
@ -1028,7 +1028,7 @@ pr_expr.pr_levels :=
|
|||
{pr_label = "expr1"; pr_box _ x = HOVbox x;
|
||||
pr_rules =
|
||||
extfun Extfun.empty with
|
||||
[ <:expr< let $opt:r$ $p1$ = $e1$ in $e$ >> ->
|
||||
[ <:expr< let $rec:r$ $p1$ = $e1$ in $e$ >> ->
|
||||
fun curr next dg k ->
|
||||
let r = if r then [: `S LR "rec" :] else [: :] in
|
||||
if dg <> ";" then
|
||||
|
@ -1049,7 +1049,7 @@ pr_expr.pr_levels :=
|
|||
[: `S LR "in" :];
|
||||
`expr e "" [: :] :];
|
||||
`HVbox [: `S LR "end"; k :] :] :]
|
||||
| <:expr< let $opt:r$ $list:pel$ in $e$ >> ->
|
||||
| <:expr< let $rec:r$ $list:pel$ in $e$ >> ->
|
||||
fun curr next dg k ->
|
||||
let r = if r then [: `S LR "rec" :] else [: :] in
|
||||
if dg <> ";" then
|
||||
|
@ -1530,7 +1530,7 @@ pr_expr.pr_levels :=
|
|||
<:expr< fun [ $list:_$ ] >> | <:expr< match $_$ with [ $list:_$ ] >> |
|
||||
<:expr< if $_$ then $_$ else $_$ >> |
|
||||
<:expr< try $_$ with [ $list:_$ ] >> |
|
||||
<:expr< let $opt:_$ $list:_$ in $_$ >> |
|
||||
<:expr< let $rec:_$ $list:_$ in $_$ >> |
|
||||
<:expr< for $_$ = $_$ $to:_$ $_$ do { $list:_$ } >> |
|
||||
<:expr< while $_$ do { $list:_$ } >> | <:expr< ($list: _$) >> |
|
||||
<:expr< $_$ . $_$ >> | <:expr< $_$ . ( $_$ ) >> |
|
||||
|
|
|
@ -454,7 +454,7 @@ and let_binding b (p, e) k =
|
|||
and let_binding0 b e k =
|
||||
let (pl, e) = expr_fun_args e in
|
||||
match e with
|
||||
[ <:expr< let $opt:r$ $lid:f$ = fun [ $list:pel$ ] in $e$ >>
|
||||
[ <:expr< let $rec:r$ $lid:f$ = fun [ $list:pel$ ] in $e$ >>
|
||||
when
|
||||
let rec call_f =
|
||||
fun
|
||||
|
@ -509,7 +509,7 @@ value field_expr (lab, e) k = HVbox [: `label lab; `S LR "="; `expr e k :];
|
|||
|
||||
value rec sequence_loop =
|
||||
fun
|
||||
[ [<:expr< let $opt:r$ $list:pel$ in $e$ >>] ->
|
||||
[ [<:expr< let $rec:r$ $list:pel$ in $e$ >>] ->
|
||||
let el =
|
||||
match e with
|
||||
[ <:expr< do { $list:el$ } >> -> el
|
||||
|
@ -519,7 +519,7 @@ value rec sequence_loop =
|
|||
[: listwbws (fun b (p, e) k -> let_binding b (p, e) k)
|
||||
[: `S LR "let"; r :] (S LR "and") pel [: `S RO ";" :];
|
||||
sequence_loop el :]
|
||||
| [(<:expr< let $opt:_$ $list:_$ in $_$ >> as e) :: el] ->
|
||||
| [(<:expr< let $rec:_$ $list:_$ in $_$ >> as e) :: el] ->
|
||||
[: `HVbox [: `S LO "("; `expr e [: `S RO ")"; `S RO ";" :] :];
|
||||
sequence_loop el :]
|
||||
| [e] -> [: `expr e [: :] :]
|
||||
|
@ -537,7 +537,7 @@ value sequence b1 b2 b3 el k =
|
|||
value rec let_sequence e =
|
||||
match e with
|
||||
[ <:expr< do { $list:el$ } >> -> Some el
|
||||
| <:expr< let $opt:_$ $list:_$ in $e1$ >> ->
|
||||
| <:expr< let $rec:_$ $list:_$ in $e1$ >> ->
|
||||
match let_sequence e1 with
|
||||
[ Some _ -> Some [e]
|
||||
| None -> None ]
|
||||
|
@ -974,7 +974,7 @@ pr_str_item.pr_levels :=
|
|||
fun curr next _ k -> [: `S LR "include"; `module_expr me k :]
|
||||
| <:str_item< type $list:tdl$ >> ->
|
||||
fun curr next _ k -> [: `type_list [: `S LR "type" :] tdl k :]
|
||||
| <:str_item< value $opt:rf$ $list:pel$ >> ->
|
||||
| <:str_item< value $rec:rf$ $list:pel$ >> ->
|
||||
fun curr next _ k ->
|
||||
[: `bind_list [: `S LR "value"; flag "rec" rf :] pel k :]
|
||||
| <:str_item< external $s$ : $t$ = $list:pl$ >> ->
|
||||
|
@ -1028,7 +1028,7 @@ pr_expr.pr_levels :=
|
|||
[{pr_label = "top"; pr_box e x = LocInfo (MLast.loc_of_expr e) (HOVbox x);
|
||||
pr_rules =
|
||||
extfun Extfun.empty with
|
||||
[ <:expr< let $opt:r$ $p1$ = $e1$ in $e$ >> ->
|
||||
[ <:expr< let $rec:r$ $p1$ = $e1$ in $e$ >> ->
|
||||
fun curr next _ k ->
|
||||
let r = flag "rec" r in
|
||||
[: `Vbox
|
||||
|
@ -1036,7 +1036,7 @@ pr_expr.pr_levels :=
|
|||
`let_binding [: `S LR "let"; r :] (p1, e1)
|
||||
[: `S LR "in" :];
|
||||
`expr e k :] :]
|
||||
| <:expr< let $opt:r$ $list:pel$ in $e$ >> ->
|
||||
| <:expr< let $rec:r$ $list:pel$ in $e$ >> ->
|
||||
fun curr next _ k ->
|
||||
let r = flag "rec" r in
|
||||
[: `Vbox
|
||||
|
@ -1392,7 +1392,7 @@ pr_expr.pr_levels :=
|
|||
<:expr< if $_$ then $_$ else $_$ >> | <:expr< do { $list:_$ } >> |
|
||||
<:expr< for $_$ = $_$ $to:_$ $_$ do { $list:_$ } >> |
|
||||
<:expr< while $_$ do { $list:_$ } >> |
|
||||
<:expr< let $opt:_$ $list:_$ in $_$ >> | MLast.ExNew _ _ 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 :] ]}];
|
||||
|
|
|
@ -435,15 +435,38 @@ value ssopt loc symb =
|
|||
{pattern = Some p; symbol = symb}
|
||||
in
|
||||
let rl =
|
||||
let anti_n =
|
||||
match symb.text "" "" with
|
||||
[ <:expr< Gramext.Stoken ("", $str:n$) >> -> n
|
||||
| _ -> "opt" ]
|
||||
in
|
||||
let r1 =
|
||||
let prod =
|
||||
(**)
|
||||
let text = stoken loc "ANTIQUOT" <:expr< $str:anti_n$ >> in
|
||||
[psymbol <:patt< a >> text <:ctyp< string >>]
|
||||
(*
|
||||
let n = mk_name loc <:expr< anti_opt >> in
|
||||
[psymbol <:patt< a >> (snterm loc n None) <:ctyp< 'anti_opt >>]
|
||||
[psymbol <:patt< a >> (snterm loc n None) <:ctyp< ast >>]
|
||||
*)
|
||||
in
|
||||
let act = <:expr< a >> in
|
||||
let act = <:expr< antiquot $str:anti_n$ loc a >> in
|
||||
{prod = prod; action = Some act}
|
||||
in
|
||||
let r2 =
|
||||
let symb =
|
||||
match symb.text "" "" with
|
||||
[ <:expr< Gramext.Stoken ("", $str:_$) >> ->
|
||||
let rule =
|
||||
let psymbol = {pattern = Some <:patt< x >>; symbol = symb} in
|
||||
let action = Some <:expr< Str x >> in
|
||||
{prod = [psymbol]; action = action}
|
||||
in
|
||||
let text = srules loc "ast" [rule] in
|
||||
let styp _ = <:ctyp< ast >> in
|
||||
{used = []; text = text; styp = styp}
|
||||
| _ -> symb ]
|
||||
in
|
||||
let psymb =
|
||||
let symb =
|
||||
{used = []; text = sopt loc symb;
|
||||
|
|
|
@ -202,7 +202,7 @@ EXTEND
|
|||
| "type"; tdl = LIST1 type_declaration SEP "and" ->
|
||||
<:str_item< type $list:tdl$ >>
|
||||
| "value"; r = OPT "rec"; l = LIST1 let_binding SEP "and" ->
|
||||
<:str_item< value $opt:o2b r$ $list:l$ >>
|
||||
<:str_item< value $rec:o2b r$ $list:l$ >>
|
||||
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
||||
;
|
||||
rebind_exn:
|
||||
|
@ -265,7 +265,7 @@ EXTEND
|
|||
[ "top" RIGHTA
|
||||
[ "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
|
||||
x = SELF ->
|
||||
<:expr< let $opt:o2b r$ $list:l$ in $x$ >>
|
||||
<:expr< let $rec:o2b r$ $list:l$ in $x$ >>
|
||||
| "let"; "module"; m = UIDENT; mb = module_binding; "in"; e = SELF ->
|
||||
<:expr< let module $m$ = $mb$ in $e$ >>
|
||||
| "fun"; "["; l = LIST0 match_case SEP "|"; "]" ->
|
||||
|
@ -292,7 +292,7 @@ EXTEND
|
|||
<:expr< while $e$ do { $list:seq$ } >> ]
|
||||
| "where"
|
||||
[ e = SELF; "where"; rf = OPT "rec"; lb = let_binding ->
|
||||
<:expr< let $opt:o2b rf$ $list:[lb]$ in $e$ >> ]
|
||||
<:expr< let $rec:o2b rf$ $list:[lb]$ in $e$ >> ]
|
||||
| ":=" NONA
|
||||
[ e1 = SELF; ":="; e2 = SELF; dummy -> <:expr< $e1$ := $e2$ >> ]
|
||||
| "||" RIGHTA
|
||||
|
@ -352,7 +352,8 @@ EXTEND
|
|||
| e1 = SELF; "."; "["; e2 = SELF; "]" -> <:expr< $e1$ .[ $e2$ ] >>
|
||||
| e1 = SELF; "."; e2 = SELF -> <:expr< $e1$ . $e2$ >> ]
|
||||
| "~-" NONA
|
||||
[ f = [ "~-" | "~-." ]; e = SELF -> <:expr< $lid:f$ $e$ >> ]
|
||||
[ "~-"; e = SELF -> <:expr< ~- $e$ >>
|
||||
| "~-."; e = SELF -> <:expr< ~-. $e$ >> ]
|
||||
| "simple"
|
||||
[ s = INT -> <:expr< $int:s$ >>
|
||||
| s = FLOAT -> <:expr< $flo:s$ >>
|
||||
|
@ -405,7 +406,7 @@ EXTEND
|
|||
[ [e] -> e
|
||||
| _ -> <:expr< do { $list:el$ } >> ]
|
||||
in
|
||||
[ <:expr< let $opt:o2b o$ $list:l$ in $e$ >>]
|
||||
[ <:expr< let $rec:o2b o$ $list:l$ in $e$ >>]
|
||||
| e = expr; ";"; el = SELF -> [e :: el]
|
||||
| e = expr; ";" -> [e]
|
||||
| e = expr -> [e] ] ]
|
||||
|
|
|
@ -91,8 +91,8 @@ value rec subst v e =
|
|||
| <:expr< $chr:_$ >> -> e
|
||||
| <:expr< $str:_$ >> -> e
|
||||
| <:expr< $_$ . $_$ >> -> e
|
||||
| <:expr< let $opt:rf$ $list:pel$ in $e$ >> ->
|
||||
<:expr< let $opt:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
|
||||
| <:expr< let $rec:rf$ $list:pel$ in $e$ >> ->
|
||||
<:expr< let $rec:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
|
||||
| <:expr< $e1$ $e2$ >> -> <:expr< $subst v e1$ $subst v e2$ >>
|
||||
| <:expr< ( $list:el$ ) >> -> <:expr< ( $list:List.map (subst v) el$ ) >>
|
||||
| _ -> raise Not_found ]
|
||||
|
|
|
@ -57,7 +57,7 @@ value o2b =
|
|||
| x -> x ]
|
||||
;
|
||||
|
||||
value mkumin f arg =
|
||||
value mkumin _ f arg =
|
||||
match arg with
|
||||
[ Node "ExInt" [Loc; Str n] when int_of_string n > 0 ->
|
||||
let n = "-" ^ n in
|
||||
|
@ -70,17 +70,19 @@ value mkumin f arg =
|
|||
Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; arg] ]
|
||||
;
|
||||
|
||||
value mklistexp last =
|
||||
value mklistexp _ last =
|
||||
loop True where rec loop top =
|
||||
fun
|
||||
[ [] ->
|
||||
[ List [] ->
|
||||
match last with
|
||||
[ Some e -> e
|
||||
| None -> Node "ExUid" [Loc; Str "[]"] ]
|
||||
| [e1 :: el] ->
|
||||
[ Option (Some e) -> e
|
||||
| Option None -> Node "ExUid" [Loc; Str "[]"]
|
||||
| a -> a ]
|
||||
| List [e1 :: el] ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExUid" [Loc; Str "::"]; e1];
|
||||
loop False el] ]
|
||||
loop False (List el)]
|
||||
| a -> a ]
|
||||
;
|
||||
|
||||
value mklistpat last =
|
||||
|
@ -149,8 +151,7 @@ EXTEND
|
|||
| "open"; i = mod_ident -> Node "StOpn" [Loc; i]
|
||||
| "type"; tdl = SLIST1 type_declaration SEP "and" ->
|
||||
Node "StTyp" [Loc; tdl]
|
||||
| "value"; r = SOPT [ x = "rec" -> Str x ];
|
||||
l = SLIST1 let_binding SEP "and" ->
|
||||
| "value"; r = SOPT "rec"; l = SLIST1 let_binding SEP "and" ->
|
||||
Node "StVal" [Loc; o2b r; l]
|
||||
| "#"; n = lident; dp = dir_param -> Node "StDir" [Loc; n; dp]
|
||||
| e = expr -> Node "StExp" [Loc; e] ] ]
|
||||
|
@ -225,8 +226,8 @@ EXTEND
|
|||
;
|
||||
expr:
|
||||
[ "top" RIGHTA
|
||||
[ "let"; r = SOPT [ x = "rec" -> Str x ];
|
||||
l = SLIST1 let_binding SEP "and"; "in"; x = SELF ->
|
||||
[ "let"; r = SOPT "rec"; l = SLIST1 let_binding SEP "and"; "in";
|
||||
x = SELF ->
|
||||
Node "ExLet" [Loc; o2b r; l; x]
|
||||
| "let"; "module"; m = a_UIDENT; mb = module_binding; "in"; e = SELF ->
|
||||
Node "ExLmd" [Loc; m; mb; e]
|
||||
|
@ -244,15 +245,17 @@ EXTEND
|
|||
Node "ExTry" [Loc; e; List [Tuple [p1; Option None; e1]]]
|
||||
| "if"; e1 = SELF; "then"; e2 = SELF; "else"; e3 = SELF ->
|
||||
Node "ExIfe" [Loc; e1; e2; e3]
|
||||
| "do"; "{"; seq = sequence; "}" -> Node "ExSeq" [Loc; seq]
|
||||
| "do"; "{"; seq = sequence; "}" ->
|
||||
match seq with
|
||||
[ List [e] -> e
|
||||
| _ -> Node "ExSeq" [Loc; seq] ]
|
||||
| "for"; i = a_LIDENT; "="; e1 = SELF; df = direction_flag; e2 = SELF;
|
||||
"do"; "{"; seq = sequence; "}" ->
|
||||
Node "ExFor" [Loc; i; e1; e2; df; seq]
|
||||
| "while"; e = SELF; "do"; "{"; seq = sequence; "}" ->
|
||||
Node "ExWhi" [Loc; e; seq] ]
|
||||
| "where"
|
||||
[ e = SELF; "where"; rf = SOPT [ x = "rec" -> Str x ];
|
||||
lb = let_binding ->
|
||||
[ e = SELF; "where"; rf = SOPT "rec"; lb = let_binding ->
|
||||
Node "ExLet" [Loc; o2b rf; List [lb]; e] ]
|
||||
| ":=" NONA
|
||||
[ e1 = SELF; ":="; e2 = SELF; dummy -> Node "ExAss" [Loc; e1; e2] ]
|
||||
|
@ -297,21 +300,59 @@ EXTEND
|
|||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "@"]; e1]; e2] ]
|
||||
| "+" LEFTA
|
||||
[ e1 = SELF; f = [ "+" | "-" | "+." | "-." ]; e2 = SELF ->
|
||||
[ e1 = SELF; "+"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
|
||||
| LEFTA
|
||||
[ e1 = SELF;
|
||||
f = [ "*" | "/" | "*." | "/." | "land" | "lor" | "lxor" | "mod" ];
|
||||
e2 = SELF ->
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "+"]; e1]; e2]
|
||||
| e1 = SELF; "-"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
|
||||
| RIGHTA
|
||||
[ e1 = SELF; f = [ "**" | "asr" | "lsl" | "lsr" ]; e2 = SELF ->
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "-"]; e1]; e2]
|
||||
| e1 = SELF; "+."; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "+."]; e1]; e2]
|
||||
| e1 = SELF; "-."; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "-."]; e1]; e2] ]
|
||||
| "*" LEFTA
|
||||
[ e1 = SELF; "*"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "*"]; e1]; e2]
|
||||
| e1 = SELF; "/"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "/"]; e1]; e2]
|
||||
| e1 = SELF; "*."; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "*."]; e1]; e2]
|
||||
| e1 = SELF; "/."; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "/."]; e1]; e2]
|
||||
| e1 = SELF; "land"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "land"]; e1]; e2]
|
||||
| e1 = SELF; "lor"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "lor"]; e1]; e2]
|
||||
| e1 = SELF; "lxor"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "lxor"]; e1]; e2]
|
||||
| e1 = SELF; "mod"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "mod"]; e1]; e2] ]
|
||||
| "**" RIGHTA
|
||||
[ e1 = SELF; "**"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "**"]; e1]; e2]
|
||||
| e1 = SELF; "asr"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "asr"]; e1]; e2]
|
||||
| e1 = SELF; "lsl"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "lsl"]; e1]; e2]
|
||||
| e1 = SELF; "lsr"; e2 = SELF ->
|
||||
Node "ExApp"
|
||||
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "lsr"]; e1]; e2] ]
|
||||
| "unary minus" NONA
|
||||
[ f = [ "-" | "-." ]; e = SELF -> mkumin f e ]
|
||||
[ "-"; e = SELF -> mkumin loc "-" e
|
||||
| "-."; e = SELF -> mkumin loc "-." e ]
|
||||
| "apply" LEFTA
|
||||
[ e1 = SELF; e2 = SELF -> Node "ExApp" [Loc; e1; e2] ]
|
||||
| "label" NONA
|
||||
|
@ -329,31 +370,21 @@ EXTEND
|
|||
[ e1 = SELF; "."; "("; e2 = SELF; ")" -> Node "ExAre" [Loc; e1; e2]
|
||||
| e1 = SELF; "."; "["; e2 = SELF; "]" -> Node "ExSte" [Loc; e1; e2]
|
||||
| e1 = SELF; "."; e2 = SELF -> Node "ExAcc" [Loc; e1; e2] ]
|
||||
| NONA
|
||||
[ f = [ "~-" | "~-." ]; e = SELF ->
|
||||
Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e] ]
|
||||
| "~-" NONA
|
||||
[ "~-"; e = SELF -> Node "ExApp" [Loc; Node "ExLid" [Loc; Str "~-"]; e]
|
||||
| "~-."; e = SELF ->
|
||||
Node "ExApp" [Loc; Node "ExLid" [Loc; Str "~-."]; e] ]
|
||||
| "simple"
|
||||
[ a = ANTIQUOT "exp" -> antiquot "exp" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a
|
||||
| s = INT -> Node "ExInt" [Loc; Str s]
|
||||
| s = FLOAT -> Node "ExFlo" [Loc; Str s]
|
||||
| s = STRING -> Node "ExStr" [Loc; Str s]
|
||||
| s = CHAR -> Node "ExChr" [Loc; Str s]
|
||||
| s = UIDENT -> Node "ExUid" [Loc; Str s]
|
||||
| s = LIDENT -> Node "ExLid" [Loc; Str s]
|
||||
| "`"; s = ident -> Node "ExVrn" [Loc; s]
|
||||
| a = anti_int -> Node "ExInt" [Loc; a]
|
||||
| a = anti_flo -> Node "ExFlo" [Loc; a]
|
||||
| a = anti_str -> Node "ExStr" [Loc; a]
|
||||
| a = anti_chr -> Node "ExChr" [Loc; a]
|
||||
| a = anti_uid -> Node "ExUid" [Loc; a]
|
||||
| a = anti_lid -> Node "ExLid" [Loc; a]
|
||||
| a = anti_anti -> Node "ExAnt" [Loc; a]
|
||||
| a = anti_ -> a
|
||||
[ a = a_expr -> a
|
||||
| s = a_INT -> Node "ExInt" [Loc; s]
|
||||
| s = a_FLOAT -> Node "ExFlo" [Loc; s]
|
||||
| s = a_STRING -> Node "ExStr" [Loc; s]
|
||||
| s = a_CHAR -> Node "ExChr" [Loc; s]
|
||||
| i = expr_ident -> i
|
||||
| "["; "]" -> Node "ExUid" [Loc; Str "[]"]
|
||||
| "["; el = LIST1 expr SEP ";"; last = OPT [ "::"; e = expr -> e ];
|
||||
| "["; el = SLIST1 expr SEP ";"; last = SOPT [ "::"; e = expr -> e ];
|
||||
"]" ->
|
||||
mklistexp last el
|
||||
mklistexp loc last el
|
||||
| "[|"; el = SLIST0 expr SEP ";"; "|]" -> Node "ExArr" [Loc; el]
|
||||
| "{"; lel = SLIST1 label_expr SEP ";"; "}" ->
|
||||
Node "ExRec" [Loc; lel; Option None]
|
||||
|
@ -364,8 +395,10 @@ EXTEND
|
|||
| "("; e = SELF; ":"; t = ctyp; ")" -> Node "ExTyc" [Loc; e; t]
|
||||
| "("; e = SELF; ","; el = SLIST1 expr SEP ","; ")" ->
|
||||
Node "ExTup" [Loc; Cons e el]
|
||||
| "("; e = SELF; ")" -> e
|
||||
| "("; el = anti_list; ")" -> Node "ExTup" [Loc; el]
|
||||
| "("; e = SELF; ")" -> e ] ]
|
||||
| a = anti_anti -> Node "ExAnt" [Loc; a]
|
||||
| "`"; s = ident -> Node "ExVrn" [Loc; s] ] ]
|
||||
;
|
||||
expr: LEVEL "top"
|
||||
[ [ "do"; seq = SLIST0 [ e = expr; ";" -> e ]; "return"; e = SELF ->
|
||||
|
@ -384,7 +417,21 @@ EXTEND
|
|||
[ [ -> () ] ]
|
||||
;
|
||||
sequence:
|
||||
[ [ seq = SLIST0 expr SEP ";" -> seq ] ]
|
||||
[ [ a = anti_list -> a
|
||||
| "let"; o = SOPT "rec"; l = SLIST1 let_binding SEP "and";
|
||||
[ "in" | ";" ]; el = SELF ->
|
||||
let e =
|
||||
match el with
|
||||
[ List [e] -> e
|
||||
| _ -> Node "ExSeq" [Loc; el] ]
|
||||
in
|
||||
List [Node "ExLet" [Loc; o2b o; l; e]]
|
||||
| e = expr; ";"; el = SELF ->
|
||||
match el with
|
||||
[ List el -> List [e :: el]
|
||||
| _ -> Cons e el ]
|
||||
| e = expr; ";" -> List [e]
|
||||
| e = expr -> List [e] ] ]
|
||||
;
|
||||
let_binding:
|
||||
[ [ p = ipatt; e = fun_binding -> Tuple [p; e] ] ]
|
||||
|
@ -409,6 +456,19 @@ EXTEND
|
|||
label_expr:
|
||||
[ [ i = patt_label_ident; "="; e = expr -> Tuple [i; e] ] ]
|
||||
;
|
||||
expr_ident:
|
||||
[ RIGHTA
|
||||
[ a = anti_ -> a
|
||||
| i = a_LIDENT -> Node "ExLid" [Loc; i]
|
||||
| i = a_UIDENT -> Node "ExUid" [Loc; i]
|
||||
| i = a_UIDENT; "."; j = SELF ->
|
||||
let rec loop m =
|
||||
fun
|
||||
[ Node "ExAcc" [_; x; y] -> loop (Node "ExAcc" [Loc; m; x]) y
|
||||
| e -> Node "ExAcc" [Loc; m; e] ]
|
||||
in
|
||||
loop (Node "ExUid" [Loc; i]) j ] ]
|
||||
;
|
||||
fun_def:
|
||||
[ [ p = ipatt; e = SELF ->
|
||||
Node "ExFun" [Loc; List [Tuple [p; Option None; e]]]
|
||||
|
@ -614,19 +674,23 @@ EXTEND
|
|||
| -> Bool False ] ]
|
||||
;
|
||||
a_module_expr:
|
||||
[ [ a = ANTIQUOT "module_expr" -> antiquot "module_expr" loc a
|
||||
[ [ a = ANTIQUOT "mexp" -> antiquot "mexp" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
|
||||
;
|
||||
a_str_item:
|
||||
[ [ a = ANTIQUOT "str_item" -> antiquot "str_item" loc a
|
||||
[ [ a = ANTIQUOT "stri" -> antiquot "stri" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
|
||||
;
|
||||
a_module_type:
|
||||
[ [ a = ANTIQUOT "module_type" -> antiquot "module_type" loc a
|
||||
[ [ a = ANTIQUOT "mtyp" -> antiquot "mtyp" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
|
||||
;
|
||||
a_sig_item:
|
||||
[ [ a = ANTIQUOT "sig_item" -> antiquot "sig_item" loc a
|
||||
[ [ a = ANTIQUOT "sigi" -> antiquot "sigi" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
|
||||
;
|
||||
a_expr:
|
||||
[ [ a = ANTIQUOT "exp" -> antiquot "exp" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
|
||||
;
|
||||
a_UIDENT:
|
||||
|
@ -639,10 +703,25 @@ EXTEND
|
|||
| a = ANTIQUOT "" -> antiquot "" loc a
|
||||
| i = LIDENT -> Str i ] ]
|
||||
;
|
||||
a_INT:
|
||||
[ [ a = ANTIQUOT "int" -> antiquot "int" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a
|
||||
| s = INT -> Str s ] ]
|
||||
;
|
||||
a_FLOAT:
|
||||
[ [ a = ANTIQUOT "flo" -> antiquot "flo" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a
|
||||
| s = FLOAT -> Str s ] ]
|
||||
;
|
||||
a_STRING:
|
||||
[ [ a = ANTIQUOT "str" -> antiquot "str" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a
|
||||
| i = STRING -> Str i ] ]
|
||||
| s = STRING -> Str s ] ]
|
||||
;
|
||||
a_CHAR:
|
||||
[ [ a = ANTIQUOT "chr" -> antiquot "chr" loc a
|
||||
| a = ANTIQUOT "" -> antiquot "" loc a
|
||||
| s = CHAR -> Str s ] ]
|
||||
;
|
||||
anti_:
|
||||
[ [ a = ANTIQUOT -> antiquot "" loc a ] ]
|
||||
|
|
|
@ -922,15 +922,58 @@ let ssopt loc symb =
|
|||
{pattern = Some p; symbol = symb}
|
||||
in
|
||||
let rl =
|
||||
let anti_n =
|
||||
match symb.text "" "" with
|
||||
MLast.ExApp
|
||||
(_,
|
||||
MLast.ExAcc
|
||||
(_, MLast.ExUid (_, "Gramext"), MLast.ExUid (_, "Stoken")),
|
||||
MLast.ExTup (_, [MLast.ExStr (_, ""); MLast.ExStr (_, n)])) ->
|
||||
n
|
||||
| _ -> "opt"
|
||||
in
|
||||
let r1 =
|
||||
let prod =
|
||||
let n = mk_name loc (MLast.ExLid (loc, "anti_opt")) in
|
||||
[psymbol (MLast.PaLid (loc, "a")) (snterm loc n None)
|
||||
(MLast.TyQuo (loc, "anti_opt"))]
|
||||
let text = stoken loc "ANTIQUOT" (MLast.ExStr (loc, anti_n)) in
|
||||
[psymbol (MLast.PaLid (loc, "a")) text (MLast.TyLid (loc, "string"))]
|
||||
in
|
||||
let act = MLast.ExLid (loc, "a") in {prod = prod; action = Some act}
|
||||
let act =
|
||||
MLast.ExApp
|
||||
(loc,
|
||||
MLast.ExApp
|
||||
(loc,
|
||||
MLast.ExApp
|
||||
(loc, MLast.ExLid (loc, "antiquot"),
|
||||
MLast.ExStr (loc, anti_n)),
|
||||
MLast.ExLid (loc, "loc")),
|
||||
MLast.ExLid (loc, "a"))
|
||||
in
|
||||
{prod = prod; action = Some act}
|
||||
in
|
||||
let r2 =
|
||||
let symb =
|
||||
match symb.text "" "" with
|
||||
MLast.ExApp
|
||||
(_,
|
||||
MLast.ExAcc
|
||||
(_, MLast.ExUid (_, "Gramext"), MLast.ExUid (_, "Stoken")),
|
||||
MLast.ExTup (_, [MLast.ExStr (_, ""); MLast.ExStr (_, _)])) ->
|
||||
let rule =
|
||||
let psymbol =
|
||||
{pattern = Some (MLast.PaLid (loc, "x")); symbol = symb}
|
||||
in
|
||||
let action =
|
||||
Some
|
||||
(MLast.ExApp
|
||||
(loc, MLast.ExUid (loc, "Str"), MLast.ExLid (loc, "x")))
|
||||
in
|
||||
{prod = [psymbol]; action = action}
|
||||
in
|
||||
let text = srules loc "ast" [rule] in
|
||||
let styp _ = MLast.TyLid (loc, "ast") in
|
||||
{used = []; text = text; styp = styp}
|
||||
| _ -> symb
|
||||
in
|
||||
let psymb =
|
||||
let symb =
|
||||
{used = []; text = sopt loc symb;
|
||||
|
|
|
@ -981,15 +981,14 @@ Grammar.extend
|
|||
(fun _ (e2 : 'expr) _ _ (e1 : 'expr) (loc : int * int) ->
|
||||
(MLast.ExAre (loc, e1, e2) : 'expr))];
|
||||
Some "~-", Some Gramext.NonA,
|
||||
[[Gramext.srules
|
||||
[[Gramext.Stoken ("", "~-.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__5));
|
||||
[Gramext.Stoken ("", "~-")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__5))];
|
||||
Gramext.Sself],
|
||||
[[Gramext.Stoken ("", "~-."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) (f : 'e__5) (loc : int * int) ->
|
||||
(MLast.ExApp (loc, MLast.ExLid (loc, f), e) : 'expr))];
|
||||
(fun (e : 'expr) _ (loc : int * int) ->
|
||||
(MLast.ExApp (loc, MLast.ExLid (loc, "~-."), e) : 'expr));
|
||||
[Gramext.Stoken ("", "~-"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (loc : int * int) ->
|
||||
(MLast.ExApp (loc, MLast.ExLid (loc, "~-"), e) : 'expr))];
|
||||
Some "simple", None,
|
||||
[[Gramext.Stoken ("QUOTATION", "")],
|
||||
Gramext.action
|
||||
|
@ -1074,10 +1073,10 @@ Grammar.extend
|
|||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__6))]);
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__5))]);
|
||||
Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
(fun _ (last : 'e__6 option) (el : 'expr list) _ (loc : int * int) ->
|
||||
(fun _ (last : 'e__5 option) (el : 'expr list) _ (loc : int * int) ->
|
||||
(mklistexp loc last el : 'expr));
|
||||
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
|
@ -1124,9 +1123,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", "and"));
|
||||
Gramext.srules
|
||||
[[Gramext.Stoken ("", ";")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__6));
|
||||
[Gramext.Stoken ("", "in")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7))];
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__6))];
|
||||
Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (el : 'sequence) _ (l : 'let_binding list) (o : string option) _
|
||||
|
@ -1173,18 +1172,18 @@ Grammar.extend
|
|||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (patt : 'patt Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__8))]);
|
||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__7))]);
|
||||
Gramext.Sopt
|
||||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "when");
|
||||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__9))]);
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__8))]);
|
||||
Gramext.Stoken ("", "->");
|
||||
Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (w : 'e__9 option) (aso : 'e__8 option) (p : 'patt)
|
||||
(fun (e : 'expr) _ (w : 'e__8 option) (aso : 'e__7 option) (p : 'patt)
|
||||
(loc : int * int) ->
|
||||
(let p =
|
||||
match aso with
|
||||
|
@ -1335,10 +1334,10 @@ Grammar.extend
|
|||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (patt : 'patt Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__10))]);
|
||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__9))]);
|
||||
Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
(fun _ (last : 'e__10 option) (pl : 'patt list) _ (loc : int * int) ->
|
||||
(fun _ (last : 'e__9 option) (pl : 'patt list) _ (loc : int * int) ->
|
||||
(mklistpat loc last pl : 'patt));
|
||||
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
|
@ -1870,9 +1869,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (cf : 'class_str_item) (loc : int * int) ->
|
||||
(cf : 'e__11))])],
|
||||
(cf : 'e__10))])],
|
||||
Gramext.action
|
||||
(fun (cf : 'e__11 list) (loc : int * int) ->
|
||||
(fun (cf : 'e__10 list) (loc : int * int) ->
|
||||
(cf : 'class_structure))]];
|
||||
Grammar.Entry.obj (class_self_patt : 'class_self_patt Grammar.Entry.e),
|
||||
None,
|
||||
|
@ -1946,9 +1945,9 @@ Grammar.extend
|
|||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "as"); Gramext.Stoken ("LIDENT", "")],
|
||||
Gramext.action
|
||||
(fun (i : string) _ (loc : int * int) -> (i : 'e__12))])],
|
||||
(fun (i : string) _ (loc : int * int) -> (i : 'e__11))])],
|
||||
Gramext.action
|
||||
(fun (pb : 'e__12 option) (ce : 'class_expr) _ (loc : int * int) ->
|
||||
(fun (pb : 'e__11 option) (ce : 'class_expr) _ (loc : int * int) ->
|
||||
(MLast.CrInh (loc, ce, pb) : 'class_str_item))]];
|
||||
Grammar.Entry.obj (cvalue : 'cvalue Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
|
@ -2011,10 +2010,10 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (csf : 'class_sig_item) (loc : int * int) ->
|
||||
(csf : 'e__13))]);
|
||||
(csf : 'e__12))]);
|
||||
Gramext.Stoken ("", "end")],
|
||||
Gramext.action
|
||||
(fun _ (csf : 'e__13 list) (cst : 'class_self_type option) _
|
||||
(fun _ (csf : 'e__12 list) (cst : 'class_self_type option) _
|
||||
(loc : int * int) ->
|
||||
(MLast.CtSig (loc, cst, csf) : 'class_type));
|
||||
[Gramext.Snterm
|
||||
|
@ -2571,10 +2570,10 @@ Grammar.extend
|
|||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__16))]);
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__15))]);
|
||||
Gramext.Stoken ("", "done")],
|
||||
Gramext.action
|
||||
(fun _ (seq : 'e__16 list) _ (e : 'expr) _ (loc : int * int) ->
|
||||
(fun _ (seq : 'e__15 list) _ (e : 'expr) _ (loc : int * int) ->
|
||||
(warning_seq (); MLast.ExWhi (loc, e, seq) : 'expr));
|
||||
[Gramext.Stoken ("", "for"); Gramext.Stoken ("LIDENT", "");
|
||||
Gramext.Stoken ("", "="); Gramext.Sself;
|
||||
|
@ -2588,10 +2587,10 @@ Grammar.extend
|
|||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__15))]);
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__14))]);
|
||||
Gramext.Stoken ("", "done")],
|
||||
Gramext.action
|
||||
(fun _ (seq : 'e__15 list) _ (e2 : 'expr) (df : 'direction_flag)
|
||||
(fun _ (seq : 'e__14 list) _ (e2 : 'expr) (df : 'direction_flag)
|
||||
(e1 : 'expr) _ (i : string) _ (loc : int * int) ->
|
||||
(warning_seq (); MLast.ExFor (loc, i, e1, e2, df, seq) : 'expr));
|
||||
[Gramext.Stoken ("", "do");
|
||||
|
@ -2601,8 +2600,8 @@ Grammar.extend
|
|||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__14))]);
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__13))]);
|
||||
Gramext.Stoken ("", "return"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (seq : 'e__14 list) _ (loc : int * int) ->
|
||||
(fun (e : 'expr) _ (seq : 'e__13 list) _ (loc : int * int) ->
|
||||
(warning_seq (); MLast.ExSeq (loc, (seq @ [e])) : 'expr))]]]);;
|
||||
|
|
|
@ -57,7 +57,7 @@ let o2b =
|
|||
| x -> x
|
||||
;;
|
||||
|
||||
let mkumin f arg =
|
||||
let mkumin _ f arg =
|
||||
match arg with
|
||||
Node ("ExInt", [Loc; Str n]) when int_of_string n > 0 ->
|
||||
let n = "-" ^ n in Node ("ExInt", [Loc; Str n])
|
||||
|
@ -68,19 +68,21 @@ let mkumin f arg =
|
|||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); arg])
|
||||
;;
|
||||
|
||||
let mklistexp last =
|
||||
let mklistexp _ last =
|
||||
let rec loop top =
|
||||
function
|
||||
[] ->
|
||||
List [] ->
|
||||
begin match last with
|
||||
Some e -> e
|
||||
| None -> Node ("ExUid", [Loc; Str "[]"])
|
||||
Option (Some e) -> e
|
||||
| Option None -> Node ("ExUid", [Loc; Str "[]"])
|
||||
| a -> a
|
||||
end
|
||||
| e1 :: el ->
|
||||
| List (e1 :: el) ->
|
||||
Node
|
||||
("ExApp",
|
||||
[Loc; Node ("ExApp", [Loc; Node ("ExUid", [Loc; Str "::"]); e1]);
|
||||
loop false el])
|
||||
loop false (List el)])
|
||||
| a -> a
|
||||
in
|
||||
loop true
|
||||
;;
|
||||
|
@ -151,6 +153,8 @@ Grammar.extend
|
|||
grammar_entry_create "match_case"
|
||||
and label_expr : 'label_expr Grammar.Entry.e =
|
||||
grammar_entry_create "label_expr"
|
||||
and expr_ident : 'expr_ident Grammar.Entry.e =
|
||||
grammar_entry_create "expr_ident"
|
||||
and fun_def : 'fun_def Grammar.Entry.e = grammar_entry_create "fun_def"
|
||||
and label_patt : 'label_patt Grammar.Entry.e =
|
||||
grammar_entry_create "label_patt"
|
||||
|
@ -192,9 +196,13 @@ Grammar.extend
|
|||
grammar_entry_create "a_module_type"
|
||||
and a_sig_item : 'a_sig_item Grammar.Entry.e =
|
||||
grammar_entry_create "a_sig_item"
|
||||
and a_expr : 'a_expr Grammar.Entry.e = grammar_entry_create "a_expr"
|
||||
and a_UIDENT : 'a_UIDENT Grammar.Entry.e = grammar_entry_create "a_UIDENT"
|
||||
and a_LIDENT : 'a_LIDENT Grammar.Entry.e = grammar_entry_create "a_LIDENT"
|
||||
and a_INT : 'a_INT Grammar.Entry.e = grammar_entry_create "a_INT"
|
||||
and a_FLOAT : 'a_FLOAT Grammar.Entry.e = grammar_entry_create "a_FLOAT"
|
||||
and a_STRING : 'a_STRING Grammar.Entry.e = grammar_entry_create "a_STRING"
|
||||
and a_CHAR : 'a_CHAR Grammar.Entry.e = grammar_entry_create "a_CHAR"
|
||||
and anti_ : 'anti_ Grammar.Entry.e = grammar_entry_create "anti_"
|
||||
and anti_anti : 'anti_anti Grammar.Entry.e =
|
||||
grammar_entry_create "anti_anti"
|
||||
|
@ -336,13 +344,13 @@ Grammar.extend
|
|||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "rec")],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'e__3))])],
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'ast))])],
|
||||
Gramext.action
|
||||
(fun (o : 'e__3 option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_opt : 'anti_opt Grammar.Entry.e))],
|
||||
(fun (o : ast option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Stoken ("ANTIQUOT", "rec")],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_opt) (loc : int * int) -> (a : 'anti))];
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "rec" loc a : 'anti))];
|
||||
Gramext.srules
|
||||
[[Gramext.Slist1sep
|
||||
(Gramext.Snterm
|
||||
|
@ -440,7 +448,7 @@ Grammar.extend
|
|||
Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3
|
||||
| _ ->
|
||||
match () with
|
||||
_ -> raise (Match_failure ("q_MLast.ml", 4528, 4544))
|
||||
_ -> raise (Match_failure ("q_MLast.ml", 4595, 4611))
|
||||
in
|
||||
Node ("StExc", [Loc; c; tl; b]) :
|
||||
'str_item));
|
||||
|
@ -546,9 +554,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (s : 'sig_item) (loc : int * int) ->
|
||||
(s : 'e__4))])],
|
||||
(s : 'e__3))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__4 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__3 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -682,7 +690,7 @@ Grammar.extend
|
|||
Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3
|
||||
| _ ->
|
||||
match () with
|
||||
_ -> raise (Match_failure ("q_MLast.ml", 6685, 6701))
|
||||
_ -> raise (Match_failure ("q_MLast.ml", 6727, 6743))
|
||||
in
|
||||
Node ("SgExc", [Loc; c; tl]) :
|
||||
'sig_item));
|
||||
|
@ -696,9 +704,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (s : 'sig_item) (loc : int * int) ->
|
||||
(s : 'e__5))])],
|
||||
(s : 'e__4))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__5 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__4 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -805,7 +813,10 @@ Grammar.extend
|
|||
Gramext.Stoken ("", "}")],
|
||||
Gramext.action
|
||||
(fun _ (seq : 'sequence) _ _ (loc : int * int) ->
|
||||
(Node ("ExSeq", [Loc; seq]) : 'expr));
|
||||
(match seq with
|
||||
List [e] -> e
|
||||
| _ -> Node ("ExSeq", [Loc; seq]) :
|
||||
'expr));
|
||||
[Gramext.Stoken ("", "if"); Gramext.Sself; Gramext.Stoken ("", "then");
|
||||
Gramext.Sself; Gramext.Stoken ("", "else"); Gramext.Sself],
|
||||
Gramext.action
|
||||
|
@ -906,13 +917,13 @@ Grammar.extend
|
|||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "rec")],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'e__6))])],
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'ast))])],
|
||||
Gramext.action
|
||||
(fun (o : 'e__6 option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_opt : 'anti_opt Grammar.Entry.e))],
|
||||
(fun (o : ast option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Stoken ("ANTIQUOT", "rec")],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_opt) (loc : int * int) -> (a : 'anti))];
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "rec" loc a : 'anti))];
|
||||
Gramext.srules
|
||||
[[Gramext.Slist1sep
|
||||
(Gramext.Snterm
|
||||
|
@ -937,13 +948,13 @@ Grammar.extend
|
|||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "rec")],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'e__7))])],
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'ast))])],
|
||||
Gramext.action
|
||||
(fun (o : 'e__7 option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_opt : 'anti_opt Grammar.Entry.e))],
|
||||
(fun (o : ast option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Stoken ("ANTIQUOT", "rec")],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_opt) (loc : int * int) -> (a : 'anti))];
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "rec" loc a : 'anti))];
|
||||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (let_binding : 'let_binding Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -1068,82 +1079,159 @@ Grammar.extend
|
|||
e2]) :
|
||||
'expr))];
|
||||
Some "+", Some Gramext.LeftA,
|
||||
[[Gramext.Sself;
|
||||
Gramext.srules
|
||||
[[Gramext.Stoken ("", "-.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
|
||||
[Gramext.Stoken ("", "+.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
|
||||
[Gramext.Stoken ("", "-")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
|
||||
[Gramext.Stoken ("", "+")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8))];
|
||||
Gramext.Sself],
|
||||
[[Gramext.Sself; Gramext.Stoken ("", "-."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) (f : 'e__8) (e1 : 'expr) (loc : int * int) ->
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "-."]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "+."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "+."]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "-"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "-"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "+"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "+"]); e1]);
|
||||
e2]) :
|
||||
'expr))];
|
||||
None, Some Gramext.LeftA,
|
||||
[[Gramext.Sself;
|
||||
Gramext.srules
|
||||
[[Gramext.Stoken ("", "mod")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "lxor")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "lor")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "land")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "/.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "*.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "/")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "*")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9))];
|
||||
Gramext.Sself],
|
||||
Some "*", Some Gramext.LeftA,
|
||||
[[Gramext.Sself; Gramext.Stoken ("", "mod"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) (f : 'e__9) (e1 : 'expr) (loc : int * int) ->
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "mod"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "lxor"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "lxor"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "lor"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "lor"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "land"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "land"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "/."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "/."]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "*."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "*."]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "/"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "/"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "*"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "*"]); e1]);
|
||||
e2]) :
|
||||
'expr))];
|
||||
None, Some Gramext.RightA,
|
||||
[[Gramext.Sself;
|
||||
Gramext.srules
|
||||
[[Gramext.Stoken ("", "lsr")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
|
||||
[Gramext.Stoken ("", "lsl")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
|
||||
[Gramext.Stoken ("", "asr")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
|
||||
[Gramext.Stoken ("", "**")],
|
||||
Some "**", Some Gramext.RightA,
|
||||
[[Gramext.Sself; Gramext.Stoken ("", "lsr"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (x : 'e__10))];
|
||||
Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) (f : 'e__10) (e1 : 'expr) (loc : int * int) ->
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "lsr"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "lsl"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "lsl"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "asr"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "asr"]); e1]);
|
||||
e2]) :
|
||||
'expr));
|
||||
[Gramext.Sself; Gramext.Stoken ("", "**"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node
|
||||
("ExApp",
|
||||
[Loc;
|
||||
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "**"]); e1]);
|
||||
e2]) :
|
||||
'expr))];
|
||||
Some "unary minus", Some Gramext.NonA,
|
||||
[[Gramext.srules
|
||||
[[Gramext.Stoken ("", "-.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__11));
|
||||
[Gramext.Stoken ("", "-")],
|
||||
[[Gramext.Stoken ("", "-."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (x : 'e__11))];
|
||||
Gramext.Sself],
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (mkumin loc "-." e : 'expr));
|
||||
[Gramext.Stoken ("", "-"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) (f : 'e__11) (loc : int * int) ->
|
||||
(mkumin f e : 'expr))];
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (mkumin loc "-" e : 'expr))];
|
||||
Some "apply", Some Gramext.LeftA,
|
||||
[[Gramext.Sself; Gramext.Sself],
|
||||
Gramext.action
|
||||
|
@ -1205,20 +1293,28 @@ Grammar.extend
|
|||
Gramext.action
|
||||
(fun _ (e2 : 'expr) _ _ (e1 : 'expr) (loc : int * int) ->
|
||||
(Node ("ExAre", [Loc; e1; e2]) : 'expr))];
|
||||
None, Some Gramext.NonA,
|
||||
[[Gramext.srules
|
||||
[[Gramext.Stoken ("", "~-.")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__12));
|
||||
[Gramext.Stoken ("", "~-")],
|
||||
Some "~-", Some Gramext.NonA,
|
||||
[[Gramext.Stoken ("", "~-."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (x : 'e__12))];
|
||||
Gramext.Sself],
|
||||
(fun (e : 'expr) _ (loc : int * int) ->
|
||||
(Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "~-."]); e]) :
|
||||
'expr));
|
||||
[Gramext.Stoken ("", "~-"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) (f : 'e__12) (loc : int * int) ->
|
||||
(Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e]) : 'expr))];
|
||||
(fun (e : 'expr) _ (loc : int * int) ->
|
||||
(Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "~-"]); e]) :
|
||||
'expr))];
|
||||
Some "simple", None,
|
||||
[[Gramext.Stoken ("", "("); Gramext.Sself; Gramext.Stoken ("", ")")],
|
||||
Gramext.action (fun _ (e : 'expr) _ (loc : int * int) -> (e : 'expr));
|
||||
[[Gramext.Stoken ("", "`");
|
||||
Gramext.Snterm (Grammar.Entry.obj (ident : 'ident Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (s : 'ident) _ (loc : int * int) ->
|
||||
(Node ("ExVrn", [Loc; s]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_anti : 'anti_anti Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_anti) (loc : int * int) ->
|
||||
(Node ("ExAnt", [Loc; a]) : 'expr));
|
||||
[Gramext.Stoken ("", "(");
|
||||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e));
|
||||
|
@ -1226,6 +1322,8 @@ Grammar.extend
|
|||
Gramext.action
|
||||
(fun _ (el : 'anti_list) _ (loc : int * int) ->
|
||||
(Node ("ExTup", [Loc; el]) : 'expr));
|
||||
[Gramext.Stoken ("", "("); Gramext.Sself; Gramext.Stoken ("", ")")],
|
||||
Gramext.action (fun _ (e : 'expr) _ (loc : int * int) -> (e : 'expr));
|
||||
[Gramext.Stoken ("", "("); Gramext.Sself; Gramext.Stoken ("", ",");
|
||||
Gramext.srules
|
||||
[[Gramext.Slist1sep
|
||||
|
@ -1306,97 +1404,62 @@ Grammar.extend
|
|||
(fun _ (el : ast) _ (loc : int * int) ->
|
||||
(Node ("ExArr", [Loc; el]) : 'expr));
|
||||
[Gramext.Stoken ("", "[");
|
||||
Gramext.Slist1sep
|
||||
(Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e)),
|
||||
Gramext.Stoken ("", ";"));
|
||||
Gramext.Sopt
|
||||
Gramext.srules
|
||||
[[Gramext.Slist1sep
|
||||
(Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e)),
|
||||
Gramext.Stoken ("", ";"))],
|
||||
Gramext.action
|
||||
(fun (l : 'expr list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))];
|
||||
Gramext.srules
|
||||
[[Gramext.Sopt
|
||||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "::");
|
||||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__13))]);
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__5))])],
|
||||
Gramext.action
|
||||
(fun (o : 'e__5 option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Stoken ("ANTIQUOT", "opt")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "opt" loc a : 'anti))];
|
||||
Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
(fun _ (last : 'e__13 option) (el : 'expr list) _ (loc : int * int) ->
|
||||
(mklistexp last el : 'expr));
|
||||
(fun _ (last : ast) (el : ast) _ (loc : int * int) ->
|
||||
(mklistexp loc last el : 'expr));
|
||||
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
(fun _ _ (loc : int * int) ->
|
||||
(Node ("ExUid", [Loc; Str "[]"]) : 'expr));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (anti_ : 'anti_ Grammar.Entry.e))],
|
||||
Gramext.action (fun (a : 'anti_) (loc : int * int) -> (a : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_anti : 'anti_anti Grammar.Entry.e))],
|
||||
(Grammar.Entry.obj (expr_ident : 'expr_ident Grammar.Entry.e))],
|
||||
Gramext.action (fun (i : 'expr_ident) (loc : int * int) -> (i : 'expr));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (a_CHAR : 'a_CHAR Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_anti) (loc : int * int) ->
|
||||
(Node ("ExAnt", [Loc; a]) : 'expr));
|
||||
(fun (s : 'a_CHAR) (loc : int * int) ->
|
||||
(Node ("ExChr", [Loc; s]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_lid : 'anti_lid Grammar.Entry.e))],
|
||||
(Grammar.Entry.obj (a_STRING : 'a_STRING Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_lid) (loc : int * int) ->
|
||||
(Node ("ExLid", [Loc; a]) : 'expr));
|
||||
(fun (s : 'a_STRING) (loc : int * int) ->
|
||||
(Node ("ExStr", [Loc; s]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_uid : 'anti_uid Grammar.Entry.e))],
|
||||
(Grammar.Entry.obj (a_FLOAT : 'a_FLOAT Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_uid) (loc : int * int) ->
|
||||
(Node ("ExUid", [Loc; a]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_chr : 'anti_chr Grammar.Entry.e))],
|
||||
(fun (s : 'a_FLOAT) (loc : int * int) ->
|
||||
(Node ("ExFlo", [Loc; s]) : 'expr));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (a_INT : 'a_INT Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_chr) (loc : int * int) ->
|
||||
(Node ("ExChr", [Loc; a]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_str : 'anti_str Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_str) (loc : int * int) ->
|
||||
(Node ("ExStr", [Loc; a]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_flo : 'anti_flo Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_flo) (loc : int * int) ->
|
||||
(Node ("ExFlo", [Loc; a]) : 'expr));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_int : 'anti_int Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_int) (loc : int * int) ->
|
||||
(Node ("ExInt", [Loc; a]) : 'expr));
|
||||
[Gramext.Stoken ("", "`");
|
||||
Gramext.Snterm (Grammar.Entry.obj (ident : 'ident Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (s : 'ident) _ (loc : int * int) ->
|
||||
(Node ("ExVrn", [Loc; s]) : 'expr));
|
||||
[Gramext.Stoken ("LIDENT", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) ->
|
||||
(Node ("ExLid", [Loc; Str s]) : 'expr));
|
||||
[Gramext.Stoken ("UIDENT", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) ->
|
||||
(Node ("ExUid", [Loc; Str s]) : 'expr));
|
||||
[Gramext.Stoken ("CHAR", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) ->
|
||||
(Node ("ExChr", [Loc; Str s]) : 'expr));
|
||||
[Gramext.Stoken ("STRING", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) ->
|
||||
(Node ("ExStr", [Loc; Str s]) : 'expr));
|
||||
[Gramext.Stoken ("FLOAT", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) ->
|
||||
(Node ("ExFlo", [Loc; Str s]) : 'expr));
|
||||
[Gramext.Stoken ("INT", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) ->
|
||||
(Node ("ExInt", [Loc; Str s]) : 'expr));
|
||||
[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'expr));
|
||||
[Gramext.Stoken ("ANTIQUOT", "exp")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "exp" loc a : 'expr))]];
|
||||
(fun (s : 'a_INT) (loc : int * int) ->
|
||||
(Node ("ExInt", [Loc; s]) : 'expr));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (a_expr : 'a_expr Grammar.Entry.e))],
|
||||
Gramext.action (fun (a : 'a_expr) (loc : int * int) -> (a : 'expr))]];
|
||||
Grammar.Entry.obj (expr : 'expr Grammar.Entry.e),
|
||||
Some (Gramext.Level "top"),
|
||||
[None, None,
|
||||
|
@ -1408,9 +1471,9 @@ Grammar.extend
|
|||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__16))])],
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__8))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__16 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__8 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -1434,9 +1497,9 @@ Grammar.extend
|
|||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__15))])],
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__7))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__15 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__7 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -1456,9 +1519,9 @@ Grammar.extend
|
|||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__14))])],
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__6))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__14 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__6 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -1473,19 +1536,66 @@ Grammar.extend
|
|||
[[], Gramext.action (fun (loc : int * int) -> (() : 'dummy))]];
|
||||
Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.srules
|
||||
[[Gramext.Slist0sep
|
||||
(Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e)),
|
||||
Gramext.Stoken ("", ";"))],
|
||||
[[Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (l : 'expr list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (e : 'expr) (loc : int * int) -> (List [e] : 'sequence));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'expr) (loc : int * int) -> (List [e] : 'sequence));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||
Gramext.Stoken ("", ";"); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (el : 'sequence) _ (e : 'expr) (loc : int * int) ->
|
||||
(match el with
|
||||
List el -> List (e :: el)
|
||||
| _ -> Cons (e, el) :
|
||||
'sequence));
|
||||
[Gramext.Stoken ("", "let");
|
||||
Gramext.srules
|
||||
[[Gramext.Sopt
|
||||
(Gramext.srules
|
||||
[[Gramext.Stoken ("", "rec")],
|
||||
Gramext.action
|
||||
(fun (x : string) (loc : int * int) -> (Str x : 'ast))])],
|
||||
Gramext.action
|
||||
(fun (o : ast option) (loc : int * int) -> (Option o : 'anti));
|
||||
[Gramext.Stoken ("ANTIQUOT", "rec")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "rec" loc a : 'anti))];
|
||||
Gramext.srules
|
||||
[[Gramext.Slist1sep
|
||||
(Gramext.Snterm
|
||||
(Grammar.Entry.obj
|
||||
(let_binding : 'let_binding Grammar.Entry.e)),
|
||||
Gramext.Stoken ("", "and"))],
|
||||
Gramext.action
|
||||
(fun (l : 'let_binding list) (loc : int * int) ->
|
||||
(List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))]],
|
||||
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))];
|
||||
Gramext.srules
|
||||
[[Gramext.Stoken ("", ";")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
|
||||
[Gramext.Stoken ("", "in")],
|
||||
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9))];
|
||||
Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (seq : ast) (loc : int * int) -> (seq : 'sequence))]];
|
||||
(fun (el : 'sequence) _ (l : ast) (o : ast) _ (loc : int * int) ->
|
||||
(let e =
|
||||
match el with
|
||||
List [e] -> e
|
||||
| _ -> Node ("ExSeq", [Loc; el])
|
||||
in
|
||||
List [Node ("ExLet", [Loc; o2b o; l; e])] :
|
||||
'sequence));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_list) (loc : int * int) -> (a : 'sequence))]];
|
||||
Grammar.Entry.obj (let_binding : 'let_binding Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Snterm (Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e));
|
||||
|
@ -1542,6 +1652,34 @@ Grammar.extend
|
|||
Gramext.action
|
||||
(fun (e : 'expr) _ (i : 'patt_label_ident) (loc : int * int) ->
|
||||
(Tuple [i; e] : 'label_expr))]];
|
||||
Grammar.Entry.obj (expr_ident : 'expr_ident Grammar.Entry.e), None,
|
||||
[None, Some Gramext.RightA,
|
||||
[[Gramext.Snterm
|
||||
(Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e));
|
||||
Gramext.Stoken ("", "."); Gramext.Sself],
|
||||
Gramext.action
|
||||
(fun (j : 'expr_ident) _ (i : 'a_UIDENT) (loc : int * int) ->
|
||||
(let rec loop m =
|
||||
function
|
||||
Node ("ExAcc", [_; x; y]) ->
|
||||
loop (Node ("ExAcc", [Loc; m; x])) y
|
||||
| e -> Node ("ExAcc", [Loc; m; e])
|
||||
in
|
||||
loop (Node ("ExUid", [Loc; i])) j :
|
||||
'expr_ident));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (i : 'a_UIDENT) (loc : int * int) ->
|
||||
(Node ("ExUid", [Loc; i]) : 'expr_ident));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (i : 'a_LIDENT) (loc : int * int) ->
|
||||
(Node ("ExLid", [Loc; i]) : 'expr_ident));
|
||||
[Gramext.Snterm (Grammar.Entry.obj (anti_ : 'anti_ Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (a : 'anti_) (loc : int * int) -> (a : 'expr_ident))]];
|
||||
Grammar.Entry.obj (fun_def : 'fun_def Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("", "->");
|
||||
|
@ -1615,10 +1753,10 @@ Grammar.extend
|
|||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__18))]);
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__11))]);
|
||||
Gramext.Stoken ("", ")")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'e__18 option) (t : 'ctyp) _ (p : 'patt) _ _ (i : 'lident)
|
||||
(fun _ (e : 'e__11 option) (t : 'ctyp) _ (p : 'patt) _ _ (i : 'lident)
|
||||
_ (loc : int * int) ->
|
||||
(let p = Node ("PaTyc", [Loc; p; t]) in
|
||||
Node ("PaOlb", [Loc; i; p; Option e]) :
|
||||
|
@ -1632,10 +1770,10 @@ Grammar.extend
|
|||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__17))]);
|
||||
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__10))]);
|
||||
Gramext.Stoken ("", ")")],
|
||||
Gramext.action
|
||||
(fun _ (e : 'e__17 option) (p : 'patt) _ _ (i : 'lident) _
|
||||
(fun _ (e : 'e__10 option) (p : 'patt) _ _ (i : 'lident) _
|
||||
(loc : int * int) ->
|
||||
(Node ("PaOlb", [Loc; i; p; Option e]) : 'patt));
|
||||
[Gramext.Stoken ("", "~");
|
||||
|
@ -1737,10 +1875,10 @@ Grammar.extend
|
|||
Gramext.Snterm
|
||||
(Grammar.Entry.obj (patt : 'patt Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__19))]);
|
||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__12))]);
|
||||
Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
(fun _ (last : 'e__19 option) (pl : 'patt list) _ (loc : int * int) ->
|
||||
(fun _ (last : 'e__12 option) (pl : 'patt list) _ (loc : int * int) ->
|
||||
(mklistpat last pl : 'patt));
|
||||
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
|
||||
Gramext.action
|
||||
|
@ -2385,40 +2523,49 @@ Grammar.extend
|
|||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "" loc a : 'a_module_expr));
|
||||
[Gramext.Stoken ("ANTIQUOT", "module_expr")],
|
||||
[Gramext.Stoken ("ANTIQUOT", "mexp")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "module_expr" loc a : 'a_module_expr))]];
|
||||
(antiquot "mexp" loc a : 'a_module_expr))]];
|
||||
Grammar.Entry.obj (a_str_item : 'a_str_item Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "" loc a : 'a_str_item));
|
||||
[Gramext.Stoken ("ANTIQUOT", "str_item")],
|
||||
[Gramext.Stoken ("ANTIQUOT", "stri")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "str_item" loc a : 'a_str_item))]];
|
||||
(antiquot "stri" loc a : 'a_str_item))]];
|
||||
Grammar.Entry.obj (a_module_type : 'a_module_type Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "" loc a : 'a_module_type));
|
||||
[Gramext.Stoken ("ANTIQUOT", "module_type")],
|
||||
[Gramext.Stoken ("ANTIQUOT", "mtyp")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "module_type" loc a : 'a_module_type))]];
|
||||
(antiquot "mtyp" loc a : 'a_module_type))]];
|
||||
Grammar.Entry.obj (a_sig_item : 'a_sig_item Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "" loc a : 'a_sig_item));
|
||||
[Gramext.Stoken ("ANTIQUOT", "sig_item")],
|
||||
[Gramext.Stoken ("ANTIQUOT", "sigi")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "sig_item" loc a : 'a_sig_item))]];
|
||||
(antiquot "sigi" loc a : 'a_sig_item))]];
|
||||
Grammar.Entry.obj (a_expr : 'a_expr Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_expr));
|
||||
[Gramext.Stoken ("ANTIQUOT", "exp")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "exp" loc a : 'a_expr))]];
|
||||
Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("UIDENT", "")],
|
||||
|
@ -2445,11 +2592,35 @@ Grammar.extend
|
|||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "lid" loc a : 'a_LIDENT))]];
|
||||
Grammar.Entry.obj (a_INT : 'a_INT Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("INT", "")],
|
||||
Gramext.action (fun (s : string) (loc : int * int) -> (Str s : 'a_INT));
|
||||
[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_INT));
|
||||
[Gramext.Stoken ("ANTIQUOT", "int")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "int" loc a : 'a_INT))]];
|
||||
Grammar.Entry.obj (a_FLOAT : 'a_FLOAT Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("FLOAT", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) -> (Str s : 'a_FLOAT));
|
||||
[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "" loc a : 'a_FLOAT));
|
||||
[Gramext.Stoken ("ANTIQUOT", "flo")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "flo" loc a : 'a_FLOAT))]];
|
||||
Grammar.Entry.obj (a_STRING : 'a_STRING Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("STRING", "")],
|
||||
Gramext.action
|
||||
(fun (i : string) (loc : int * int) -> (Str i : 'a_STRING));
|
||||
(fun (s : string) (loc : int * int) -> (Str s : 'a_STRING));
|
||||
[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
|
@ -2458,6 +2629,18 @@ Grammar.extend
|
|||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "str" loc a : 'a_STRING))]];
|
||||
Grammar.Entry.obj (a_CHAR : 'a_CHAR Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("CHAR", "")],
|
||||
Gramext.action
|
||||
(fun (s : string) (loc : int * int) -> (Str s : 'a_CHAR));
|
||||
[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_CHAR));
|
||||
[Gramext.Stoken ("ANTIQUOT", "chr")],
|
||||
Gramext.action
|
||||
(fun (a : string) (loc : int * int) ->
|
||||
(antiquot "chr" loc a : 'a_CHAR))]];
|
||||
Grammar.Entry.obj (anti_ : 'anti_ Grammar.Entry.e), None,
|
||||
[None, None,
|
||||
[[Gramext.Stoken ("ANTIQUOT", "")],
|
||||
|
@ -2809,9 +2992,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (cf : 'class_str_item) (loc : int * int) ->
|
||||
(cf : 'e__20))])],
|
||||
(cf : 'e__13))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__20 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__13 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -2907,9 +3090,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (s : 'class_str_item) (loc : int * int) ->
|
||||
(s : 'e__21))])],
|
||||
(s : 'e__14))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__21 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__14 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -2983,9 +3166,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (csf : 'class_sig_item) (loc : int * int) ->
|
||||
(csf : 'e__22))])],
|
||||
(csf : 'e__15))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__22 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__15 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
@ -3106,9 +3289,9 @@ Grammar.extend
|
|||
Gramext.Stoken ("", ";")],
|
||||
Gramext.action
|
||||
(fun _ (s : 'class_sig_item) (loc : int * int) ->
|
||||
(s : 'e__23))])],
|
||||
(s : 'e__16))])],
|
||||
Gramext.action
|
||||
(fun (l : 'e__23 list) (loc : int * int) -> (List l : 'anti));
|
||||
(fun (l : 'e__16 list) (loc : int * int) -> (List l : 'anti));
|
||||
[Gramext.Snterm
|
||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||
Gramext.action
|
||||
|
|
Loading…
Reference in New Issue