This commit is contained in:
Pierre-Emmanuel Wulfman 2020-05-27 19:48:17 +02:00
parent 44ee2be055
commit 195175287a
20 changed files with 1269 additions and 1120 deletions

View File

@ -0,0 +1,55 @@
open Cli_expect
let contract basename =
"../../test/contracts/" ^ basename
let bad_contract basename =
"../../test/contracts/negative/" ^ basename
let%expect_test _ =
run_ligo_bad [ "compile-contract" ; bad_contract "bad_michelson_insertion_1.ligo" ; "main" ] ;
[%expect{|
ligo: generated Michelson contract failed to typecheck: bad contract type
{ parameter nat ;
storage nat ;
code { DUP ;
LAMBDA (pair nat nat) nat ADD ;
SWAP ;
EXEC ;
NIL operation ;
PAIR ;
DIP { DROP } } }
If you're not sure how to fix this error, you can
do one of the following:
* Visit our documentation: https://ligolang.org/docs/intro/introduction
* Ask a question on our Discord: https://discord.gg/9rhYaEt
* Open a gitlab issue: https://gitlab.com/ligolang/ligo/issues/new
* Check the changelog by running 'ligo changelog' |}]
let%expect_test _ =
run_ligo_bad [ "compile-contract" ; bad_contract "bad_michelson_insertion_2.ligo" ; "main" ] ;
[%expect{|
ligo: in file "bad_michelson_insertion_2.ligo", line 5, characters 32-40. different kinds: {"a":"nat","b":"( nat * nat )"}
If you're not sure how to fix this error, you can
do one of the following:
* Visit our documentation: https://ligolang.org/docs/intro/introduction
* Ask a question on our Discord: https://discord.gg/9rhYaEt
* Open a gitlab issue: https://gitlab.com/ligolang/ligo/issues/new
* Check the changelog by running 'ligo changelog' |}]
let%expect_test _ =
run_ligo_good [ "compile-contract" ; bad_contract "bad_michelson_insertion_3.ligo" ; "main" ] ;
[%expect{|
{ parameter nat ;
storage nat ;
code { DUP ;
LAMBDA (pair nat nat) nat { { { DUP ; CDR ; SWAP ; CAR } } ; ADD } ;
SWAP ;
EXEC ;
NIL operation ;
PAIR ;
DIP { DROP } } } |}]

View File

@ -227,26 +227,26 @@ and field_pattern = {
} }
and expr = and expr =
ECase of expr case reg ECase of expr case reg
| ECond of cond_expr reg | ECond of cond_expr reg
| EAnnot of annot_expr par reg | EAnnot of annot_expr par reg
| ELogic of logic_expr | ELogic of logic_expr
| EArith of arith_expr | EArith of arith_expr
| EString of string_expr | EString of string_expr
| EList of list_expr | EList of list_expr
| EConstr of constr_expr | EConstr of constr_expr
| ERecord of record reg | ERecord of record reg
| EProj of projection reg | EProj of projection reg
| EUpdate of update reg | EUpdate of update reg
| EVar of variable | EVar of variable
| ECall of (expr * expr nseq) reg | ECall of (expr * expr nseq) reg
| EBytes of (string * Hex.t) reg | EBytes of (string * Hex.t) reg
| EUnit of the_unit reg | EUnit of the_unit reg
| ETuple of (expr, comma) nsepseq reg | ETuple of (expr, comma) nsepseq reg
| EPar of expr par reg | EPar of expr par reg
| ELetIn of let_in reg | ELetIn of let_in reg
| EFun of fun_expr reg | EFun of fun_expr reg
| ESeq of expr injection reg | ESeq of expr injection reg
| ECodeInsert of code_insert reg | ECodeInsert of code_insert reg
and annot_expr = expr * colon * type_expr and annot_expr = expr * colon * type_expr

View File

@ -132,26 +132,27 @@ and pp_type_decl decl =
^^ group (nest padding (break 1 ^^ pp_type_expr type_expr)) ^^ group (nest padding (break 1 ^^ pp_type_expr type_expr))
and pp_expr = function and pp_expr = function
ECase e -> pp_case_expr e ECase e -> pp_case_expr e
| ECond e -> group (pp_cond_expr e) | ECond e -> group (pp_cond_expr e)
| EAnnot e -> pp_annot_expr e | EAnnot e -> pp_annot_expr e
| ELogic e -> group (pp_logic_expr e) | ELogic e -> group (pp_logic_expr e)
| EArith e -> group (pp_arith_expr e) | EArith e -> group (pp_arith_expr e)
| EString e -> pp_string_expr e | EString e -> pp_string_expr e
| EList e -> group (pp_list_expr e) | EList e -> group (pp_list_expr e)
| EConstr e -> pp_constr_expr e | EConstr e -> pp_constr_expr e
| ERecord e -> pp_record_expr e | ERecord e -> pp_record_expr e
| EProj e -> pp_projection e | EProj e -> pp_projection e
| EUpdate e -> pp_update e | EUpdate e -> pp_update e
| EVar v -> pp_ident v | EVar v -> pp_ident v
| ECall e -> pp_call_expr e | ECall e -> pp_call_expr e
| EBytes e -> pp_bytes e | EBytes e -> pp_bytes e
| EUnit _ -> string "()" | EUnit _ -> string "()"
| ETuple e -> pp_tuple_expr e | ETuple e -> pp_tuple_expr e
| EPar e -> pp_par_expr e | EPar e -> pp_par_expr e
| ELetIn e -> pp_let_in e | ELetIn e -> pp_let_in e
| EFun e -> pp_fun e | EFun e -> pp_fun e
| ESeq e -> pp_seq e | ESeq e -> pp_seq e
| ECodeInsert e -> pp_code_insert e
and pp_case_expr {value; _} = and pp_case_expr {value; _} =
let {expr; cases; _} = value in let {expr; cases; _} = value in
@ -313,6 +314,12 @@ and pp_update {value; _} =
string "{" ^^ record ^^ string " with" string "{" ^^ record ^^ string " with"
^^ nest 2 (break 1 ^^ updates ^^ string "}") ^^ nest 2 (break 1 ^^ updates ^^ string "}")
and pp_code_insert {value; _} =
let {language; code; _} = value in
let language = pp_string language
and code = pp_expr code in
string "[%" ^^ language ^^ string " " ^^ code ^^ string " ]"
and pp_field_path_assign {value; _} = and pp_field_path_assign {value; _} =
let {field_path; field_expr; _} = value in let {field_path; field_expr; _} = value in
let path = pp_path field_path in let path = pp_path field_path in

View File

