Improved code injection. Fixed a few bugs on the way.
This commit is contained in:
parent
1c5ea4b3f2
commit
a7f6de9fac
@ -227,27 +227,27 @@ and field_pattern = {
|
||||
}
|
||||
|
||||
and expr =
|
||||
ECase of expr case reg
|
||||
| ECond of cond_expr reg
|
||||
| EAnnot of annot_expr par reg
|
||||
| ELogic of logic_expr
|
||||
| EArith of arith_expr
|
||||
| EString of string_expr
|
||||
| EList of list_expr
|
||||
| EConstr of constr_expr
|
||||
| ERecord of record reg
|
||||
| EProj of projection reg
|
||||
| EUpdate of update reg
|
||||
| EVar of variable
|
||||
| ECall of (expr * expr nseq) reg
|
||||
| EBytes of (string * Hex.t) reg
|
||||
| EUnit of the_unit reg
|
||||
| ETuple of (expr, comma) nsepseq reg
|
||||
| EPar of expr par reg
|
||||
| ELetIn of let_in reg
|
||||
| EFun of fun_expr reg
|
||||
| ESeq of expr injection reg
|
||||
| ECodeInsert of code_insert reg
|
||||
ECase of expr case reg
|
||||
| ECond of cond_expr reg
|
||||
| EAnnot of annot_expr par reg
|
||||
| ELogic of logic_expr
|
||||
| EArith of arith_expr
|
||||
| EString of string_expr
|
||||
| EList of list_expr
|
||||
| EConstr of constr_expr
|
||||
| ERecord of record reg
|
||||
| EProj of projection reg
|
||||
| EUpdate of update reg
|
||||
| EVar of variable
|
||||
| ECall of (expr * expr nseq) reg
|
||||
| EBytes of (string * Hex.t) reg
|
||||
| EUnit of the_unit reg
|
||||
| ETuple of (expr, comma) nsepseq reg
|
||||
| EPar of expr par reg
|
||||
| ELetIn of let_in reg
|
||||
| EFun of fun_expr reg
|
||||
| ESeq of expr injection reg
|
||||
| ECodeInj of code_inj reg
|
||||
|
||||
and annot_expr = expr * colon * type_expr
|
||||
|
||||
@ -400,13 +400,12 @@ and cond_expr = {
|
||||
ifnot : expr
|
||||
}
|
||||
|
||||
and code_insert = {
|
||||
lbracket : lbracket;
|
||||
percent : percent;
|
||||
language : string reg;
|
||||
code : expr;
|
||||
rbracket : rbracket;
|
||||
and code_inj = {
|
||||
language : string reg reg;
|
||||
code : expr;
|
||||
rbracket : rbracket;
|
||||
}
|
||||
|
||||
(* Projecting regions from some nodes of the AST *)
|
||||
|
||||
let rec last to_region = function
|
||||
@ -491,7 +490,7 @@ let expr_to_region = function
|
||||
| ECall {region;_} | EVar {region; _} | EProj {region; _}
|
||||
| EUnit {region;_} | EPar {region;_} | EBytes {region; _}
|
||||
| ESeq {region; _} | ERecord {region; _} | EUpdate {region; _}
|
||||
| ECodeInsert {region; _} -> region
|
||||
| ECodeInj {region; _} -> region
|
||||
|
||||
let selection_to_region = function
|
||||
FieldName f -> f.region
|
||||
|
@ -29,9 +29,22 @@ type lexeme = string
|
||||
(* TOKENS *)
|
||||
|
||||
type t =
|
||||
(* Symbols *)
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
ARROW of Region.t (* "->" *)
|
||||
Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
| Lang of lexeme Region.reg Region.reg
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
| ARROW of Region.t (* "->" *)
|
||||
| CONS of Region.t (* "::" *)
|
||||
| CAT of Region.t (* "^" *)
|
||||
(*| APPEND (* "@" *)*)
|
||||
@ -42,7 +55,6 @@ type t =
|
||||
| PLUS of Region.t (* "+" *)
|
||||
| SLASH of Region.t (* "/" *)
|
||||
| TIMES of Region.t (* "*" *)
|
||||
| PERCENT of Region.t (* "%" *)
|
||||
|
||||
(* Compounds *)
|
||||
|
||||
@ -77,18 +89,6 @@ type t =
|
||||
| BOOL_OR of Region.t (* "||" *)
|
||||
| BOOL_AND of Region.t (* "&&" *)
|
||||
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
| Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
(*| And*)
|
||||
@ -155,6 +155,7 @@ val mk_verbatim : lexeme -> Region.t -> token
|
||||
val mk_bytes : lexeme -> Region.t -> token
|
||||
val mk_constr : lexeme -> Region.t -> token
|
||||
val mk_attr : string -> lexeme -> Region.t -> (token, attr_err) result
|
||||
val mk_lang : lexeme Region.reg -> Region.t -> token
|
||||
val eof : Region.t -> token
|
||||
|
||||
(* Predicates *)
|
||||
|
@ -13,9 +13,22 @@ module SSet = Utils.String.Set
|
||||
(* TOKENS *)
|
||||
|
||||
type t =
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
| Lang of lexeme Region.reg Region.reg
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
ARROW of Region.t (* "->" *)
|
||||
| ARROW of Region.t (* "->" *)
|
||||
| CONS of Region.t (* "::" *)
|
||||
| CAT of Region.t (* "^" *)
|
||||
(*| APPEND (* "@" *)*)
|
||||
@ -26,7 +39,6 @@ type t =
|
||||
| PLUS of Region.t (* "+" *)
|
||||
| SLASH of Region.t (* "/" *)
|
||||
| TIMES of Region.t (* "*" *)
|
||||
| PERCENT of Region.t (* "%" *)
|
||||
|
||||
(* Compounds *)
|
||||
|
||||
@ -61,18 +73,6 @@ type t =
|
||||
| BOOL_OR of Region.t (* "||" *)
|
||||
| BOOL_AND of Region.t (* "&&" *)
|
||||
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
| Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
(*| And*)
|
||||
@ -113,26 +113,28 @@ let proj_token = function
|
||||
(* Literals *)
|
||||
|
||||
String Region.{region; value} ->
|
||||
region, sprintf "String %s" value
|
||||
region, sprintf "String %S" value
|
||||
| Verbatim Region.{region; value} ->
|
||||
region, sprintf "Verbatim {|%s|}" value
|
||||
region, sprintf "Verbatim %S" value
|
||||
| Bytes Region.{region; value = s,b} ->
|
||||
region,
|
||||
sprintf "Bytes (\"%s\", \"0x%s\")" s (Hex.show b)
|
||||
sprintf "Bytes (%S, \"0x%s\")" s (Hex.show b)
|
||||
| Int Region.{region; value = s,n} ->
|
||||
region, sprintf "Int (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Int (%S, %s)" s (Z.to_string n)
|
||||
| Nat Region.{region; value = s,n} ->
|
||||
region, sprintf "Nat (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Nat (%S, %s)" s (Z.to_string n)
|
||||
| Mutez Region.{region; value = s,n} ->
|
||||
region, sprintf "Mutez (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Mutez (%S, %s)" s (Z.to_string n)
|
||||
| Ident Region.{region; value} ->
|
||||
region, sprintf "Ident %s" value
|
||||
region, sprintf "Ident %S" value
|
||||
| Constr Region.{region; value} ->
|
||||
region, sprintf "Constr %s" value
|
||||
region, sprintf "Constr %S" value
|
||||
| Attr Region.{region; value} ->
|
||||
region, sprintf "Attr \"%s\"" value
|
||||
region, sprintf "Attr %S" value
|
||||
| Lang Region.{region; value} ->
|
||||
region, sprintf "Lang %S" (value.Region.value)
|
||||
|
||||
(* Symbols *)
|
||||
(* Symbols *)
|
||||
|
||||
| ARROW region -> region, "ARROW"
|
||||
| CONS region -> region, "CONS"
|
||||
@ -141,7 +143,6 @@ let proj_token = function
|
||||
| PLUS region -> region, "PLUS"
|
||||
| SLASH region -> region, "SLASH"
|
||||
| TIMES region -> region, "TIMES"
|
||||
| PERCENT region -> region, "PERCENT"
|
||||
| LPAR region -> region, "LPAR"
|
||||
| RPAR region -> region, "RPAR"
|
||||
| LBRACKET region -> region, "LBRACKET"
|
||||
@ -206,6 +207,7 @@ let to_lexeme = function
|
||||
| Ident id -> id.Region.value
|
||||
| Constr id -> id.Region.value
|
||||
| Attr a -> a.Region.value
|
||||
| Lang lang -> Region.(lang.value.value)
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -216,7 +218,6 @@ let to_lexeme = function
|
||||
| PLUS _ -> "+"
|
||||
| SLASH _ -> "/"
|
||||
| TIMES _ -> "*"
|
||||
| PERCENT _ -> "%"
|
||||
| LPAR _ -> "("
|
||||
| RPAR _ -> ")"
|
||||
| LBRACKET _ -> "["
|
||||
@ -478,7 +479,6 @@ let mk_sym lexeme region =
|
||||
| "-" -> Ok (MINUS region)
|
||||
| "*" -> Ok (TIMES region)
|
||||
| "/" -> Ok (SLASH region)
|
||||
| "%" -> Ok (PERCENT region)
|
||||
| "<" -> Ok (LT region)
|
||||
| "<=" -> Ok (LE region)
|
||||
| ">" -> Ok (GT region)
|
||||
@ -512,6 +512,10 @@ let mk_attr header lexeme region =
|
||||
if header = "[@" then Error Invalid_attribute
|
||||
else Ok (Attr Region.{value=lexeme; region})
|
||||
|
||||
(* Language injection *)
|
||||
|
||||
let mk_lang lang region = Lang Region.{value=lang; region}
|
||||
|
||||
(* Predicates *)
|
||||
|
||||
let is_string = function String _ -> true | _ -> false
|
||||
@ -573,7 +577,7 @@ let check_right_context token next_token buffer : unit =
|
||||
else ()
|
||||
else
|
||||
if is_bytes token
|
||||
then if is_string next || is_ident next
|
||||
then if is_string next || is_ident next
|
||||
then fail region Missing_break
|
||||
else if is_int next
|
||||
then fail region Odd_lengthed_bytes
|
||||
|
@ -5,15 +5,16 @@
|
||||
|
||||
(* Literals *)
|
||||
|
||||
%token <string Region.reg> String "<string>"
|
||||
%token <string Region.reg> Verbatim "<verbatim>"
|
||||
%token <(LexToken.lexeme * Hex.t) Region.reg> Bytes "<bytes>"
|
||||
%token <(string * Z.t) Region.reg> Int "<int>"
|
||||
%token <(string * Z.t) Region.reg> Nat "<nat>"
|
||||
%token <(string * Z.t) Region.reg> Mutez "<mutez>"
|
||||
%token <string Region.reg> Ident "<ident>"
|
||||
%token <string Region.reg> Constr "<constr>"
|
||||
%token <string Region.reg> Attr "<attr>"
|
||||
%token <string Region.reg> String "<string>"
|
||||
%token <string Region.reg> Verbatim "<verbatim>"
|
||||
%token <(LexToken.lexeme * Hex.t) Region.reg> Bytes "<bytes>"
|
||||
%token <(string * Z.t) Region.reg> Int "<int>"
|
||||
%token <(string * Z.t) Region.reg> Nat "<nat>"
|
||||
%token <(string * Z.t) Region.reg> Mutez "<mutez>"
|
||||
%token <string Region.reg> Ident "<ident>"
|
||||
%token <string Region.reg> Constr "<constr>"
|
||||
%token <string Region.reg> Attr "<attr>"
|
||||
%token <LexToken.lexeme Region.reg Region.reg> Lang "<lang>"
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -21,7 +22,6 @@
|
||||
%token <Region.t> PLUS "+"
|
||||
%token <Region.t> SLASH "/"
|
||||
%token <Region.t> TIMES "*"
|
||||
%token <Region.t> PERCENT "%"
|
||||
|
||||
%token <Region.t> LPAR "("
|
||||
%token <Region.t> RPAR ")"
|
||||
|
@ -583,7 +583,7 @@ core_expr:
|
||||
| sequence { ESeq $1 }
|
||||
| record_expr { ERecord $1 }
|
||||
| update_record { EUpdate $1 }
|
||||
| code_insert { ECodeInsert $1 }
|
||||
| code_inj { ECodeInj $1 }
|
||||
| par(expr) { EPar $1 }
|
||||
| par(annot_expr) { EAnnot $1 }
|
||||
|
||||
@ -708,13 +708,8 @@ last_expr:
|
||||
seq_expr:
|
||||
disj_expr_level | if_then_else (seq_expr) { $1 }
|
||||
|
||||
code_insert:
|
||||
"[" "%" Constr expr "]" {
|
||||
let region = cover $1 $5 in
|
||||
let value = {
|
||||
lbracket =$1;
|
||||
percent =$2;
|
||||
language =$3;
|
||||
code =$4;
|
||||
rbracket =$5}
|
||||
code_inj:
|
||||
"<lang>" expr "]" {
|
||||
let region = cover $1.region $3
|
||||
and value = {language=$1; code=$2; rbracket=$3}
|
||||
in {region; value} }
|
||||
|
@ -89,12 +89,6 @@ let print_pvar state {region; value} =
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
let print_uident state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: Uident %s\n"
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
let print_string state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: String %S\n"
|
||||
@ -103,7 +97,7 @@ let print_string state {region; value} =
|
||||
|
||||
let print_verbatim state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: Verbatim {|%s|}\n"
|
||||
sprintf "%s: Verbatim %S\n"
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
@ -211,7 +205,7 @@ and print_cartesian state Region.{value;_} =
|
||||
print_nsepseq state "*" print_type_expr value
|
||||
|
||||
and print_variant state {value = {constr; arg}; _} =
|
||||
print_uident state constr;
|
||||
print_constr state constr;
|
||||
match arg with
|
||||
None -> ()
|
||||
| Some (kwd_of, t_expr) ->
|
||||
@ -340,7 +334,7 @@ and print_some_app_pattern state {value; _} =
|
||||
|
||||
and print_constr_app_pattern state node =
|
||||
let {value=constr, p_opt; _} = node in
|
||||
print_uident state constr;
|
||||
print_constr state constr;
|
||||
match p_opt with
|
||||
None -> ()
|
||||
| Some pattern -> print_pattern state pattern
|
||||
@ -366,7 +360,7 @@ and print_expr state = function
|
||||
| ESeq seq -> print_sequence state seq
|
||||
| ERecord e -> print_record_expr state e
|
||||
| EConstr e -> print_constr_expr state e
|
||||
| ECodeInsert e -> print_code_insert state e
|
||||
| ECodeInj e -> print_code_inj state e
|
||||
|
||||
and print_constr_expr state = function
|
||||
ENone e -> print_none_expr state e
|
||||
@ -519,13 +513,15 @@ and print_comp_expr state = function
|
||||
and print_record_expr state e =
|
||||
print_ne_injection state print_field_assign e
|
||||
|
||||
and print_code_insert state {value; _} =
|
||||
let {lbracket;percent;language;code;rbracket} : code_insert = value in
|
||||
print_token state lbracket "[";
|
||||
print_token state percent "%";
|
||||
print_string state language;
|
||||
print_expr state code;
|
||||
print_token state rbracket "]"
|
||||
and print_code_inj state {value; _} =
|
||||
let {language; code; rbracket} = value in
|
||||
let {value=lang; region} = language in
|
||||
let header_stop = region#start#shift_bytes 1 in
|
||||
let header_reg = Region.make ~start:region#start ~stop:header_stop in
|
||||
print_token state header_reg "[%";
|
||||
print_string state lang;
|
||||
print_expr state code;
|
||||
print_token state rbracket "]"
|
||||
|
||||
and print_field_assign state {value; _} =
|
||||
let {field_name; assignment; field_expr} = value in
|
||||
@ -869,9 +865,9 @@ and pp_expr state = function
|
||||
| ESeq {value; region} ->
|
||||
pp_loc_node state "ESeq" region;
|
||||
pp_injection pp_expr state value
|
||||
| ECodeInsert {value; region} ->
|
||||
pp_loc_node state "ECodeInsert" region;
|
||||
pp_code_insert state value
|
||||
| ECodeInj {value; region} ->
|
||||
pp_loc_node state "ECodeInj" region;
|
||||
pp_code_inj state value
|
||||
|
||||
and pp_fun_expr state node =
|
||||
let {binders; lhs_type; body; _} = node in
|
||||
@ -893,16 +889,16 @@ and pp_fun_expr state node =
|
||||
pp_expr (state#pad 1 0) body
|
||||
in ()
|
||||
|
||||
and pp_code_insert state (rc : code_insert) =
|
||||
and pp_code_inj state rc =
|
||||
let () =
|
||||
let state = state#pad 3 0 in
|
||||
let state = state#pad 2 0 in
|
||||
pp_node state "<language>";
|
||||
pp_string (state#pad 1 0) rc.language in
|
||||
pp_string (state#pad 1 0) rc.language.value in
|
||||
let () =
|
||||
let state = state#pad 3 1 in
|
||||
let state = state#pad 2 1 in
|
||||
pp_node state "<code>";
|
||||
pp_expr (state#pad 1 0) rc.code in
|
||||
()
|
||||
pp_expr (state#pad 1 0) rc.code
|
||||
in ()
|
||||
|
||||
and pp_let_in state node =
|
||||
let {binding; body; attributes; kwd_rec; _} = node in
|
||||
|
@ -52,22 +52,22 @@ and pp_let_binding (binding : let_binding) =
|
||||
in prefix 2 1 (lhs ^^ string " =") (pp_expr let_rhs)
|
||||
|
||||
and pp_pattern = function
|
||||
PConstr p -> pp_pconstr p
|
||||
| PUnit _ -> string "()"
|
||||
| PFalse _ -> string "false"
|
||||
| PTrue _ -> string "true"
|
||||
| PVar v -> pp_ident v
|
||||
| PInt i -> pp_int i
|
||||
| PNat n -> pp_nat n
|
||||
| PBytes b -> pp_bytes b
|
||||
| PString s -> pp_string s
|
||||
PConstr p -> pp_pconstr p
|
||||
| PUnit _ -> string "()"
|
||||
| PFalse _ -> string "false"
|
||||
| PTrue _ -> string "true"
|
||||
| PVar v -> pp_ident v
|
||||
| PInt i -> pp_int i
|
||||
| PNat n -> pp_nat n
|
||||
| PBytes b -> pp_bytes b
|
||||
| PString s -> pp_string s
|
||||
| PVerbatim s -> pp_verbatim s
|
||||
| PWild _ -> string "_"
|
||||
| PList l -> pp_plist l
|
||||
| PTuple t -> pp_ptuple t
|
||||
| PPar p -> pp_ppar p
|
||||
| PRecord r -> pp_precord r
|
||||
| PTyped t -> pp_ptyped t
|
||||
| PWild _ -> string "_"
|
||||
| PList l -> pp_plist l
|
||||
| PTuple t -> pp_ptuple t
|
||||
| PPar p -> pp_ppar p
|
||||
| PRecord r -> pp_precord r
|
||||
| PTyped t -> pp_ptyped t
|
||||
|
||||
and pp_pconstr = function
|
||||
PNone _ -> string "None"
|
||||
@ -152,7 +152,7 @@ and pp_expr = function
|
||||
| ELetIn e -> pp_let_in e
|
||||
| EFun e -> pp_fun e
|
||||
| ESeq e -> pp_seq e
|
||||
| ECodeInsert e -> pp_code_insert e
|
||||
| ECodeInj e -> pp_code_inj e
|
||||
|
||||
and pp_case_expr {value; _} =
|
||||
let {expr; cases; _} = value in
|
||||
@ -314,11 +314,11 @@ and pp_update {value; _} =
|
||||
string "{" ^^ record ^^ string " with"
|
||||
^^ nest 2 (break 1 ^^ updates ^^ string "}")
|
||||
|
||||
and pp_code_insert {value; _} =
|
||||
and pp_code_inj {value; _} =
|
||||
let {language; code; _} = value in
|
||||
let language = pp_string language
|
||||
and code = pp_expr code in
|
||||
string "[%" ^^ language ^^ string " " ^^ code ^^ string " ]"
|
||||
let language = pp_string language.value
|
||||
and code = pp_expr code in
|
||||
string "[%" ^^ language ^/^ code ^^ string "]"
|
||||
|
||||
and pp_field_path_assign {value; _} =
|
||||
let {field_path; field_expr; _} = value in
|
||||
|
File diff suppressed because it is too large
Load Diff
@ -82,7 +82,6 @@ type rbrace = Region.t (* "}" *)
|
||||
type lbracket = Region.t (* "[" *)
|
||||
type rbracket = Region.t (* "]" *)
|
||||
type cons = Region.t (* "#" *)
|
||||
type percent = Region.t (* "%" *)
|
||||
type vbar = Region.t (* "|" *)
|
||||
type arrow = Region.t (* "->" *)
|
||||
type assign = Region.t (* ":=" *)
|
||||
@ -437,12 +436,10 @@ and for_collect = {
|
||||
block : block reg
|
||||
}
|
||||
|
||||
and code_insert = {
|
||||
lbracket : lbracket;
|
||||
percent : percent;
|
||||
language : string reg;
|
||||
code : expr;
|
||||
rbracket : rbracket;
|
||||
and code_inj = {
|
||||
language : string reg reg;
|
||||
code : expr;
|
||||
rbracket : rbracket;
|
||||
}
|
||||
|
||||
and collection =
|
||||
@ -453,27 +450,27 @@ and collection =
|
||||
(* Expressions *)
|
||||
|
||||
and expr =
|
||||
ECase of expr case reg
|
||||
| ECond of cond_expr reg
|
||||
| EAnnot of annot_expr par reg
|
||||
| ELogic of logic_expr
|
||||
| EArith of arith_expr
|
||||
| EString of string_expr
|
||||
| EList of list_expr
|
||||
| ESet of set_expr
|
||||
| EConstr of constr_expr
|
||||
| ERecord of record reg
|
||||
| EProj of projection reg
|
||||
| EUpdate of update reg
|
||||
| EMap of map_expr
|
||||
| EVar of Lexer.lexeme reg
|
||||
| ECall of fun_call
|
||||
| EBytes of (Lexer.lexeme * Hex.t) reg
|
||||
| EUnit of c_Unit
|
||||
| ETuple of tuple_expr
|
||||
| EPar of expr par reg
|
||||
| EFun of fun_expr reg
|
||||
| ECodeInsert of code_insert reg
|
||||
ECase of expr case reg
|
||||
| ECond of cond_expr reg
|
||||
| EAnnot of annot_expr par reg
|
||||
| ELogic of logic_expr
|
||||
| EArith of arith_expr
|
||||
| EString of string_expr
|
||||
| EList of list_expr
|
||||
| ESet of set_expr
|
||||
| EConstr of constr_expr
|
||||
| ERecord of record reg
|
||||
| EProj of projection reg
|
||||
| EUpdate of update reg
|
||||
| EMap of map_expr
|
||||
| EVar of Lexer.lexeme reg
|
||||
| ECall of fun_call
|
||||
| EBytes of (Lexer.lexeme * Hex.t) reg
|
||||
| EUnit of c_Unit
|
||||
| ETuple of tuple_expr
|
||||
| EPar of expr par reg
|
||||
| EFun of fun_expr reg
|
||||
| ECodeInj of code_inj reg
|
||||
|
||||
and annot_expr = expr * colon * type_expr
|
||||
|
||||
@ -688,17 +685,17 @@ let rec expr_to_region = function
|
||||
| ERecord e -> record_expr_to_region e
|
||||
| EMap e -> map_expr_to_region e
|
||||
| ETuple e -> tuple_expr_to_region e
|
||||
| EUpdate {region; _}
|
||||
| EProj {region; _}
|
||||
| EVar {region; _}
|
||||
| ECall {region; _}
|
||||
| EBytes {region; _}
|
||||
| EUnit region
|
||||
| ECase {region;_}
|
||||
| ECond {region; _}
|
||||
| EPar {region; _}
|
||||
| EFun {region; _}
|
||||
| ECodeInsert {region; _} -> region
|
||||
| EUpdate {region; _}
|
||||
| EProj {region; _}
|
||||
| EVar {region; _}
|
||||
| ECall {region; _}
|
||||
| EBytes {region; _}
|
||||
| EUnit region
|
||||
| ECase {region;_}
|
||||
| ECond {region; _}
|
||||
| EPar {region; _}
|
||||
| EFun {region; _}
|
||||
| ECodeInj {region; _} -> region
|
||||
|
||||
and tuple_expr_to_region {region; _} = region
|
||||
|
||||
|
@ -44,6 +44,7 @@ type t =
|
||||
| Mutez of (lexeme * Z.t) Region.reg
|
||||
| Ident of lexeme Region.reg
|
||||
| Constr of lexeme Region.reg
|
||||
| Lang of lexeme Region.reg Region.reg
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -73,7 +74,6 @@ type t =
|
||||
| DOT of Region.t (* "." *)
|
||||
| WILD of Region.t (* "_" *)
|
||||
| CAT of Region.t (* "^" *)
|
||||
| PERCENT of Region.t (* "%" *)
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
@ -162,6 +162,7 @@ val mk_verbatim : lexeme -> Region.t -> token
|
||||
val mk_bytes : lexeme -> Region.t -> token
|
||||
val mk_constr : lexeme -> Region.t -> token
|
||||
val mk_attr : string -> lexeme -> Region.t -> (token, attr_err) result
|
||||
val mk_lang : lexeme Region.reg -> Region.t -> token
|
||||
val eof : Region.t -> token
|
||||
|
||||
(* Predicates *)
|
||||
|
@ -32,6 +32,7 @@ type t =
|
||||
| Mutez of (lexeme * Z.t) Region.reg
|
||||
| Ident of lexeme Region.reg
|
||||
| Constr of lexeme Region.reg
|
||||
| Lang of lexeme Region.reg Region.reg
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -61,7 +62,6 @@ type t =
|
||||
| DOT of Region.t
|
||||
| WILD of Region.t
|
||||
| CAT of Region.t
|
||||
| PERCENT of Region.t (* "%" *)
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
@ -126,26 +126,23 @@ let proj_token = function
|
||||
region, sprintf "String %S" value
|
||||
|
||||
| Verbatim Region.{region; value} ->
|
||||
region, sprintf "Verbatim {|%s|}" value
|
||||
region, sprintf "Verbatim %S" value
|
||||
|
||||
| Bytes Region.{region; value = s,b} ->
|
||||
region,
|
||||
sprintf "Bytes (\"%s\", \"0x%s\")" s (Hex.show b)
|
||||
sprintf "Bytes (%S, \"0x%s\")" s (Hex.show b)
|
||||
| Int Region.{region; value = s,n} ->
|
||||
region, sprintf "Int (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Int (%S, %s)" s (Z.to_string n)
|
||||
| Nat Region.{region; value = s,n} ->
|
||||
region, sprintf "Nat (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Nat (%S, %s)" s (Z.to_string n)
|
||||
| Mutez Region.{region; value = s,n} ->
|
||||
region, sprintf "Mutez (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Mutez (%S, %s)" s (Z.to_string n)
|
||||
| Ident Region.{region; value} ->
|
||||
region, sprintf "Ident \"%s\"" value
|
||||
region, sprintf "Ident %S" value
|
||||
| Constr Region.{region; value} ->
|
||||
region, sprintf "Constr \"%s\"" value
|
||||
|
||||
(*
|
||||
| Attr {header; string={region; value}} ->
|
||||
region, sprintf "Attr (\"%s\",\"%s\")" header value
|
||||
*)
|
||||
region, sprintf "Constr %S" value
|
||||
| Lang Region.{region; value} ->
|
||||
region, sprintf "Lang %S" (value.Region.value)
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -175,7 +172,6 @@ let proj_token = function
|
||||
| DOT region -> region, "DOT"
|
||||
| WILD region -> region, "WILD"
|
||||
| CAT region -> region, "CAT"
|
||||
| PERCENT region -> region, "PERCENT"
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
@ -232,14 +228,15 @@ let proj_token = function
|
||||
let to_lexeme = function
|
||||
(* Literals *)
|
||||
|
||||
String s -> String.escaped s.Region.value
|
||||
String s -> String.escaped s.Region.value
|
||||
| Verbatim v -> String.escaped v.Region.value
|
||||
| Bytes b -> fst b.Region.value
|
||||
| Bytes b -> fst b.Region.value
|
||||
| Int i
|
||||
| Nat i
|
||||
| Mutez i -> fst i.Region.value
|
||||
| Mutez i -> fst i.Region.value
|
||||
| Ident id
|
||||
| Constr id -> id.Region.value
|
||||
| Constr id -> id.Region.value
|
||||
| Lang lang -> Region.(lang.value.value)
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -269,7 +266,6 @@ let to_lexeme = function
|
||||
| DOT _ -> "."
|
||||
| WILD _ -> "_"
|
||||
| CAT _ -> "^"
|
||||
| PERCENT _ -> "%"
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
@ -521,7 +517,6 @@ let mk_sym lexeme region =
|
||||
| "-" -> Ok (MINUS region)
|
||||
| "*" -> Ok (TIMES region)
|
||||
| "/" -> Ok (SLASH region)
|
||||
| "%" -> Ok (PERCENT region)
|
||||
| "<" -> Ok (LT region)
|
||||
| "<=" -> Ok (LE region)
|
||||
| ">" -> Ok (GT region)
|
||||
@ -552,6 +547,10 @@ type attr_err = Invalid_attribute
|
||||
|
||||
let mk_attr _ _ _ = Error Invalid_attribute
|
||||
|
||||
(* Language injection *)
|
||||
|
||||
let mk_lang lang region = Lang Region.{value=lang; region}
|
||||
|
||||
(* Predicates *)
|
||||
|
||||
let is_string = function String _ -> true | _ -> false
|
||||
@ -613,7 +612,7 @@ let check_right_context token next_token buffer : unit =
|
||||
else ()
|
||||
else
|
||||
if is_bytes token
|
||||
then if is_string next || is_ident next
|
||||
then if is_string next || is_ident next
|
||||
then fail region Missing_break
|
||||
else if is_int next
|
||||
then fail region Odd_lengthed_bytes
|
||||
|
@ -5,14 +5,15 @@
|
||||
|
||||
(* Literals *)
|
||||
|
||||
%token <LexToken.lexeme Region.reg> String "<string>"
|
||||
%token <LexToken.lexeme Region.reg> Verbatim "<verbatim>"
|
||||
%token <(LexToken.lexeme * Hex.t) Region.reg> Bytes "<bytes>"
|
||||
%token <(LexToken.lexeme * Z.t) Region.reg> Int "<int>"
|
||||
%token <(LexToken.lexeme * Z.t) Region.reg> Nat "<nat>"
|
||||
%token <(LexToken.lexeme * Z.t) Region.reg> Mutez "<mutez>"
|
||||
%token <LexToken.lexeme Region.reg> Ident "<ident>"
|
||||
%token <LexToken.lexeme Region.reg> Constr "<constr>"
|
||||
%token <LexToken.lexeme Region.reg> String "<string>"
|
||||
%token <LexToken.lexeme Region.reg> Verbatim "<verbatim>"
|
||||
%token <(LexToken.lexeme * Hex.t) Region.reg> Bytes "<bytes>"
|
||||
%token <(LexToken.lexeme * Z.t) Region.reg> Int "<int>"
|
||||
%token <(LexToken.lexeme * Z.t) Region.reg> Nat "<nat>"
|
||||
%token <(LexToken.lexeme * Z.t) Region.reg> Mutez "<mutez>"
|
||||
%token <LexToken.lexeme Region.reg> Ident "<ident>"
|
||||
%token <LexToken.lexeme Region.reg> Constr "<constr>"
|
||||
%token <LexToken.lexeme Region.reg Region.reg> Lang "<lang>"
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -42,7 +43,6 @@
|
||||
%token <Region.t> DOT "."
|
||||
%token <Region.t> WILD "_"
|
||||
%token <Region.t> CAT "^"
|
||||
%token <Region.t> PERCENT "%"
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
|
@ -855,7 +855,7 @@ core_expr:
|
||||
| set_expr { ESet $1 }
|
||||
| record_expr { ERecord $1 }
|
||||
| update_record { EUpdate $1 }
|
||||
| code_insert_expr { ECodeInsert $1 }
|
||||
| code_inj { ECodeInj $1 }
|
||||
| "<constr>" arguments {
|
||||
let region = cover $1.region $2.region in
|
||||
EConstr (ConstrApp {region; value = $1, Some $2})
|
||||
@ -974,15 +974,10 @@ update_record:
|
||||
let value = {record=$1; kwd_with=$2; updates}
|
||||
in {region; value} }
|
||||
|
||||
code_insert_expr:
|
||||
"[" "%" Constr expr "]" {
|
||||
let region = cover $1 $5 in
|
||||
let value = {
|
||||
lbracket =$1;
|
||||
percent =$2;
|
||||
language =$3;
|
||||
code =$4;
|
||||
rbracket =$5}
|
||||
code_inj:
|
||||
"<lang>" expr "]" {
|
||||
let region = cover $1.region $3
|
||||
and value = {language=$1; code=$2; rbracket=$3}
|
||||
in {region; value} }
|
||||
|
||||
field_assignment:
|
||||
|
@ -71,26 +71,32 @@ let print_token state region lexeme =
|
||||
|
||||
let print_var state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: Ident \"%s\"\n"
|
||||
sprintf "%s: Ident %S\n"
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
let print_constr state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: Constr \"%s\"\n"
|
||||
sprintf "%s: Constr %S\n"
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
let print_string state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: String %s\n"
|
||||
sprintf "%s: String %S\n"
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
let print_verbatim state {region; value} =
|
||||
let line =
|
||||
sprintf "%s: Verbatim %S\n"
|
||||
(compact state region) value
|
||||
in Buffer.add_string state#buffer line
|
||||
|
||||
let print_bytes state {region; value} =
|
||||
let lexeme, abstract = value in
|
||||
let line =
|
||||
sprintf "%s: Bytes (\"%s\", \"0x%s\")\n"
|
||||
sprintf "%s: Bytes (%S, \"0x%s\")\n"
|
||||
(compact state region) lexeme
|
||||
(Hex.show abstract)
|
||||
in Buffer.add_string state#buffer line
|
||||
@ -98,7 +104,7 @@ let print_bytes state {region; value} =
|
||||
let print_int state {region; value} =
|
||||
let lexeme, abstract = value in
|
||||
let line =
|
||||
sprintf "%s: Int (\"%s\", %s)\n"
|
||||
sprintf "%s: Int (%S, %s)\n"
|
||||
(compact state region) lexeme
|
||||
(Z.to_string abstract)
|
||||
in Buffer.add_string state#buffer line
|
||||
@ -106,7 +112,7 @@ let print_int state {region; value} =
|
||||
let print_nat state {region; value} =
|
||||
let lexeme, abstract = value in
|
||||
let line =
|
||||
sprintf "%s: Nat (\"%s\", %s)\n"
|
||||
sprintf "%s: Nat (%S, %s)\n"
|
||||
(compact state region) lexeme
|
||||
(Z.to_string abstract)
|
||||
in Buffer.add_string state#buffer line
|
||||
@ -230,13 +236,15 @@ and print_fun_expr state {value; _} =
|
||||
print_token state kwd_is "is";
|
||||
print_expr state return
|
||||
|
||||
and print_code_insert state {value; _} =
|
||||
let {lbracket;percent;language;code;rbracket} : code_insert = value in
|
||||
print_token state lbracket "[";
|
||||
print_token state percent "%";
|
||||
print_string state language;
|
||||
print_expr state code;
|
||||
print_token state rbracket "]"
|
||||
and print_code_inj state {value; _} =
|
||||
let {language; code; rbracket} = value in
|
||||
let {value=lang; region} = language in
|
||||
let header_stop = region#start#shift_bytes 1 in
|
||||
let header_reg = Region.make ~start:region#start ~stop:header_stop in
|
||||
print_token state header_reg "[%";
|
||||
print_string state lang;
|
||||
print_expr state code;
|
||||
print_token state rbracket "]"
|
||||
|
||||
and print_parameters state {value; _} =
|
||||
let {lpar; inside; rpar} = value in
|
||||
@ -467,7 +475,7 @@ and print_expr state = function
|
||||
| ETuple e -> print_tuple_expr state e
|
||||
| EPar e -> print_par_expr state e
|
||||
| EFun e -> print_fun_expr state e
|
||||
| ECodeInsert e -> print_code_insert state e
|
||||
| ECodeInj e -> print_code_inj state e
|
||||
|
||||
and print_annot_expr state node =
|
||||
let {inside; _} : annot_expr par = node in
|
||||
@ -609,7 +617,7 @@ and print_string_expr state = function
|
||||
| String s ->
|
||||
print_string state s
|
||||
| Verbatim v ->
|
||||
print_string state v
|
||||
print_verbatim state v
|
||||
|
||||
and print_list_expr state = function
|
||||
ECons {value = {arg1; op; arg2}; _} ->
|
||||
@ -1019,16 +1027,16 @@ and pp_fun_expr state (expr: fun_expr) =
|
||||
pp_expr (state#pad 1 0) expr.return
|
||||
in ()
|
||||
|
||||
and pp_code_insert state (rc : code_insert) =
|
||||
and pp_code_inj state rc =
|
||||
let () =
|
||||
let state = state#pad 3 0 in
|
||||
let state = state#pad 2 0 in
|
||||
pp_node state "<language>";
|
||||
pp_string (state#pad 1 0) rc.language in
|
||||
pp_string (state#pad 1 0) rc.language.value in
|
||||
let () =
|
||||
let state = state#pad 3 1 in
|
||||
let state = state#pad 2 1 in
|
||||
pp_node state "<code>";
|
||||
pp_expr (state#pad 1 0) rc.code in
|
||||
()
|
||||
pp_expr (state#pad 1 0) rc.code
|
||||
in ()
|
||||
|
||||
and pp_parameters state {value; _} =
|
||||
let params = Utils.nsepseq_to_list value.inside in
|
||||
@ -1511,9 +1519,9 @@ and pp_expr state = function
|
||||
| EFun {value; region} ->
|
||||
pp_loc_node state "EFun" region;
|
||||
pp_fun_expr state value;
|
||||
| ECodeInsert {value; region} ->
|
||||
pp_loc_node state "ECodeInsert" region;
|
||||
pp_code_insert state value;
|
||||
| ECodeInj {value; region} ->
|
||||
pp_loc_node state "ECodeInj" region;
|
||||
pp_code_inj state value;
|
||||
|
||||
and pp_list_expr state = function
|
||||
ECons {value; region} ->
|
||||
|
@ -381,7 +381,7 @@ and pp_expr = function
|
||||
| ETuple e -> pp_tuple_expr e
|
||||
| EPar e -> pp_par pp_expr e
|
||||
| EFun e -> pp_fun_expr e
|
||||
| ECodeInsert e -> pp_code_insert e
|
||||
| ECodeInj e -> pp_code_inj e
|
||||
|
||||
and pp_annot_expr {value; _} =
|
||||
let expr, _, type_expr = value.inside in
|
||||
@ -496,11 +496,11 @@ and pp_update {value; _} =
|
||||
and record = pp_path record in
|
||||
record ^^ string " with" ^^ nest 2 (break 1 ^^ updates)
|
||||
|
||||
and pp_code_insert {value; _} =
|
||||
and pp_code_inj {value; _} =
|
||||
let {language; code; _} = value in
|
||||
let language = pp_string language
|
||||
and code = pp_expr code in
|
||||
string "[%" ^^ language ^^ string " " ^^ code ^^ string " ]"
|
||||
let language = pp_string language.value
|
||||
and code = pp_expr code in
|
||||
string "[%" ^^ language ^/^ code ^^ string "]"
|
||||
|
||||
and pp_field_path_assign {value; _} =
|
||||
let {field_path; field_expr; _} = value in
|
||||
|
File diff suppressed because it is too large
Load Diff
@ -29,9 +29,22 @@ type lexeme = string
|
||||
(* TOKENS *)
|
||||
|
||||
type t =
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
| Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
| Lang of lexeme Region.reg Region.reg
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
CAT of Region.t (* "++" *)
|
||||
| CAT of Region.t (* "++" *)
|
||||
|
||||
(* Arithmetics *)
|
||||
|
||||
@ -39,7 +52,6 @@ type t =
|
||||
| PLUS of Region.t (* "+" *)
|
||||
| SLASH of Region.t (* "/" *)
|
||||
| TIMES of Region.t (* "*" *)
|
||||
| PERCENT of Region.t (* "%" *)
|
||||
|
||||
(* Compounds *)
|
||||
|
||||
@ -80,18 +92,6 @@ type t =
|
||||
| BOOL_AND of Region.t (* "&&" *)
|
||||
| NOT of Region.t (* ! *)
|
||||
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
| Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
| Else of Region.t
|
||||
@ -147,13 +147,14 @@ val mk_int : lexeme -> Region.t -> (token, int_err) result
|
||||
val mk_nat : lexeme -> Region.t -> (token, nat_err) result
|
||||
val mk_mutez : lexeme -> Region.t -> (token, int_err) result
|
||||
val mk_ident : lexeme -> Region.t -> (token, ident_err) result
|
||||
val mk_attr : string -> lexeme -> Region.t -> (token, attr_err) result
|
||||
val mk_sym : lexeme -> Region.t -> (token, sym_err) result
|
||||
val mk_kwd : lexeme -> Region.t -> (token, kwd_err) result
|
||||
val mk_string : lexeme -> Region.t -> token
|
||||
val mk_verbatim : lexeme -> Region.t -> token
|
||||
val mk_bytes : lexeme -> Region.t -> token
|
||||
val mk_constr : lexeme -> Region.t -> token
|
||||
val mk_attr : string -> lexeme -> Region.t -> (token, attr_err) result
|
||||
val mk_lang : lexeme Region.reg -> Region.t -> token
|
||||
val eof : Region.t -> token
|
||||
|
||||
(* Predicates *)
|
||||
|
@ -15,9 +15,22 @@ let sprintf = Printf.sprintf
|
||||
(* TOKENS *)
|
||||
|
||||
type t =
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
| Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
| Lang of lexeme Region.reg Region.reg
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
CAT of Region.t (* "++" *)
|
||||
| CAT of Region.t (* "++" *)
|
||||
|
||||
(* Arithmetics *)
|
||||
|
||||
@ -25,7 +38,6 @@ type t =
|
||||
| PLUS of Region.t (* "+" *)
|
||||
| SLASH of Region.t (* "/" *)
|
||||
| TIMES of Region.t (* "*" *)
|
||||
| PERCENT of Region.t (* "%" *)
|
||||
|
||||
(* Compounds *)
|
||||
|
||||
@ -66,18 +78,6 @@ type t =
|
||||
| BOOL_AND of Region.t (* "&&" *)
|
||||
| NOT of Region.t (* ! *)
|
||||
|
||||
(* Identifiers, labels, numbers and strings *)
|
||||
|
||||
| Ident of string Region.reg
|
||||
| Constr of string Region.reg
|
||||
| Int of (string * Z.t) Region.reg
|
||||
| Nat of (string * Z.t) Region.reg
|
||||
| Mutez of (string * Z.t) Region.reg
|
||||
| String of string Region.reg
|
||||
| Verbatim of string Region.reg
|
||||
| Bytes of (string * Hex.t) Region.reg
|
||||
| Attr of string Region.reg
|
||||
|
||||
(* Keywords *)
|
||||
|
||||
| Else of Region.t
|
||||
@ -109,22 +109,26 @@ let proj_token = function
|
||||
(* Literals *)
|
||||
|
||||
String Region.{region; value} ->
|
||||
region, sprintf "String %s" value
|
||||
region, sprintf "String %S" value
|
||||
| Verbatim Region.{region; value} ->
|
||||
region, sprintf "Verbatim {|%s|}" value
|
||||
region, sprintf "Verbatim %S" value
|
||||
| Bytes Region.{region; value = s,b} ->
|
||||
region,
|
||||
sprintf "Bytes (\"%s\", \"0x%s\")" s (Hex.show b)
|
||||
sprintf "Bytes (%S, \"0x%s\")" s (Hex.show b)
|
||||
| Int Region.{region; value = s,n} ->
|
||||
region, sprintf "Int (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Int (%S, %s)" s (Z.to_string n)
|
||||
| Nat Region.{region; value = s,n} ->
|
||||
region, sprintf "Nat (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Nat (%S, %s)" s (Z.to_string n)
|
||||
| Mutez Region.{region; value = s,n} ->
|
||||
region, sprintf "Mutez (\"%s\", %s)" s (Z.to_string n)
|
||||
region, sprintf "Mutez (%S, %s)" s (Z.to_string n)
|
||||
| Ident Region.{region; value} ->
|
||||
region, sprintf "Ident %s" value
|
||||
region, sprintf "Ident %S" value
|
||||
| Constr Region.{region; value} ->
|
||||
region, sprintf "Constr %s" value
|
||||
region, sprintf "Constr %S" value
|
||||
| Attr Region.{region; value} ->
|
||||
region, sprintf "Attr %S" value
|
||||
| Lang Region.{region; value} ->
|
||||
region, sprintf "Lang %S" (value.Region.value)
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -133,7 +137,6 @@ let proj_token = function
|
||||
| PLUS region -> region, "PLUS"
|
||||
| SLASH region -> region, "SLASH"
|
||||
| TIMES region -> region, "TIMES"
|
||||
| PERCENT region -> region, "PERCENT"
|
||||
| LPAR region -> region, "LPAR"
|
||||
| RPAR region -> region, "RPAR"
|
||||
| LBRACKET region -> region, "LBRACKET"
|
||||
@ -170,7 +173,6 @@ let proj_token = function
|
||||
| Type region -> region, "Type"
|
||||
| C_None region -> region, "C_None"
|
||||
| C_Some region -> region, "C_Some"
|
||||
| Attr Region.{region; value} -> region, sprintf "Attr %s" value
|
||||
| EOF region -> region, "EOF"
|
||||
|
||||
let to_lexeme = function
|
||||
@ -185,6 +187,7 @@ let to_lexeme = function
|
||||
| Ident id -> id.Region.value
|
||||
| Constr id -> id.Region.value
|
||||
| Attr a -> a.Region.value
|
||||
| Lang lang -> Region.(lang.value.value)
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -193,7 +196,6 @@ let to_lexeme = function
|
||||
| PLUS _ -> "+"
|
||||
| SLASH _ -> "/"
|
||||
| TIMES _ -> "*"
|
||||
| PERCENT _ -> "%"
|
||||
| LPAR _ -> "("
|
||||
| RPAR _ -> ")"
|
||||
| LBRACKET _ -> "["
|
||||
@ -432,7 +434,6 @@ let mk_sym lexeme region =
|
||||
| "+" -> Ok (PLUS region)
|
||||
| "/" -> Ok (SLASH region)
|
||||
| "*" -> Ok (TIMES region)
|
||||
| "%" -> Ok (PERCENT region)
|
||||
| "[" -> Ok (LBRACKET region)
|
||||
| "]" -> Ok (RBRACKET region)
|
||||
| "{" -> Ok (LBRACE region)
|
||||
@ -488,6 +489,10 @@ let mk_attr header lexeme region =
|
||||
Ok (Attr Region.{value=lexeme; region})
|
||||
else Error Invalid_attribute
|
||||
|
||||
(* Language injection *)
|
||||
|
||||
let mk_lang lang region = Lang Region.{value=lang; region}
|
||||
|
||||
(* Predicates *)
|
||||
|
||||
let is_string = function String _ -> true | _ -> false
|
||||
@ -549,7 +554,7 @@ let check_right_context token next_token buffer : unit =
|
||||
else ()
|
||||
else
|
||||
if is_bytes token
|
||||
then if is_string next || is_ident next
|
||||
then if is_string next || is_ident next
|
||||
then fail region Missing_break
|
||||
else if is_int next
|
||||
then fail region Odd_lengthed_bytes
|
||||
|
@ -5,15 +5,16 @@
|
||||
|
||||
(* Literals *)
|
||||
|
||||
%token <string Region.reg> String "<string>"
|
||||
%token <string Region.reg> Verbatim "<verbatim>"
|
||||
%token <(LexToken.lexeme * Hex.t) Region.reg> Bytes "<bytes>"
|
||||
%token <(string * Z.t) Region.reg> Int "<int>"
|
||||
%token <(string * Z.t) Region.reg> Nat "<nat>"
|
||||
%token <(string * Z.t) Region.reg> Mutez "<mutez>"
|
||||
%token <string Region.reg> Ident "<ident>"
|
||||
%token <string Region.reg> Constr "<constr>"
|
||||
%token <string Region.reg> Attr "<attr>"
|
||||
%token <string Region.reg> String "<string>"
|
||||
%token <string Region.reg> Verbatim "<verbatim>"
|
||||
%token <(LexToken.lexeme * Hex.t) Region.reg> Bytes "<bytes>"
|
||||
%token <(string * Z.t) Region.reg> Int "<int>"
|
||||
%token <(string * Z.t) Region.reg> Nat "<nat>"
|
||||
%token <(string * Z.t) Region.reg> Mutez "<mutez>"
|
||||
%token <string Region.reg> Ident "<ident>"
|
||||
%token <string Region.reg> Constr "<constr>"
|
||||
%token <string Region.reg> Attr "<attr>"
|
||||
%token <LexToken.lexeme Region.reg Region.reg> Lang "<lang>"
|
||||
|
||||
(* Symbols *)
|
||||
|
||||
@ -21,7 +22,6 @@
|
||||
%token <Region.t> PLUS "+"
|
||||
%token <Region.t> SLASH "/"
|
||||
%token <Region.t> TIMES "*"
|
||||
%token <Region.t> PERCENT "%"
|
||||
|
||||
%token <Region.t> LPAR "("
|
||||
%token <Region.t> RPAR ")"
|
||||
|
@ -801,20 +801,20 @@ call_expr:
|
||||
in ECall {region; value} }
|
||||
|
||||
common_expr:
|
||||
"<int>" { EArith (Int $1) }
|
||||
| "<mutez>" { EArith (Mutez $1) }
|
||||
| "<nat>" { EArith (Nat $1) }
|
||||
| "<bytes>" { EBytes $1 }
|
||||
| "<ident>" | module_field { EVar $1 }
|
||||
| projection { EProj $1 }
|
||||
| "_" { EVar {value = "_"; region = $1} }
|
||||
| update_record { EUpdate $1 }
|
||||
| "<string>" { EString (String $1) }
|
||||
| "<verbatim>" { EString (Verbatim $1) }
|
||||
| unit { EUnit $1 }
|
||||
| "false" { ELogic (BoolExpr (False $1)) }
|
||||
| "true" { ELogic (BoolExpr (True $1)) }
|
||||
| code_insert { ECodeInsert $1 }
|
||||
"<int>" { EArith (Int $1) }
|
||||
| "<mutez>" { EArith (Mutez $1) }
|
||||
| "<nat>" { EArith (Nat $1) }
|
||||
| "<bytes>" { EBytes $1 }
|
||||
| "<ident>" | module_field { EVar $1 }
|
||||
| projection { EProj $1 }
|
||||
| "_" { EVar {value = "_"; region = $1} }
|
||||
| update_record { EUpdate $1 }
|
||||
| "<string>" { EString (String $1) }
|
||||
| "<verbatim>" { EString (Verbatim $1) }
|
||||
| unit { EUnit $1 }
|
||||
| "false" { ELogic (BoolExpr (False $1)) }
|
||||
| "true" { ELogic (BoolExpr (True $1)) }
|
||||
| code_inj { ECodeInj $1 }
|
||||
|
||||
core_expr_2:
|
||||
common_expr { $1 }
|
||||
@ -920,15 +920,10 @@ update_record:
|
||||
rbrace = $6}
|
||||
in {region; value} }
|
||||
|
||||
code_insert:
|
||||
"[" "%" Constr expr "]" {
|
||||
let region = cover $1 $5 in
|
||||
let value = {
|
||||
lbracket =$1;
|
||||
percent =$2;
|
||||
language =$3;
|
||||
code =$4;
|
||||
rbracket =$5}
|
||||
code_inj:
|
||||
"<lang>" expr "]" {
|
||||
let region = cover $1.region $3
|
||||
and value = {language=$1; code=$2; rbracket=$3}
|
||||
in {region; value} }
|
||||
|
||||
expr_with_let_expr:
|
||||
|
@ -159,7 +159,7 @@ and pp_expr = function
|
||||
| ELetIn e -> pp_let_in e
|
||||
| EFun e -> pp_fun e
|
||||
| ESeq e -> pp_seq e
|
||||
| ECodeInsert e -> pp_code_insert e
|
||||
| ECodeInj e -> pp_code_inj e
|
||||
|
||||
and pp_case_expr {value; _} =
|
||||
let {expr; cases; _} = value in
|
||||
@ -320,11 +320,11 @@ and pp_update {value; _} =
|
||||
string "{..." ^^ record ^^ string ","
|
||||
^^ nest 2 (break 1 ^^ updates ^^ string "}")
|
||||
|
||||
and pp_code_insert {value; _} =
|
||||
and pp_code_inj {value; _} =
|
||||
let {language; code; _} = value in
|
||||
let language = pp_string language
|
||||
and code = pp_expr code in
|
||||
string "[%" ^^ language ^^ string " " ^^ code ^^ string " ]"
|
||||
let language = pp_string language.value
|
||||
and code = pp_expr code in
|
||||
string "[%" ^^ language ^/^ code ^^ string "]"
|
||||
|
||||
and pp_field_path_assign {value; _} =
|
||||
let {field_path; field_expr; _} = value in
|
||||
|
File diff suppressed because it is too large
Load Diff
@ -79,6 +79,7 @@ module type TOKEN =
|
||||
val mk_bytes : lexeme -> Region.t -> token
|
||||
val mk_constr : lexeme -> Region.t -> token
|
||||
val mk_attr : string -> lexeme -> Region.t -> (token, attr_err) result
|
||||
val mk_lang : lexeme Region.reg -> Region.t -> token
|
||||
val eof : Region.t -> token
|
||||
|
||||
(* Predicates *)
|
||||
|
@ -43,6 +43,7 @@ module type TOKEN =
|
||||
val mk_bytes : lexeme -> Region.t -> token
|
||||
val mk_constr : lexeme -> Region.t -> token
|
||||
val mk_attr : string -> lexeme -> Region.t -> (token, attr_err) result
|
||||
val mk_lang : lexeme Region.reg -> Region.t -> token
|
||||
val eof : Region.t -> token
|
||||
|
||||
(* Predicates *)
|
||||
@ -273,6 +274,15 @@ module Make (Token : TOKEN) : (S with module Token = Token) =
|
||||
let token = Token.mk_constr lexeme region
|
||||
in state#enqueue token
|
||||
|
||||
let mk_lang lang state buffer =
|
||||
let region, _, state = state#sync buffer in
|
||||
let start = region#start#shift_bytes 1 in
|
||||
let stop = region#stop in
|
||||
let lang_reg = Region.make ~start ~stop in
|
||||
let lang = Region.{value=lang; region=lang_reg} in
|
||||
let token = Token.mk_lang lang region
|
||||
in state#enqueue token
|
||||
|
||||
let mk_sym state buffer =
|
||||
let region, lexeme, state = state#sync buffer in
|
||||
match Token.mk_sym lexeme region with
|
||||
@ -314,7 +324,7 @@ let esc = "\\n" | "\\\"" | "\\\\" | "\\b"
|
||||
|
||||
let common_sym = ';' | ',' | '(' | ')' | '[' | ']' | '{' | '}'
|
||||
| '=' | ':' | '|' | "->" | '.' | '_' | '^'
|
||||
| '+' | '-' | '*' | '/' | '%' | '<' | "<=" | '>' | ">="
|
||||
| '+' | '-' | '*' | '/' | '<' | "<=" | '>' | ">="
|
||||
let pascaligo_sym = "=/=" | '#' | ":="
|
||||
let cameligo_sym = "<>" | "::" | "||" | "&&"
|
||||
let reasonligo_sym = '!' | "=>" | "!=" | "==" | "++" | "..." | "||" | "&&"
|
||||
@ -388,6 +398,7 @@ and scan state = parse
|
||||
| eof { mk_eof state lexbuf }
|
||||
| "[@" (attr as a) "]" { mk_attr "[@" a state lexbuf }
|
||||
| "[@@" (attr as a) "]" { mk_attr "[@@" a state lexbuf }
|
||||
| "[%" (attr as l) { mk_lang l state lexbuf }
|
||||
|
||||
(* Management of #include preprocessing directives
|
||||
|
||||
|
@ -631,19 +631,17 @@ in trace (abstracting_expr t) @@
|
||||
return @@ e_sequence a e1'
|
||||
in List.fold_left apply expr' more)
|
||||
)
|
||||
| ECond c -> (
|
||||
| ECond c ->
|
||||
let (c , loc) = r_split c in
|
||||
let%bind expr = compile_expression c.test in
|
||||
let%bind match_true = compile_expression c.ifso in
|
||||
let%bind match_false = compile_expression c.ifnot in
|
||||
return @@ e_cond ~loc expr match_true match_false
|
||||
)
|
||||
| ECodeInsert ci -> (
|
||||
let (ci, loc) = r_split ci in
|
||||
let language = ci.language.value in
|
||||
let%bind code = compile_expression ci.code in
|
||||
return @@ e_raw_code ~loc language code
|
||||
)
|
||||
| ECodeInj ci ->
|
||||
let ci, loc = r_split ci in
|
||||
let language = ci.language.value.value in
|
||||
let%bind code = compile_expression ci.code
|
||||
in ok @@ e_raw_code ~loc language code
|
||||
|
||||
and compile_fun lamb' : expr result =
|
||||
let return x = ok x in
|
||||
|
@ -459,11 +459,11 @@ let rec compile_expression (t:Raw.expr) : expr result =
|
||||
let (f , loc) = r_split f in
|
||||
let%bind (_ty_opt, f') = compile_fun_expression ~loc f
|
||||
in return @@ f'
|
||||
| ECodeInsert ci ->
|
||||
let (ci, loc) = r_split ci in
|
||||
let language = ci.language.value in
|
||||
let%bind code = compile_expression ci.code in
|
||||
return @@ e_raw_code ~loc language code
|
||||
| ECodeInj ci ->
|
||||
let ci, loc = r_split ci in
|
||||
let language = ci.language.value.value in
|
||||
let%bind code = compile_expression ci.code
|
||||
in ok @@ e_raw_code ~loc language code
|
||||
|
||||
and compile_update (u: Raw.update Region.reg) =
|
||||
let u, loc = r_split u in
|
||||
|
Loading…
Reference in New Issue
Block a user