@ -963,7 +963,7 @@ interactive_expr: Begin Verbatim With
interactive_expr: Begin With interactive_expr: Begin With
## ##
## Ends in an error in state: 204. ## Ends in an error in state: 206.
## ##
## sequence -> Begin . option(series) End [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## sequence -> Begin . option(series) End [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
@ -1002,7 +1002,7 @@ interactive_expr: C_Some With
interactive_expr: Constr DOT Ident DOT With interactive_expr: Constr DOT Ident DOT With
## ##
## Ends in an error in state: 199. ## Ends in an error in state: 201.
## ##
## projection -> Constr DOT Ident DOT . nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## projection -> Constr DOT Ident DOT . nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
@ -1014,7 +1014,7 @@ interactive_expr: Constr DOT Ident DOT With
interactive_expr: Constr DOT Ident WILD interactive_expr: Constr DOT Ident WILD
## ##
## Ends in an error in state: 198. ## Ends in an error in state: 200.
## ##
## module_fun -> Ident . [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## module_fun -> Ident . [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## projection -> Constr DOT Ident . DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## projection -> Constr DOT Ident . DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
@ -1027,7 +1027,7 @@ interactive_expr: Constr DOT Ident WILD
interactive_expr: Constr DOT With interactive_expr: Constr DOT With
## ##
## Ends in an error in state: 196. ## Ends in an error in state: 198.
## ##
## module_field -> Constr DOT . module_fun [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## module_field -> Constr DOT . module_fun [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## projection -> Constr DOT . Ident DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## projection -> Constr DOT . Ident DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
@ -1040,7 +1040,7 @@ interactive_expr: Constr DOT With
interactive_expr: Constr WILD interactive_expr: Constr WILD
## ##
## Ends in an error in state: 195. ## Ends in an error in state: 197.
## ##
## constr_expr -> Constr . core_expr [ With VBAR Type Then TIMES SLASH SEMI RPAR RBRACKET RBRACE PLUS Or NE Mod MINUS Let LT LE In GT GE End Else EQ EOF CONS COMMA COLON CAT BOOL_OR BOOL_AND Attr ] ## constr_expr -> Constr . core_expr [ With VBAR Type Then TIMES SLASH SEMI RPAR RBRACKET RBRACE PLUS Or NE Mod MINUS Let LT LE In GT GE End Else EQ EOF CONS COMMA COLON CAT BOOL_OR BOOL_AND Attr ]
## constr_expr -> Constr . [ With VBAR Type Then TIMES SLASH SEMI RPAR RBRACKET RBRACE PLUS Or NE Mod MINUS Let LT LE In GT GE End Else EQ EOF CONS COMMA COLON CAT BOOL_OR BOOL_AND Attr ] ## constr_expr -> Constr . [ With VBAR Type Then TIMES SLASH SEMI RPAR RBRACKET RBRACE PLUS Or NE Mod MINUS Let LT LE In GT GE End Else EQ EOF CONS COMMA COLON CAT BOOL_OR BOOL_AND Attr ]
@ -1055,7 +1055,7 @@ interactive_expr: Constr WILD
interactive_expr: Fun WILD ARROW With interactive_expr: Fun WILD ARROW With
## ##
## Ends in an error in state: 193. ## Ends in an error in state: 195.
## ##
## fun_expr(expr) -> Fun nseq(irrefutable) ARROW . expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## fun_expr(expr) -> Fun nseq(irrefutable) ARROW . expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -1103,7 +1103,7 @@ interactive_expr: Fun WILD WILD RPAR
interactive_expr: Fun With interactive_expr: Fun With
## ##
## Ends in an error in state: 191. ## Ends in an error in state: 193.
## ##
## fun_expr(expr) -> Fun . nseq(irrefutable) ARROW expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## fun_expr(expr) -> Fun . nseq(irrefutable) ARROW expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -1115,7 +1115,7 @@ interactive_expr: Fun With
interactive_expr: Ident DOT Int DOT With interactive_expr: Ident DOT Int DOT With
## ##
## Ends in an error in state: 188. ## Ends in an error in state: 190.
## ##
## nsepseq(selection,DOT) -> selection DOT . nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## nsepseq(selection,DOT) -> selection DOT . nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
@ -1127,7 +1127,7 @@ interactive_expr: Ident DOT Int DOT With
interactive_expr: Ident DOT Int WILD interactive_expr: Ident DOT Int WILD
## ##
## Ends in an error in state: 187. ## Ends in an error in state: 189.
## ##
## nsepseq(selection,DOT) -> selection . [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## nsepseq(selection,DOT) -> selection . [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## nsepseq(selection,DOT) -> selection . DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## nsepseq(selection,DOT) -> selection . DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
@ -1140,7 +1140,7 @@ interactive_expr: Ident DOT Int WILD
interactive_expr: Ident DOT With interactive_expr: Ident DOT With
## ##
## Ends in an error in state: 184. ## Ends in an error in state: 186.
## ##
## projection -> Ident DOT . nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## projection -> Ident DOT . nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
@ -1152,7 +1152,7 @@ interactive_expr: Ident DOT With
interactive_expr: Ident WILD interactive_expr: Ident WILD
## ##
## Ends in an error in state: 183. ## Ends in an error in state: 185.
## ##
## core_expr -> Ident . [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## core_expr -> Ident . [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## projection -> Ident . DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## projection -> Ident . DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
@ -1275,8 +1275,8 @@ interactive_expr: If Verbatim Then Let Rec WILD EQ Bytes Attr Type
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -1352,8 +1352,8 @@ interactive_expr: If Verbatim Then Let WILD EQ Bytes Attr Type
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -1585,8 +1585,8 @@ interactive_expr: If Verbatim Then Match Verbatim With WILD ARROW Let Rec WILD E
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -1662,8 +1662,8 @@ interactive_expr: If Verbatim Then Match Verbatim With WILD ARROW Let WILD EQ By
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -1787,6 +1787,9 @@ interactive_expr: If Verbatim Then Match Verbatim With WILD CONS Bytes SEMI
## In state 97, spurious reduction of production tail -> sub_pattern ## In state 97, spurious reduction of production tail -> sub_pattern
## In state 252, spurious reduction of production pattern -> sub_pattern CONS tail ## In state 252, spurious reduction of production pattern -> sub_pattern CONS tail
## ##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: If Verbatim Then Match Verbatim With With interactive_expr: If Verbatim Then Match Verbatim With With
## ##
## Ends in an error in state: 496. ## Ends in an error in state: 496.
@ -1930,7 +1933,7 @@ interactive_expr: If Verbatim With
interactive_expr: If With interactive_expr: If With
## ##
## Ends in an error in state: 182. ## Ends in an error in state: 184.
## ##
## if_then(expr) -> If . expr Then expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## if_then(expr) -> If . expr Then expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## if_then_else(expr) -> If . expr Then closed_if Else expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## if_then_else(expr) -> If . expr Then closed_if Else expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
@ -1999,7 +2002,7 @@ interactive_expr: LBRACE Ident DOT Ident Verbatim
interactive_expr: LBRACE Ident EQ Bytes SEMI Ident EQ Bytes SEMI With interactive_expr: LBRACE Ident EQ Bytes SEMI Ident EQ Bytes SEMI With
## ##
## Ends in an error in state: 557. ## Ends in an error in state: 555.
## ##
## nsepseq(field_assignment,SEMI) -> field_assignment SEMI . nsepseq(field_assignment,SEMI) [ RBRACE ] ## nsepseq(field_assignment,SEMI) -> field_assignment SEMI . nsepseq(field_assignment,SEMI) [ RBRACE ]
## seq(__anonymous_0(field_assignment,SEMI)) -> field_assignment SEMI . seq(__anonymous_0(field_assignment,SEMI)) [ RBRACE ] ## seq(__anonymous_0(field_assignment,SEMI)) -> field_assignment SEMI . seq(__anonymous_0(field_assignment,SEMI)) [ RBRACE ]
@ -2012,7 +2015,7 @@ interactive_expr: LBRACE Ident EQ Bytes SEMI Ident EQ Bytes SEMI With
interactive_expr: LBRACE Ident EQ Bytes SEMI Ident EQ Bytes With interactive_expr: LBRACE Ident EQ Bytes SEMI Ident EQ Bytes With
## ##
## Ends in an error in state: 556. ## Ends in an error in state: 554.
## ##
## nsepseq(field_assignment,SEMI) -> field_assignment . [ RBRACE ] ## nsepseq(field_assignment,SEMI) -> field_assignment . [ RBRACE ]
## nsepseq(field_assignment,SEMI) -> field_assignment . SEMI nsepseq(field_assignment,SEMI) [ RBRACE ] ## nsepseq(field_assignment,SEMI) -> field_assignment . SEMI nsepseq(field_assignment,SEMI) [ RBRACE ]
@ -2044,7 +2047,7 @@ interactive_expr: LBRACE Ident EQ Bytes SEMI Ident EQ Bytes With
interactive_expr: LBRACE Ident EQ Bytes SEMI Ident With interactive_expr: LBRACE Ident EQ Bytes SEMI Ident With
## ##
## Ends in an error in state: 553. ## Ends in an error in state: 551.
## ##
## field_assignment -> Ident . EQ expr [ SEMI RBRACE ] ## field_assignment -> Ident . EQ expr [ SEMI RBRACE ]
## ##
@ -2056,7 +2059,7 @@ interactive_expr: LBRACE Ident EQ Bytes SEMI Ident With
interactive_expr: LBRACE Ident EQ Bytes SEMI With interactive_expr: LBRACE Ident EQ Bytes SEMI With
## ##
## Ends in an error in state: 552. ## Ends in an error in state: 550.
## ##
## nsepseq(field_assignment,SEMI) -> field_assignment SEMI . nsepseq(field_assignment,SEMI) [ RBRACE ] ## nsepseq(field_assignment,SEMI) -> field_assignment SEMI . nsepseq(field_assignment,SEMI) [ RBRACE ]
## nseq(__anonymous_0(field_assignment,SEMI)) -> field_assignment SEMI . seq(__anonymous_0(field_assignment,SEMI)) [ RBRACE ] ## nseq(__anonymous_0(field_assignment,SEMI)) -> field_assignment SEMI . seq(__anonymous_0(field_assignment,SEMI)) [ RBRACE ]
@ -2069,7 +2072,7 @@ interactive_expr: LBRACE Ident EQ Bytes SEMI With
interactive_expr: LBRACE Ident EQ Bytes With interactive_expr: LBRACE Ident EQ Bytes With
## ##
## Ends in an error in state: 551. ## Ends in an error in state: 549.
## ##
## nsepseq(field_assignment,SEMI) -> field_assignment . [ RBRACE ] ## nsepseq(field_assignment,SEMI) -> field_assignment . [ RBRACE ]
## nsepseq(field_assignment,SEMI) -> field_assignment . SEMI nsepseq(field_assignment,SEMI) [ RBRACE ] ## nsepseq(field_assignment,SEMI) -> field_assignment . SEMI nsepseq(field_assignment,SEMI) [ RBRACE ]
@ -2101,7 +2104,7 @@ interactive_expr: LBRACE Ident EQ Bytes With
interactive_expr: LBRACE Ident EQ With interactive_expr: LBRACE Ident EQ With
## ##
## Ends in an error in state: 180. ## Ends in an error in state: 182.
## ##
## field_assignment -> Ident EQ . expr [ SEMI RBRACE ] ## field_assignment -> Ident EQ . expr [ SEMI RBRACE ]
## ##
@ -2113,7 +2116,7 @@ interactive_expr: LBRACE Ident EQ With
interactive_expr: LBRACE Ident WILD interactive_expr: LBRACE Ident WILD
## ##
## Ends in an error in state: 179. ## Ends in an error in state: 181.
## ##
## field_assignment -> Ident . EQ expr [ SEMI RBRACE ] ## field_assignment -> Ident . EQ expr [ SEMI RBRACE ]
## path -> Ident . [ With ] ## path -> Ident . [ With ]
@ -2125,21 +2128,29 @@ interactive_expr: LBRACE Ident WILD
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident DOT With interactive_expr: LBRACE Ident With Ident DOT Ident With
## ##
## Ends in an error in state: 533. ## Ends in an error in state: 535.
## ##
## nsepseq(field_name,DOT) -> Ident DOT . nsepseq(field_name,DOT) [ EQ ] ## field_path_assignment -> path . EQ expr [ SEMI RBRACE ]
## ##
## The known suffix of the stack is as follows: ## The known suffix of the stack is as follows:
## Ident DOT ## path
##
## WARNING: This example involves spurious reductions.
## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next).
## In state 189, spurious reduction of production nsepseq(selection,DOT) -> selection
## In state 192, spurious reduction of production projection -> Ident DOT nsepseq(selection,DOT)
## In state 529, spurious reduction of production path -> projection
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident EQ Bytes SEMI Ident EQ Bytes SEMI With interactive_expr: LBRACE Ident With Ident EQ Bytes SEMI Ident EQ Bytes SEMI With
## ##
## Ends in an error in state: 547. ## Ends in an error in state: 545.
## ##
## nsepseq(field_path_assignment,SEMI) -> field_path_assignment SEMI . nsepseq(field_path_assignment,SEMI) [ RBRACE ] ## nsepseq(field_path_assignment,SEMI) -> field_path_assignment SEMI . nsepseq(field_path_assignment,SEMI) [ RBRACE ]
## seq(__anonymous_0(field_path_assignment,SEMI)) -> field_path_assignment SEMI . seq(__anonymous_0(field_path_assignment,SEMI)) [ RBRACE ] ## seq(__anonymous_0(field_path_assignment,SEMI)) -> field_path_assignment SEMI . seq(__anonymous_0(field_path_assignment,SEMI)) [ RBRACE ]
@ -2150,9 +2161,9 @@ interactive_expr: LBRACE Ident With Ident EQ Bytes SEMI Ident EQ Bytes SEMI With
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident DOT Ident EQ Bytes SEMI Ident DOT Ident EQ Bytes With interactive_expr: LBRACE Ident With Ident EQ Bytes SEMI Ident EQ Bytes With
## ##
## Ends in an error in state: 546. ## Ends in an error in state: 544.
## ##
## nsepseq(field_path_assignment,SEMI) -> field_path_assignment . [ RBRACE ] ## nsepseq(field_path_assignment,SEMI) -> field_path_assignment . [ RBRACE ]
## nsepseq(field_path_assignment,SEMI) -> field_path_assignment . SEMI nsepseq(field_path_assignment,SEMI) [ RBRACE ] ## nsepseq(field_path_assignment,SEMI) -> field_path_assignment . SEMI nsepseq(field_path_assignment,SEMI) [ RBRACE ]
@ -2177,23 +2188,109 @@ interactive_expr: LBRACE Ident With Ident DOT Ident EQ Bytes SEMI Ident DOT Iden
## In state 371, spurious reduction of production base_expr(expr) -> disj_expr_level ## In state 371, spurious reduction of production base_expr(expr) -> disj_expr_level
## In state 373, spurious reduction of production base_cond__open(expr) -> base_expr(expr) ## In state 373, spurious reduction of production base_cond__open(expr) -> base_expr(expr)
## In state 374, spurious reduction of production expr -> base_cond__open(expr) ## In state 374, spurious reduction of production expr -> base_cond__open(expr)
## In state 541, spurious reduction of production field_path_assignment -> nsepseq(field_name,DOT) EQ expr ## In state 537, spurious reduction of production field_path_assignment -> path EQ expr
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident DOT Ident EQ Bytes SEMI With interactive_expr: LBRACE Ident With Ident EQ Bytes SEMI With
## ##
## Ends in an error in state: 541.
##
## nsepseq(field_path_assignment,SEMI) -> field_path_assignment SEMI . nsepseq(field_path_assignment,SEMI) [ RBRACE ]
## nseq(__anonymous_0(field_path_assignment,SEMI)) -> field_path_assignment SEMI . seq(__anonymous_0(field_path_assignment,SEMI)) [ RBRACE ]
##
## The known suffix of the stack is as follows:
## field_path_assignment SEMI
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident EQ Bytes With
##
## Ends in an error in state: 540.
##
## nsepseq(field_path_assignment,SEMI) -> field_path_assignment . [ RBRACE ]
## nsepseq(field_path_assignment,SEMI) -> field_path_assignment . SEMI nsepseq(field_path_assignment,SEMI) [ RBRACE ]
## nseq(__anonymous_0(field_path_assignment,SEMI)) -> field_path_assignment . SEMI seq(__anonymous_0(field_path_assignment,SEMI)) [ RBRACE ]
##
## The known suffix of the stack is as follows:
## field_path_assignment
##
## WARNING: This example involves spurious reductions.
## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next).
## In state 227, spurious reduction of production call_expr_level -> core_expr
## In state 234, spurious reduction of production unary_expr_level -> call_expr_level
## In state 221, spurious reduction of production mult_expr_level -> unary_expr_level
## In state 224, spurious reduction of production add_expr_level -> mult_expr_level
## In state 314, spurious reduction of production cons_expr_level -> add_expr_level
## In state 304, spurious reduction of production cat_expr_level -> cons_expr_level
## In state 336, spurious reduction of production comp_expr_level -> cat_expr_level
## In state 343, spurious reduction of production conj_expr_level -> comp_expr_level
## In state 350, spurious reduction of production disj_expr_level -> conj_expr_level
## In state 371, spurious reduction of production base_expr(expr) -> disj_expr_level
## In state 373, spurious reduction of production base_cond__open(expr) -> base_expr(expr)
## In state 374, spurious reduction of production expr -> base_cond__open(expr)
## In state 537, spurious reduction of production field_path_assignment -> path EQ expr
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident EQ With
##
## Ends in an error in state: 536.
##
## field_path_assignment -> path EQ . expr [ SEMI RBRACE ]
##
## The known suffix of the stack is as follows:
## path EQ
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident With
##
## Ends in an error in state: 532.
##
## path -> Ident . [ EQ ]
## projection -> Ident . DOT nsepseq(selection,DOT) [ EQ ]
##
## The known suffix of the stack is as follows:
## Ident
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With With
##
## Ends in an error in state: 531.
##
## update_record -> LBRACE path With . sep_or_term_list(field_path_assignment,SEMI) RBRACE [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
##
## The known suffix of the stack is as follows:
## LBRACE path With
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE With
##
## Ends in an error in state: 180.
##
## record_expr -> LBRACE . sep_or_term_list(field_assignment,SEMI) RBRACE [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## update_record -> LBRACE . path With sep_or_term_list(field_path_assignment,SEMI) RBRACE [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## update_record -> LBRACE . path With sep_or_term_list(field_path_assignment,SEMI) RBRACE [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
##
## The known suffix of the stack is as follows: ## The known suffix of the stack is as follows:
## LBRACE ## LBRACE
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident DOT Ident EQ Bytes With interactive_expr: LBRACKET PERCENT Constr Verbatim With
## ##
## Ends in an error in state: 542. ## Ends in an error in state: 560.
## ##
## code_insert -> LBRACKET PERCENT Constr expr . RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## code_insert -> LBRACKET PERCENT Constr expr . RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
@ -2216,95 +2313,27 @@ interactive_expr: LBRACE Ident With Ident DOT Ident EQ Bytes With
## In state 371, spurious reduction of production base_expr(expr) -> disj_expr_level ## In state 371, spurious reduction of production base_expr(expr) -> disj_expr_level
## In state 373, spurious reduction of production base_cond__open(expr) -> base_expr(expr) ## In state 373, spurious reduction of production base_cond__open(expr) -> base_expr(expr)
## In state 374, spurious reduction of production expr -> base_cond__open(expr) ## In state 374, spurious reduction of production expr -> base_cond__open(expr)
## In state 541, spurious reduction of production field_path_assignment -> nsepseq(field_name,DOT) EQ expr
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident EQ With interactive_expr: LBRACKET PERCENT Constr With
## ##
## Ends in an error in state: 540. ## Ends in an error in state: 172.
## ##
## field_path_assignment -> nsepseq(field_name,DOT) EQ . expr [ SEMI RBRACE ] ## code_insert -> LBRACKET PERCENT Constr . expr RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
## The known suffix of the stack is as follows: ## The known suffix of the stack is as follows:
## nsepseq(field_name,DOT) EQ ## LBRACKET PERCENT Constr
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident With
##
## Ends in an error in state: 532.
##
## nsepseq(field_name,DOT) -> Ident . [ EQ ]
## nsepseq(field_name,DOT) -> Ident . DOT nsepseq(field_name,DOT) [ EQ ]
##
## The known suffix of the stack is as follows:
## Ident
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With With
##
## Ends in an error in state: 531.
##
## update_record -> LBRACE path With . sep_or_term_list(field_path_assignment,SEMI) RBRACE [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
##
## The known suffix of the stack is as follows:
## LBRACE path With
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident DOT Ident EQ With
##
## Ends in an error in state: 533.
##
## field_path_assignment -> path EQ . expr [ SEMI RBRACE ]
##
## The known suffix of the stack is as follows:
## path EQ
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE Ident With Ident DOT Ident With
##
## Ends in an error in state: 562.
##
## field_path_assignment -> path . EQ expr [ SEMI RBRACE ]
##
## The known suffix of the stack is as follows:
## path
##
## WARNING: This example involves spurious reductions.
## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next).
## In state 227, spurious reduction of production call_expr_level -> core_expr
## In state 234, spurious reduction of production unary_expr_level -> call_expr_level
## In state 221, spurious reduction of production mult_expr_level -> unary_expr_level
## In state 224, spurious reduction of production add_expr_level -> mult_expr_level
## In state 314, spurious reduction of production cons_expr_level -> add_expr_level
## In state 304, spurious reduction of production cat_expr_level -> cons_expr_level
## In state 336, spurious reduction of production comp_expr_level -> cat_expr_level
## In state 343, spurious reduction of production conj_expr_level -> comp_expr_level
## In state 350, spurious reduction of production disj_expr_level -> conj_expr_level
## In state 371, spurious reduction of production base_expr(expr) -> disj_expr_level
## In state 373, spurious reduction of production base_cond__open(expr) -> base_expr(expr)
## In state 374, spurious reduction of production expr -> base_cond__open(expr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACKET PERCENT With interactive_expr: LBRACKET PERCENT With
## ##
## Ends in an error in state: 529. ## Ends in an error in state: 171.
## ##
## path -> Ident . [ EQ ] ## code_insert -> LBRACKET PERCENT . Constr expr RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## projection -> Ident . DOT nsepseq(selection,DOT) [ EQ ]
## ##
## The known suffix of the stack is as follows: ## The known suffix of the stack is as follows:
## LBRACKET PERCENT ## LBRACKET PERCENT
@ -2312,21 +2341,9 @@ interactive_expr: LBRACKET PERCENT With
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACKET Verbatim End
##
## Ends in an error in state: 528.
##
## update_record -> LBRACE path With . sep_or_term_list(field_path_assignment,SEMI) RBRACE [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
##
## The known suffix of the stack is as follows:
## LBRACE path With
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACKET Verbatim SEMI Verbatim SEMI With interactive_expr: LBRACKET Verbatim SEMI Verbatim SEMI With
## ##
## Ends in an error in state: 574. ## Ends in an error in state: 572.
## ##
## nsepseq(expr,SEMI) -> expr SEMI . nsepseq(expr,SEMI) [ RBRACKET ] ## nsepseq(expr,SEMI) -> expr SEMI . nsepseq(expr,SEMI) [ RBRACKET ]
## seq(__anonymous_0(expr,SEMI)) -> expr SEMI . seq(__anonymous_0(expr,SEMI)) [ RBRACKET ] ## seq(__anonymous_0(expr,SEMI)) -> expr SEMI . seq(__anonymous_0(expr,SEMI)) [ RBRACKET ]
@ -2339,7 +2356,7 @@ interactive_expr: LBRACKET Verbatim SEMI Verbatim SEMI With
interactive_expr: LBRACKET Verbatim SEMI Verbatim With interactive_expr: LBRACKET Verbatim SEMI Verbatim With
## ##
## Ends in an error in state: 573. ## Ends in an error in state: 571.
## ##
## nsepseq(expr,SEMI) -> expr . [ RBRACKET ] ## nsepseq(expr,SEMI) -> expr . [ RBRACKET ]
## nsepseq(expr,SEMI) -> expr . SEMI nsepseq(expr,SEMI) [ RBRACKET ] ## nsepseq(expr,SEMI) -> expr . SEMI nsepseq(expr,SEMI) [ RBRACKET ]
@ -2370,7 +2387,7 @@ interactive_expr: LBRACKET Verbatim SEMI Verbatim With
interactive_expr: LBRACKET Verbatim SEMI With interactive_expr: LBRACKET Verbatim SEMI With
## ##
## Ends in an error in state: 570. ## Ends in an error in state: 568.
## ##
## nsepseq(expr,SEMI) -> expr SEMI . nsepseq(expr,SEMI) [ RBRACKET ] ## nsepseq(expr,SEMI) -> expr SEMI . nsepseq(expr,SEMI) [ RBRACKET ]
## nseq(__anonymous_0(expr,SEMI)) -> expr SEMI . seq(__anonymous_0(expr,SEMI)) [ RBRACKET ] ## nseq(__anonymous_0(expr,SEMI)) -> expr SEMI . seq(__anonymous_0(expr,SEMI)) [ RBRACKET ]
@ -2383,7 +2400,7 @@ interactive_expr: LBRACKET Verbatim SEMI With
interactive_expr: LBRACKET Verbatim With interactive_expr: LBRACKET Verbatim With
## ##
## Ends in an error in state: 569. ## Ends in an error in state: 567.
## ##
## nsepseq(expr,SEMI) -> expr . [ RBRACKET ] ## nsepseq(expr,SEMI) -> expr . [ RBRACKET ]
## nsepseq(expr,SEMI) -> expr . SEMI nsepseq(expr,SEMI) [ RBRACKET ] ## nsepseq(expr,SEMI) -> expr . SEMI nsepseq(expr,SEMI) [ RBRACKET ]
@ -2416,6 +2433,7 @@ interactive_expr: LBRACKET With
## ##
## Ends in an error in state: 170. ## Ends in an error in state: 170.
## ##
## code_insert -> LBRACKET . PERCENT Constr expr RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## list__(expr) -> LBRACKET . option(sep_or_term_list(expr,SEMI)) RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## list__(expr) -> LBRACKET . option(sep_or_term_list(expr,SEMI)) RBRACKET [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
## The known suffix of the stack is as follows: ## The known suffix of the stack is as follows:
@ -2426,7 +2444,7 @@ interactive_expr: LBRACKET With
interactive_expr: LPAR Verbatim COLON Ident VBAR interactive_expr: LPAR Verbatim COLON Ident VBAR
## ##
## Ends in an error in state: 587. ## Ends in an error in state: 586.
## ##
## par(annot_expr) -> LPAR annot_expr . RPAR [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## par(annot_expr) -> LPAR annot_expr . RPAR [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## ##
@ -2440,14 +2458,14 @@ interactive_expr: LPAR Verbatim COLON Ident VBAR
## In state 28, spurious reduction of production cartesian -> core_type ## In state 28, spurious reduction of production cartesian -> core_type
## In state 36, spurious reduction of production fun_type -> cartesian ## In state 36, spurious reduction of production fun_type -> cartesian
## In state 27, spurious reduction of production type_expr -> fun_type ## In state 27, spurious reduction of production type_expr -> fun_type
## In state 580, spurious reduction of production annot_expr -> expr COLON type_expr ## In state 585, spurious reduction of production annot_expr -> expr COLON type_expr
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LPAR Verbatim COLON With interactive_expr: LPAR Verbatim COLON With
## ##
## Ends in an error in state: 586. ## Ends in an error in state: 584.
## ##
## annot_expr -> expr COLON . type_expr [ RPAR ] ## annot_expr -> expr COLON . type_expr [ RPAR ]
## ##
@ -2459,7 +2477,7 @@ interactive_expr: LPAR Verbatim COLON With
interactive_expr: LPAR Verbatim With interactive_expr: LPAR Verbatim With
## ##
## Ends in an error in state: 584. ## Ends in an error in state: 582.
## ##
## annot_expr -> expr . COLON type_expr [ RPAR ] ## annot_expr -> expr . COLON type_expr [ RPAR ]
## par(expr) -> LPAR expr . RPAR [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## par(expr) -> LPAR expr . RPAR [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
@ -2503,7 +2521,7 @@ interactive_expr: LPAR With
interactive_expr: Let Rec WILD EQ Bytes Attr Type interactive_expr: Let Rec WILD EQ Bytes Attr Type
## ##
## Ends in an error in state: 176. ## Ends in an error in state: 178.
## ##
## let_expr(expr) -> Let Rec let_binding seq(Attr) . In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let Rec let_binding seq(Attr) . In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2514,15 +2532,15 @@ interactive_expr: Let Rec WILD EQ Bytes Attr Type
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: Let Rec WILD EQ Bytes In With interactive_expr: Let Rec WILD EQ Bytes In With
## ##
## Ends in an error in state: 177. ## Ends in an error in state: 179.
## ##
## let_expr(expr) -> Let Rec let_binding seq(Attr) In . expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let Rec let_binding seq(Attr) In . expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2534,7 +2552,7 @@ interactive_expr: Let Rec WILD EQ Bytes In With
interactive_expr: Let Rec WILD EQ Bytes With interactive_expr: Let Rec WILD EQ Bytes With
## ##
## Ends in an error in state: 173. ## Ends in an error in state: 175.
## ##
## let_expr(expr) -> Let Rec let_binding . seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let Rec let_binding . seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2564,7 +2582,7 @@ interactive_expr: Let Rec WILD EQ Bytes With
interactive_expr: Let Rec With interactive_expr: Let Rec With
## ##
## Ends in an error in state: 172. ## Ends in an error in state: 174.
## ##
## let_expr(expr) -> Let Rec . let_binding seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let Rec . let_binding seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2576,7 +2594,7 @@ interactive_expr: Let Rec With
interactive_expr: Let WILD EQ Bytes Attr Type interactive_expr: Let WILD EQ Bytes Attr Type
## ##
## Ends in an error in state: 560. ## Ends in an error in state: 558.
## ##
## let_expr(expr) -> Let let_binding seq(Attr) . In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let let_binding seq(Attr) . In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2587,15 +2605,15 @@ interactive_expr: Let WILD EQ Bytes Attr Type
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: Let WILD EQ Bytes In With interactive_expr: Let WILD EQ Bytes In With
## ##
## Ends in an error in state: 561. ## Ends in an error in state: 559.
## ##
## let_expr(expr) -> Let let_binding seq(Attr) In . expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let let_binding seq(Attr) In . expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2607,7 +2625,7 @@ interactive_expr: Let WILD EQ Bytes In With
interactive_expr: Let WILD EQ Bytes With interactive_expr: Let WILD EQ Bytes With
## ##
## Ends in an error in state: 559. ## Ends in an error in state: 557.
## ##
## let_expr(expr) -> Let let_binding . seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let let_binding . seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2637,7 +2655,7 @@ interactive_expr: Let WILD EQ Bytes With
interactive_expr: Let With interactive_expr: Let With
## ##
## Ends in an error in state: 171. ## Ends in an error in state: 173.
## ##
## let_expr(expr) -> Let . let_binding seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let . let_binding seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## let_expr(expr) -> Let . Rec let_binding seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## let_expr(expr) -> Let . Rec let_binding seq(Attr) In expr [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
@ -2662,7 +2680,7 @@ interactive_expr: MINUS With
interactive_expr: Match Verbatim Type interactive_expr: Match Verbatim Type
## ##
## Ends in an error in state: 577. ## Ends in an error in state: 575.
## ##
## match_expr(base_cond) -> Match expr . With option(VBAR) cases(base_cond) [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## match_expr(base_cond) -> Match expr . With option(VBAR) cases(base_cond) [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2704,7 +2722,7 @@ interactive_expr: Match Verbatim With LPAR Bytes RPAR With
interactive_expr: Match Verbatim With VBAR Begin interactive_expr: Match Verbatim With VBAR Begin
## ##
## Ends in an error in state: 579. ## Ends in an error in state: 577.
## ##
## match_expr(base_cond) -> Match expr With option(VBAR) . cases(base_cond) [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## match_expr(base_cond) -> Match expr With option(VBAR) . cases(base_cond) [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2716,7 +2734,7 @@ interactive_expr: Match Verbatim With VBAR Begin
interactive_expr: Match Verbatim With WILD ARROW Bytes VBAR With interactive_expr: Match Verbatim With WILD ARROW Bytes VBAR With
## ##
## Ends in an error in state: 583. ## Ends in an error in state: 581.
## ##
## cases(base_cond) -> cases(base_cond) VBAR . case_clause(base_cond) [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## cases(base_cond) -> cases(base_cond) VBAR . case_clause(base_cond) [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -2862,8 +2880,8 @@ interactive_expr: Match Verbatim With WILD ARROW If Verbatim Then Let Rec WILD E
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -2939,8 +2957,8 @@ interactive_expr: Match Verbatim With WILD ARROW If Verbatim Then Let WILD EQ By
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -3115,8 +3133,8 @@ interactive_expr: Match Verbatim With WILD ARROW Let Rec WILD EQ Bytes Attr Type
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -3188,8 +3206,8 @@ interactive_expr: Match Verbatim With WILD ARROW Let WILD EQ Bytes Attr Type
## This implies that, although the LR(1) items shown above provide an ## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they ## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next). ## may provide an INCOMPLETE view of the future (what was expected next).
## In state 174, spurious reduction of production seq(Attr) -> ## In state 176, spurious reduction of production seq(Attr) ->
## In state 175, spurious reduction of production seq(Attr) -> Attr seq(Attr) ## In state 177, spurious reduction of production seq(Attr) -> Attr seq(Attr)
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -3251,7 +3269,7 @@ interactive_expr: Match Verbatim With WILD ARROW Let With
interactive_expr: Match Verbatim With WILD ARROW Verbatim COMMA Bytes Else interactive_expr: Match Verbatim With WILD ARROW Verbatim COMMA Bytes Else
## ##
## Ends in an error in state: 582. ## Ends in an error in state: 580.
## ##
## cases(base_cond) -> cases(base_cond) . VBAR case_clause(base_cond) [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## cases(base_cond) -> cases(base_cond) . VBAR case_clause(base_cond) [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## match_expr(base_cond) -> Match expr With option(VBAR) cases(base_cond) . [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## match_expr(base_cond) -> Match expr With option(VBAR) cases(base_cond) . [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
@ -3315,7 +3333,7 @@ interactive_expr: Match Verbatim With WILD ARROW Verbatim End
interactive_expr: Match Verbatim With WILD ARROW With interactive_expr: Match Verbatim With WILD ARROW With
## ##
## Ends in an error in state: 581. ## Ends in an error in state: 579.
## ##
## case_clause(base_cond) -> pattern ARROW . base_cond [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## case_clause(base_cond) -> pattern ARROW . base_cond [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -3364,7 +3382,7 @@ interactive_expr: Match Verbatim With WILD COMMA With
interactive_expr: Match Verbatim With WILD CONS Bytes SEMI interactive_expr: Match Verbatim With WILD CONS Bytes SEMI
## ##
## Ends in an error in state: 580. ## Ends in an error in state: 578.
## ##
## case_clause(base_cond) -> pattern . ARROW base_cond [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## case_clause(base_cond) -> pattern . ARROW base_cond [ With VBAR Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -3408,7 +3426,7 @@ interactive_expr: Match Verbatim With WILD With
interactive_expr: Match Verbatim With With interactive_expr: Match Verbatim With With
## ##
## Ends in an error in state: 578. ## Ends in an error in state: 576.
## ##
## match_expr(base_cond) -> Match expr With . option(VBAR) cases(base_cond) [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ] ## match_expr(base_cond) -> Match expr With . option(VBAR) cases(base_cond) [ With Type Then SEMI RPAR RBRACKET RBRACE Let In EOF COLON Attr ]
## ##
@ -3545,7 +3563,7 @@ interactive_expr: Verbatim CONS With
interactive_expr: Verbatim Constr With interactive_expr: Verbatim Constr With
## ##
## Ends in an error in state: 202. ## Ends in an error in state: 204.
## ##
## module_field -> Constr . DOT module_fun [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## module_field -> Constr . DOT module_fun [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
## projection -> Constr . DOT Ident DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ] ## projection -> Constr . DOT Ident DOT nsepseq(selection,DOT) [ With Verbatim VBAR Type True Then TIMES String SLASH SEMI RPAR RBRACKET RBRACE PLUS Or Nat NE Mutez Mod MINUS Let LT LPAR LE LBRACKET LBRACE Int In Ident GT GE False End Else EQ EOF Constr CONS COMMA COLON CAT Bytes Begin BOOL_OR BOOL_AND Attr ]
@ -3798,7 +3816,7 @@ interactive_expr: Verbatim WILD
interactive_expr: Verbatim With interactive_expr: Verbatim With
## ##
## Ends in an error in state: 604. ## Ends in an error in state: 603.
## ##
## interactive_expr -> expr . EOF [ # ] ## interactive_expr -> expr . EOF [ # ]
## ##
@ -3827,7 +3845,7 @@ interactive_expr: Verbatim With
interactive_expr: With interactive_expr: With
## ##
## Ends in an error in state: 602. ## Ends in an error in state: 601.
## ##
## interactive_expr' -> . interactive_expr [ # ] ## interactive_expr' -> . interactive_expr [ # ]
## ##
@ -4273,7 +4291,7 @@ contract: Let LPAR With
contract: Let Rec WILD EQ Bytes With contract: Let Rec WILD EQ Bytes With
## ##
## Ends in an error in state: 591. ## Ends in an error in state: 590.
## ##
## let_declaration -> Let Rec let_binding . seq(Attr) [ Type Let EOF ] ## let_declaration -> Let Rec let_binding . seq(Attr) [ Type Let EOF ]
## ##
@ -4386,7 +4404,7 @@ contract: Let WILD COMMA With
contract: Let WILD EQ Bytes Attr With contract: Let WILD EQ Bytes Attr With
## ##
## Ends in an error in state: 174. ## Ends in an error in state: 176.
## ##
## seq(Attr) -> Attr . seq(Attr) [ Type Let In EOF ] ## seq(Attr) -> Attr . seq(Attr) [ Type Let In EOF ]
## ##
@ -4398,7 +4416,7 @@ contract: Let WILD EQ Bytes Attr With
contract: Let WILD EQ Bytes With contract: Let WILD EQ Bytes With
## ##
## Ends in an error in state: 593. ## Ends in an error in state: 592.
## ##
## let_declaration -> Let let_binding . seq(Attr) [ Type Let EOF ] ## let_declaration -> Let let_binding . seq(Attr) [ Type Let EOF ]
## ##
@ -4534,7 +4552,7 @@ contract: Type Ident EQ Constr With
contract: Type Ident EQ Ident VBAR contract: Type Ident EQ Ident VBAR
## ##
## Ends in an error in state: 599. ## Ends in an error in state: 598.
## ##
## declarations -> declaration . [ EOF ] ## declarations -> declaration . [ EOF ]
## declarations -> declaration . declarations [ EOF ] ## declarations -> declaration . declarations [ EOF ]
@ -4550,7 +4568,7 @@ contract: Type Ident EQ Ident VBAR
## In state 36, spurious reduction of production fun_type -> cartesian ## In state 36, spurious reduction of production fun_type -> cartesian
## In state 27, spurious reduction of production type_expr -> fun_type ## In state 27, spurious reduction of production type_expr -> fun_type
## In state 61, spurious reduction of production type_decl -> Type Ident EQ type_expr ## In state 61, spurious reduction of production type_decl -> Type Ident EQ type_expr
## In state 595, spurious reduction of production declaration -> type_decl ## In state 594, spurious reduction of production declaration -> type_decl
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
@ -4902,3 +4920,4 @@ contract: With
## ##
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>

View File

@ -361,26 +361,27 @@ and pp_collection = function
(* Expressions *) (* Expressions *)
and pp_expr = function and pp_expr = function
ECase e -> pp_case pp_expr e ECase e -> pp_case pp_expr e
| ECond e -> group (pp_cond_expr e) | ECond e -> group (pp_cond_expr e)
| EAnnot e -> pp_annot_expr e | EAnnot e -> pp_annot_expr e
| ELogic e -> group (pp_logic_expr e) | ELogic e -> group (pp_logic_expr e)
| EArith e -> group (pp_arith_expr e) | EArith e -> group (pp_arith_expr e)
| EString e -> pp_string_expr e | EString e -> pp_string_expr e
| EList e -> group (pp_list_expr e) | EList e -> group (pp_list_expr e)
| ESet e -> pp_set_expr e | ESet e -> pp_set_expr e
| EConstr e -> pp_constr_expr e | EConstr e -> pp_constr_expr e
| ERecord e -> pp_record e | ERecord e -> pp_record e
| EProj e -> pp_projection e | EProj e -> pp_projection e
| EUpdate e -> pp_update e | EUpdate e -> pp_update e
| EMap e -> pp_map_expr e | EMap e -> pp_map_expr e
| EVar e -> pp_ident e | EVar e -> pp_ident e
| ECall e -> pp_fun_call e | ECall e -> pp_fun_call e
| EBytes e -> pp_bytes e | EBytes e -> pp_bytes e
| EUnit _ -> string "Unit" | EUnit _ -> string "Unit"
| ETuple e -> pp_tuple_expr e | ETuple e -> pp_tuple_expr e
| EPar e -> pp_par pp_expr e | EPar e -> pp_par pp_expr e
| EFun e -> pp_fun_expr e | EFun e -> pp_fun_expr e
| ECodeInsert e -> pp_code_insert e
and pp_annot_expr {value; _} = and pp_annot_expr {value; _} =
let expr, _, type_expr = value.inside in let expr, _, type_expr = value.inside in
@ -495,6 +496,12 @@ and pp_update {value; _} =
and record = pp_path record in and record = pp_path record in
record ^^ string " with" ^^ nest 2 (break 1 ^^ updates) record ^^ string " with" ^^ nest 2 (break 1 ^^ updates)
and pp_code_insert {value; _} =
let {language; code; _} = value in
let language = pp_string language
and code = pp_expr code in
string "[%" ^^ language ^^ string " " ^^ code ^^ string " ]"
and pp_field_path_assign {value; _} = and pp_field_path_assign {value; _} =
let {field_path; field_expr; _} = value in let {field_path; field_expr; _} = value in
let path = pp_path field_path in let path = pp_path field_path in

File diff suppressed because it is too large Load Diff

View File

@ -139,26 +139,27 @@ and pp_type_decl decl =
^^ group (pp_type_expr type_expr) ^^ string ";" ^^ group (pp_type_expr type_expr) ^^ string ";"
and pp_expr = function and pp_expr = function
ECase e -> pp_case_expr e ECase e -> pp_case_expr e
| ECond e -> group (pp_cond_expr e) | ECond e -> group (pp_cond_expr e)
| EAnnot e -> pp_annot_expr e | EAnnot e -> pp_annot_expr e
| ELogic e -> pp_logic_expr e | ELogic e -> pp_logic_expr e
| EArith e -> group (pp_arith_expr e) | EArith e -> group (pp_arith_expr e)
| EString e -> pp_string_expr e | EString e -> pp_string_expr e
| EList e -> group (pp_list_expr e) | EList e -> group (pp_list_expr e)
| EConstr e -> pp_constr_expr e | EConstr e -> pp_constr_expr e
| ERecord e -> pp_record_expr e | ERecord e -> pp_record_expr e
| EProj e -> pp_projection e | EProj e -> pp_projection e
| EUpdate e -> pp_update e | EUpdate e -> pp_update e
| EVar v -> pp_ident v | EVar v -> pp_ident v
| ECall e -> pp_call_expr e | ECall e -> pp_call_expr e
| EBytes e -> pp_bytes e | EBytes e -> pp_bytes e
| EUnit _ -> string "()" | EUnit _ -> string "()"
| ETuple e -> pp_tuple_expr e | ETuple e -> pp_tuple_expr e
| EPar e -> pp_par_expr e | EPar e -> pp_par_expr e
| ELetIn e -> pp_let_in e | ELetIn e -> pp_let_in e
| EFun e -> pp_fun e | EFun e -> pp_fun e
| ESeq e -> pp_seq e | ESeq e -> pp_seq e
| ECodeInsert e -> pp_code_insert e
and pp_case_expr {value; _} = and pp_case_expr {value; _} =
let {expr; cases; _} = value in let {expr; cases; _} = value in
@ -319,6 +320,12 @@ and pp_update {value; _} =
string "{..." ^^ record ^^ string "," string "{..." ^^ record ^^ string ","
^^ nest 2 (break 1 ^^ updates ^^ string "}") ^^ nest 2 (break 1 ^^ updates ^^ string "}")
and pp_code_insert {value; _} =
let {language; code; _} = value in
let language = pp_string language
and code = pp_expr code in
string "[%" ^^ language ^^ string " " ^^ code ^^ string " ]"
and pp_field_path_assign {value; _} = and pp_field_path_assign {value; _} =
let {field_path; field_expr; _} = value in let {field_path; field_expr; _} = value in
let path = pp_path field_path in let path = pp_path field_path in

View File

@ -947,19 +947,6 @@ interactive_expr: LBRACE ELLIPSIS Ident COMMA Ident COLON Bytes COMMA Ident COLO
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE ELLIPSIS Ident COMMA Ident COMMA Ident COMMA WILD
##
## Ends in an error in state: 277.
##
## nsepseq(field_path_assignment,COMMA) -> field_path_assignment COMMA . nsepseq(field_path_assignment,COMMA) [ RBRACE ]
## seq(__anonymous_0(field_path_assignment,COMMA)) -> field_path_assignment COMMA . seq(__anonymous_0(field_path_assignment,COMMA)) [ RBRACE ]
##
## The known suffix of the stack is as follows:
## field_path_assignment COMMA
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE ELLIPSIS Ident COMMA Ident COLON Bytes COMMA WILD interactive_expr: LBRACE ELLIPSIS Ident COMMA Ident COLON Bytes COMMA WILD
## ##
## Ends in an error in state: 273. ## Ends in an error in state: 273.
@ -1048,26 +1035,6 @@ interactive_expr: LBRACE ELLIPSIS Ident COMMA WILD
<YOUR SYNTAX ERROR MESSAGE HERE> <YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE ELLIPSIS Ident DOT Ident VBAR
##
## Ends in an error in state: 259.
##
## update_record -> LBRACE ELLIPSIS path . COMMA sep_or_term_list(field_path_assignment,COMMA) RBRACE [ VBAR Type TIMES SLASH SEMI RPAR RBRACKET RBRACE PLUS Or NE Mod MINUS Let LT LPAR LE LBRACE GT GE EQEQ EOF COMMA COLON CAT BOOL_OR BOOL_AND Attr ARROW ]
##
## The known suffix of the stack is as follows:
## LBRACE ELLIPSIS path
##
## WARNING: This example involves spurious reductions.
## This implies that, although the LR(1) items shown above provide an
## accurate view of the past (what has been recognized so far), they
## may provide an INCOMPLETE view of the future (what was expected next).
## In state 107, spurious reduction of production selection -> DOT Ident
## In state 110, spurious reduction of production projection -> Ident selection
## In state 258, spurious reduction of production path -> projection
##
<YOUR SYNTAX ERROR MESSAGE HERE>
interactive_expr: LBRACE ELLIPSIS Ident WILD interactive_expr: LBRACE ELLIPSIS Ident WILD
## ##
## Ends in an error in state: 254. ## Ends in an error in state: 254.

View File

@ -312,7 +312,7 @@ let raw_code : T.type_expression -> (constraints * T.type_variable) =
let type_anno = type_expression_to_type_value type_anno in let type_anno = type_expression_to_type_value type_anno in
let whole_expr = Core.fresh_type_variable () in let whole_expr = Core.fresh_type_variable () in
[ [
c_equation type_anno (P_variable whole_expr) "wrap: raw_code: type_anno (whole)"; c_equation type_anno ({ tsrc = "wrap: raw_code: whole"; t = P_variable whole_expr }) "wrap: raw_code: type_anno (whole)" ;
], whole_expr ], whole_expr
let assign : T.type_expression -> T.type_expression -> (constraints * T.type_variable) = let assign : T.type_expression -> T.type_expression -> (constraints * T.type_variable) =

View File

@ -92,13 +92,12 @@ them. please report this to the developers." in
] in ] in
error ~data title content error ~data title content
let language_backend_mismatch language backend location = let language_backend_mismatch language backend =
let title () = "Language insert - Backend Mismatch" in let title () = "Language insert - Backend Mismatch" in
let content () = "only provide code insertion in the language you are compiling to" in let content () = "only provide code insertion in the language you are compiling to" in
let data = [ let data = [
("Code Insertion Language", fun () -> language); ("Code Insertion Language", fun () -> language);
("Target backend", fun () -> backend); ("Target backend", fun () -> backend);
("Location", fun() -> Format.asprintf "%a" Location.pp location);
] in ] in
error ~data title content error ~data title content
@ -618,13 +617,14 @@ and transpile_annotated_expression (ae:AST.expression) : expression result =
) )
| E_raw_code { language; code} -> | E_raw_code { language; code} ->
let backend = "Michelson" in let backend = "Michelson" in
let%bind () = trace_strong (language_backend_mismatch language backend ae.location) @@ let%bind () =
Assert.assert_true (String.equal language backend) trace_strong (language_backend_mismatch language backend) @@
Assert.assert_true (String.equal language backend)
in in
let type_anno = get_type_expression code in let type_anno = get_type_expression code in
let%bind type_anno' = transpile_type type_anno in let%bind type_anno' = transpile_type type_anno in
let%bind code = get_a_verbatim code in let%bind code = get_a_string code in
return @@ E_raw_michelson (code, type_anno') return ~tv:type_anno' @@ E_raw_michelson code
and transpile_lambda l (input_type , output_type) = and transpile_lambda l (input_type , output_type) =
let { binder ; result } : AST.lambda = l in let { binder ; result } : AST.lambda = l in

View File

@ -493,12 +493,14 @@ and translate_expression (expr:expression) (env:environment) : michelson result
i_push_unit ; i_push_unit ;
] ]
) )
| E_raw_michelson (code, type_anno) -> | E_raw_michelson code ->
let code = Format.asprintf "{%s}" code in let%bind code =
let%bind code = Proto_alpha_utils.Trace.trace_tzresult (raw_michelson_parsing_error code) @@ Proto_alpha_utils.Trace.trace_tzresult (raw_michelson_parsing_error code) @@
Tezos_micheline.Micheline_parser.no_parsing_error @@ Michelson_parser.V1.parse_expression ~check:false code in Tezos_micheline.Micheline_parser.no_parsing_error @@
Michelson_parser.V1.parse_expression ~check:false code
in
let code = Tezos_micheline.Micheline.root code.expanded in let code = Tezos_micheline.Micheline.root code.expanded in
let%bind ty = Compiler_type.type_ type_anno in let%bind ty = Compiler_type.type_ ty in
return @@ i_push ty code return @@ i_push ty code
and translate_function_body ({body ; binder} : anon_function) lst input : michelson result = and translate_function_body ({body ; binder} : anon_function) lst input : michelson result =

View File

@ -314,6 +314,7 @@ and expression_content =
| E_lambda of lambda | E_lambda of lambda
| E_recursive of recursive | E_recursive of recursive
| E_let_in of let_in | E_let_in of let_in
| E_raw_code of raw_code
(* Variant *) (* Variant *)
| E_constructor of constructor (* For user defined constructors *) | E_constructor of constructor (* For user defined constructors *)
| E_matching of matching | E_matching of matching
@ -346,6 +347,11 @@ and let_in = {
inline : bool ; inline : bool ;
} }
and raw_code = {
language : string;
code : expression;
}
and recursive = { and recursive = {
fun_name : expression_variable; fun_name : expression_variable;
fun_type : type_expression; fun_type : type_expression;

View File

@ -79,7 +79,7 @@ and type_expression ppf : type_expression -> unit = fun te -> match te.type_cont
| T_function (a, b) -> fprintf ppf "lambda (%a) %a" type_expression a type_expression b | T_function (a, b) -> fprintf ppf "lambda (%a) %a" type_expression a type_expression b
| T_base tc -> fprintf ppf "%a" type_constant tc | T_base tc -> fprintf ppf "%a" type_constant tc
| T_map (k,v) -> fprintf ppf "Map (%a,%a)" type_expression k type_expression v | T_map (k,v) -> fprintf ppf "Map (%a,%a)" type_expression k type_expression v
| T_big_map (k,v) -> fprintf ppf "BigMap (%a,%a)" type_expression k type_expression v | T_big_map (k,v) -> fprintf ppf "Big_map (%a,%a)" type_expression k type_expression v
| T_list e -> fprintf ppf "List (%a)" type_expression e | T_list e -> fprintf ppf "List (%a)" type_expression e
| T_set e -> fprintf ppf "Set (%a)" type_expression e | T_set e -> fprintf ppf "Set (%a)" type_expression e
| T_contract c -> fprintf ppf "Contract (%a)" type_expression c | T_contract c -> fprintf ppf "Contract (%a)" type_expression c
@ -125,7 +125,7 @@ and expression_content ppf (e:expression_content) = match e with
fprintf ppf "@[{ %a@;<1 2>with@;<1 2>{ %a = %a } }@]" expression r (list_sep lr (const ".")) path expression update fprintf ppf "@[{ %a@;<1 2>with@;<1 2>{ %a = %a } }@]" expression r (list_sep lr (const ".")) path expression update
| E_while (e , b) -> | E_while (e , b) ->
fprintf ppf "@[while %a do %a@]" expression e expression b fprintf ppf "@[while %a do %a@]" expression e expression b
| E_raw_michelson (code, _) -> | E_raw_michelson code ->
fprintf ppf "%s" code fprintf ppf "%s" code
and expression_with_type : _ -> expression -> _ = fun ppf e -> and expression_with_type : _ -> expression -> _ = fun ppf e ->

View File

@ -91,7 +91,7 @@ and expression_content =
| E_sequence of (expression * expression) | E_sequence of (expression * expression)
| E_record_update of (expression * [`Left | `Right] list * expression) | E_record_update of (expression * [`Left | `Right] list * expression)
| E_while of (expression * expression) | E_while of (expression * expression)
| E_raw_michelson of (string * type_expression) | E_raw_michelson of string
and expression = { and expression = {
content : expression_content ; content : expression_content ;

View File

@ -1,5 +1,5 @@
// Test michelson insertion in PascaLIGO // Test michelson insertion in PascaLIGO
function michelson_add (var n : nat * nat ) : nat is block { function michelson_add (var n : nat * nat ) : nat is block {
const f : (nat * nat -> nat)= [%Michelson ({| UNPAIR; ADD |} : nat *nat -> nat)]; const f : (nat * nat -> nat)= [%Michelson ({| { UNPAIR; ADD } |} : nat *nat -> nat)];
} with f (n) } with f (n)

View File

@ -1,4 +1,4 @@
// Test michelson insertion in CameLIGO // Test michelson insertion in CameLIGO
let michelson_add (n : nat * nat) : nat = let michelson_add (n : nat * nat) : nat =
[%Michelson ({| UNPAIR;ADD |} : nat * nat -> nat) ] n [%Michelson ({| { UNPAIR;ADD } |} : nat * nat -> nat) ] n

View File

@ -1,4 +1,4 @@
// Test michelson insertion in ReasonLIGO // Test michelson insertion in ReasonLIGO
let michelson_add = (n : (nat, nat)) : nat => let michelson_add = (n : (nat, nat)) : nat =>
[%Michelson ({| UNPAIR;ADD |} : ((nat, nat) => nat)) ](n); [%Michelson ({| { UNPAIR;ADD } |} : ((nat, nat) => nat)) ](n);

View File

@ -0,0 +1,5 @@
// Test michelson insertion in PascaLIGO
function main (const p : nat; const s: nat ) : list (operation)* nat is block {
const f : (nat * nat -> nat)= [%Michelson ({| ADD |} : nat *nat -> nat)];
} with ((nil: list(operation)), f (p, s))

View File

@ -0,0 +1,5 @@
// Test michelson insertion in PascaLIGO
function main (const p : nat; const s: nat ) : list (operation)* nat is block {
const f : (nat -> nat -> nat)= [%Michelson ({| ADD |} : nat -> nat -> nat)];
} with ((nil: list(operation)), f (p, s))

View File

@ -0,0 +1,5 @@
// Test michelson insertion in PascaLIGO
function main (const p : nat; const s: nat ) : list (operation)* nat is block {
const f : (nat * nat -> nat)= [%Michelson (" { UNPAIR; ADD } " : nat * nat -> nat)];
} with ((nil: list(operation)), f (p, s))