Compleating assignment for interpreter, modified grammars, fixed tests
This commit is contained in:
@ -5,7 +5,7 @@ Random.self_init ()
|
||||
|
||||
let (let*) = Result.bind
|
||||
|
||||
let rec evaluate (mem: memory) (command: t_exp) : (permittedValues, error) result =
|
||||
let rec evaluate (mem: memory) (command: t_exp) : (permittedValues, [> error]) result =
|
||||
match command with
|
||||
Integer n -> Ok (IntegerPermitted n)
|
||||
| Boolean b -> Ok (BooleanPermitted b)
|
||||
@ -341,7 +341,7 @@ let rec evaluate (mem: memory) (command: t_exp) : (permittedValues, error) resul
|
||||
evaluate mem2 rest
|
||||
|
||||
|
||||
let reduce (program: t_exp) (iin : int) : (int, error) result =
|
||||
let reduce (program: t_exp) (iin : int) : (int, [> error]) result =
|
||||
let program' = (Application (program, (Integer iin))) in
|
||||
let mem : memory = {assignments = VariableMap.empty} in
|
||||
match (evaluate mem program') with
|
||||
|
||||
@ -1,3 +1,3 @@
|
||||
val reduce : Types.t_exp -> int -> (int, Types.error) result
|
||||
val evaluate : Types.memory -> Types.t_exp -> (Types.permittedValues, [> Types.error]) result
|
||||
|
||||
val evaluate : Types.memory -> Types.t_exp -> (Types.permittedValues, Types.error) result
|
||||
val reduce : Types.t_exp -> int -> (int, [> Types.error]) result
|
||||
|
||||
@ -5,7 +5,7 @@ Random.self_init ()
|
||||
|
||||
let (let*) = Result.bind
|
||||
|
||||
let rec evaluate_type (program: t_exp) (context: ftype VariableMap.t) : (ftype, error) result =
|
||||
let rec evaluate_type (program: t_exp) (context: ftype VariableMap.t) : (ftype, [> typechecking_error]) result =
|
||||
match program with
|
||||
Integer _ -> Ok IntegerType
|
||||
| Boolean _ -> Ok BooleanType
|
||||
@ -150,7 +150,7 @@ let rec evaluate_type (program: t_exp) (context: ftype VariableMap.t) : (ftype,
|
||||
| _ -> Error (`WrongTypeSpecification
|
||||
"Specification of function is not a function type.")
|
||||
|
||||
let typecheck (program: t_exp) : (ftype, error) result =
|
||||
let typecheck (program: t_exp) : (ftype, [> typechecking_error]) result =
|
||||
let* typeprogram = evaluate_type program VariableMap.empty in
|
||||
match typeprogram with
|
||||
FunctionType (IntegerType, IntegerType) -> (
|
||||
|
||||
@ -1 +1 @@
|
||||
val typecheck : Types.t_exp -> (Types.ftype, Types.error) result
|
||||
val typecheck : Types.t_exp -> (Types.ftype, [> Types.typechecking_error]) result
|
||||
|
||||
@ -53,9 +53,18 @@ type memory = {
|
||||
assignments: permittedValues VariableMap.t
|
||||
}
|
||||
|
||||
type error = [
|
||||
|
||||
type base_error = [
|
||||
`AbsentAssignment of string
|
||||
| `WrongType of string
|
||||
| `DivisionByZero of string
|
||||
]
|
||||
|
||||
type typechecking_error = [
|
||||
| base_error
|
||||
| `WrongTypeSpecification of string
|
||||
]
|
||||
|
||||
type error = [
|
||||
| base_error
|
||||
| `DivisionByZero of string
|
||||
]
|
||||
|
||||
@ -53,9 +53,18 @@ type memory = {
|
||||
assignments: permittedValues VariableMap.t
|
||||
}
|
||||
|
||||
type error = [
|
||||
|
||||
type base_error = [
|
||||
`AbsentAssignment of string
|
||||
| `WrongType of string
|
||||
| `DivisionByZero of string
|
||||
]
|
||||
|
||||
type typechecking_error = [
|
||||
| base_error
|
||||
| `WrongTypeSpecification of string
|
||||
]
|
||||
|
||||
type error = [
|
||||
| base_error
|
||||
| `DivisionByZero of string
|
||||
]
|
||||
|
||||
@ -13,4 +13,4 @@
|
||||
(modules Lexer Parser Types Semantics TypeChecker)
|
||||
(libraries utility menhirLib))
|
||||
|
||||
(include_subdirs qualified)
|
||||
(include_subdirs qualified)
|
||||
|
||||
@ -9,18 +9,24 @@
|
||||
|
||||
let keyword_table =
|
||||
let mapping = [
|
||||
("main", MAIN);
|
||||
("skip", SKIP);
|
||||
("if", IF);
|
||||
("else", ELSE);
|
||||
("while", WHILE);
|
||||
("for", FOR);
|
||||
("as", AS);
|
||||
("def", DEF);
|
||||
("do", DO);
|
||||
("true", BOOL(true));
|
||||
("else", ELSE);
|
||||
("false", BOOL(false));
|
||||
("for", FOR);
|
||||
("if", IF);
|
||||
("input", INPUT);
|
||||
("main", MAIN);
|
||||
("not", BNOT);
|
||||
("rand", RAND);
|
||||
("output", OUTPUT);
|
||||
("powmod", POWERMOD);
|
||||
("rand", RAND);
|
||||
("skip", SKIP);
|
||||
("then", THEN);
|
||||
("true", BOOL(true));
|
||||
("while", WHILE);
|
||||
("with", WITH);
|
||||
]
|
||||
in create_hashtable (List.length mapping) mapping
|
||||
}
|
||||
@ -42,26 +48,24 @@ rule read = parse
|
||||
| Some keyword -> keyword
|
||||
| None -> VARIABLE(v)
|
||||
}
|
||||
| ";" {SEQUENCE}
|
||||
| "," {COMMA}
|
||||
| "{" {LEFTGPAR}
|
||||
| "}" {RIGHTGPAR}
|
||||
| "%" {MODULO}
|
||||
| "&&" {BAND}
|
||||
| "(" {LEFTPAR}
|
||||
| ")" {RIGHTPAR}
|
||||
| "<" {BCMPLESS}
|
||||
| ">" {BCMPGREATER}
|
||||
| "+" {PLUS}
|
||||
| "-" {MINUS}
|
||||
| "*" {TIMES}
|
||||
| "+" {PLUS}
|
||||
| "," {COMMA}
|
||||
| "-" {MINUS}
|
||||
| "/" {DIVISION}
|
||||
| "%" {MODULO}
|
||||
| "^" {POWER}
|
||||
| ":=" {ASSIGNMENT}
|
||||
| "&&" {BAND}
|
||||
| "||" {BOR}
|
||||
| "==" {BCMP}
|
||||
| ";" {SEQUENCE}
|
||||
| "<" {BCMPLESS}
|
||||
| "<=" {BCMPLESSEQ}
|
||||
| "==" {BCMP}
|
||||
| ">" {BCMPGREATER}
|
||||
| ">=" {BCMPGREATEREQ}
|
||||
| "^" {POWER}
|
||||
| "||" {BOR}
|
||||
| integer as i {INT(int_of_string i)}
|
||||
| "(*" {comments 0 lexbuf}
|
||||
| eof {EOF}
|
||||
|
||||
File diff suppressed because it is too large
Load Diff
@ -6,14 +6,13 @@
|
||||
%}
|
||||
|
||||
(* tokens *)
|
||||
%token MAIN SKIP ASSIGNMENT SEQUENCE IF ELSE WHILE FOR DO COMMA
|
||||
%token LEFTGPAR RIGHTGPAR
|
||||
%token <bool> BOOL
|
||||
%token BAND BOR BNOT BCMP BCMPLESS BCMPLESSEQ BCMPGREATER BCMPGREATEREQ
|
||||
%token <string> VARIABLE
|
||||
%token <int> INT
|
||||
%token LEFTPAR RIGHTPAR
|
||||
%token MAIN DEF WITH INPUT OUTPUT AS SKIP ASSIGNMENT SEQUENCE IF THEN ELSE WHILE
|
||||
%token FOR DO COMMA LEFTPAR RIGHTPAR
|
||||
%token PLUS MINUS TIMES DIVISION MODULO POWER POWERMOD RAND
|
||||
%token BAND BOR BNOT BCMP BCMPLESS BCMPLESSEQ BCMPGREATER BCMPGREATEREQ
|
||||
%token <bool> BOOL
|
||||
%token <int> INT
|
||||
%token <string> VARIABLE
|
||||
%token EOF
|
||||
|
||||
%type <c_exp> cexpp
|
||||
@ -25,7 +24,7 @@
|
||||
%start prg
|
||||
|
||||
(* associativity in order of precedence *)
|
||||
%left twoseq
|
||||
%left lowest
|
||||
%left SEQUENCE
|
||||
%left ELSE
|
||||
%left PLUS MINUS BOR BAND
|
||||
@ -34,52 +33,53 @@
|
||||
%left MODULO
|
||||
%left TIMES
|
||||
%left POWER
|
||||
%left DO
|
||||
|
||||
%%
|
||||
|
||||
(* grammar *)
|
||||
prg:
|
||||
| MAIN; a = VARIABLE; b = VARIABLE; LEFTGPAR; t = cexpp; RIGHTGPAR; EOF
|
||||
{Main (a, b, t)} // main a b {...}
|
||||
| DEF; MAIN; WITH; INPUT; a = VARIABLE; OUTPUT; b = VARIABLE; AS; t = cexpp; EOF
|
||||
{Main (a, b, t)} // def main with input a output b as t
|
||||
cexpp:
|
||||
| SKIP {Skip} // skip
|
||||
| a = VARIABLE; ASSIGNMENT; body = aexpp
|
||||
{Assignment (a, body)} // a := ...
|
||||
| t1 = cexpp; SEQUENCE; t2 = cexpp %prec twoseq
|
||||
{Sequence (t1, t2)} // ...; ...
|
||||
| t = cexpp; SEQUENCE {t} // ...;
|
||||
| IF; LEFTPAR; guard = bexpp; RIGHTPAR; body1 = cexpp; ELSE; body2 = cexpp
|
||||
{If (guard, body1, body2)} // if (...) ... else ...
|
||||
| WHILE; guard = bexpp; DO; LEFTGPAR; body = cexpp; RIGHTGPAR
|
||||
{While (guard, body)} // while ... do {...}
|
||||
{Assignment (a, body)} // a := body
|
||||
| t1 = cexpp; SEQUENCE; t2 = cexpp %prec lowest
|
||||
{Sequence (t1, t2)} // t1; t2
|
||||
| t = cexpp; SEQUENCE {t} // t;
|
||||
| IF; guard = bexpp; THEN; body1 = cexpp; ELSE; body2 = cexpp
|
||||
{If (guard, body1, body2)} // if ... then ... else ...
|
||||
| WHILE; guard = bexpp; DO; body = cexpp;
|
||||
{While (guard, body)} // while ... do ...
|
||||
| FOR; LEFTPAR; ass = cexpp; COMMA; guard = bexpp; COMMA; iter = cexpp; RIGHTPAR;
|
||||
DO; LEFTGPAR; body = cexpp; RIGHTGPAR
|
||||
{For (ass, guard, iter, body)} // for (..., ..., ...) do {...}
|
||||
| LEFTGPAR; t = cexpp; RIGHTGPAR {t} // {...}
|
||||
DO; body = cexpp;
|
||||
{For (ass, guard, iter, body)} // for (..., ..., ...) do ...
|
||||
| LEFTPAR; t = cexpp; RIGHTPAR {t} // (...)
|
||||
bexpp:
|
||||
| b = BOOL {Boolean (b)}
|
||||
| b1 = bexpp; BAND; b2 = bexpp {BAnd (b1, b2)}
|
||||
| b1 = bexpp; BOR; b2 = bexpp {BOr (b1, b2)}
|
||||
| BNOT; b = bexpp {BNot (b)}
|
||||
| a1 = aexpp; BCMP; a2 = aexpp {BCmp (a1, a2)}
|
||||
| a1 = aexpp; BCMPLESS; a2 = aexpp {BCmpLess (a1, a2)}
|
||||
| a1 = aexpp; BCMPLESSEQ; a2 = aexpp {BCmpLessEq (a1, a2)}
|
||||
| a1 = aexpp; BCMPGREATER; a2 = aexpp {BCmpGreater (a1, a2)}
|
||||
| a1 = aexpp; BCMPGREATEREQ; a2 = aexpp {BCmpGreaterEq (a1, a2)}
|
||||
| LEFTPAR; b = bexpp; RIGHTPAR {b}
|
||||
| b = BOOL {Boolean (b)} // true, false
|
||||
| b1 = bexpp; BAND; b2 = bexpp {BAnd (b1, b2)} // &&
|
||||
| b1 = bexpp; BOR; b2 = bexpp {BOr (b1, b2)} // ||
|
||||
| BNOT; b = bexpp {BNot (b)} // not
|
||||
| a1 = aexpp; BCMP; a2 = aexpp {BCmp (a1, a2)} // ==
|
||||
| a1 = aexpp; BCMPLESS; a2 = aexpp {BCmpLess (a1, a2)} // <
|
||||
| a1 = aexpp; BCMPLESSEQ; a2 = aexpp {BCmpLessEq (a1, a2)} // <=
|
||||
| a1 = aexpp; BCMPGREATER; a2 = aexpp {BCmpGreater (a1, a2)} // >
|
||||
| a1 = aexpp; BCMPGREATEREQ; a2 = aexpp {BCmpGreaterEq (a1, a2)} // >=
|
||||
| LEFTPAR; b = bexpp; RIGHTPAR {b} // (b)
|
||||
aexpp:
|
||||
| a = VARIABLE {Variable (a)}
|
||||
| i = INT {Integer (i)}
|
||||
| t1 = aexpp; PLUS; t2 = aexpp {Plus (t1, t2)}
|
||||
| t1 = aexpp; MINUS; t2 = aexpp {Minus (t1, t2)}
|
||||
| t1 = aexpp; PLUS; t2 = aexpp {Plus (t1, t2)} // +
|
||||
| t1 = aexpp; MINUS; t2 = aexpp {Minus (t1, t2)} // -
|
||||
| MINUS; i = INT {Integer (-i)}
|
||||
| t1 = aexpp; TIMES; t2 = aexpp {Times (t1, t2)}
|
||||
| t1 = aexpp; DIVISION; t2 = aexpp {Division (t1, t2)}
|
||||
| t1 = aexpp; MODULO; t2 = aexpp {Modulo (t1, t2)}
|
||||
| t1 = aexpp; POWER; t2 = aexpp {Power (t1, t2)}
|
||||
| t1 = aexpp; TIMES; t2 = aexpp {Times (t1, t2)} // *
|
||||
| t1 = aexpp; DIVISION; t2 = aexpp {Division (t1, t2)} // /
|
||||
| t1 = aexpp; MODULO; t2 = aexpp {Modulo (t1, t2)} // %
|
||||
| t1 = aexpp; POWER; t2 = aexpp {Power (t1, t2)} // ^
|
||||
| POWERMOD; LEFTPAR; t1 = aexpp; COMMA;
|
||||
t2 = aexpp; COMMA;
|
||||
t3 = aexpp; RIGHTPAR
|
||||
{PowerMod (t1, t2, t3)} // powmod (..., ..., ...)
|
||||
| RAND; LEFTPAR; t = aexpp; RIGHTPAR {Rand (t)}
|
||||
| LEFTPAR; a = aexpp; RIGHTPAR {a}
|
||||
{PowerMod (t1, t2, t3)} // powmod(..., ..., ...)
|
||||
| RAND; LEFTPAR; t = aexpp; RIGHTPAR {Rand (t)} // rand()
|
||||
| LEFTPAR; a = aexpp; RIGHTPAR {a} // (a)
|
||||
|
||||
@ -4,139 +4,153 @@ module Utility = Utility;;
|
||||
|
||||
Random.self_init ()
|
||||
|
||||
let rec evaluate (mem: memory) (command: c_exp) =
|
||||
let (let*) = Result.bind
|
||||
|
||||
let rec evaluate (mem: memory) (command: c_exp) : (memory, [> error]) result =
|
||||
match command with
|
||||
Skip -> mem
|
||||
| Assignment (v, exp_a) -> {
|
||||
(* Map.add replaces the previeus value *)
|
||||
assignments = VariableMap.add v (evaluate_a mem exp_a) mem.assignments
|
||||
Skip -> Ok mem
|
||||
| Assignment (v, exp_a) ->
|
||||
let* vval = evaluate_a mem exp_a in
|
||||
Ok {
|
||||
(* Map.add replaces the previus value *)
|
||||
assignments = VariableMap.add v vval mem.assignments
|
||||
}
|
||||
| Sequence (exp_c1, exp_c2) -> (
|
||||
let mem2 = evaluate mem exp_c1 in
|
||||
let* mem2 = evaluate mem exp_c1 in
|
||||
evaluate mem2 exp_c2
|
||||
)
|
||||
| If (exp_b, exp_c1, exp_c2) -> (
|
||||
if evaluate_b mem exp_b then
|
||||
let* guard = evaluate_b mem exp_b in
|
||||
if guard then
|
||||
evaluate mem exp_c1
|
||||
else
|
||||
evaluate mem exp_c2
|
||||
)
|
||||
| While (exp_b, exp_c) -> (
|
||||
if evaluate_b mem exp_b then
|
||||
let mem2 = evaluate mem exp_c in
|
||||
let* guard = evaluate_b mem exp_b in
|
||||
if guard then
|
||||
let* mem2 = evaluate mem exp_c in
|
||||
evaluate mem2 command
|
||||
else
|
||||
mem
|
||||
Ok mem
|
||||
)
|
||||
| For (exp_c1, exp_b, exp_c2, body_c) -> (
|
||||
let mem2 = evaluate mem exp_c1 in
|
||||
let rec f localmem =
|
||||
if (evaluate_b localmem exp_b)
|
||||
then f (
|
||||
let tmpmem = (evaluate localmem body_c) in
|
||||
(evaluate tmpmem exp_c2))
|
||||
else localmem
|
||||
let* mem2 = evaluate mem exp_c1 in
|
||||
let rec f (localmem: memory) : (memory, [> error]) result =
|
||||
let* guard = (evaluate_b localmem exp_b) in
|
||||
if guard
|
||||
then
|
||||
let* stepmem = evaluate localmem body_c in
|
||||
let* incrementmem = evaluate stepmem exp_c2 in
|
||||
f incrementmem
|
||||
else Ok localmem
|
||||
in
|
||||
f mem2
|
||||
)
|
||||
|
||||
and evaluate_a (mem: memory) (exp_a: a_exp) =
|
||||
|
||||
and evaluate_a (mem: memory) (exp_a: a_exp) : (int, [> error]) result =
|
||||
match exp_a with
|
||||
Variable v -> (
|
||||
match VariableMap.find_opt v mem.assignments with
|
||||
None -> raise (AbsentAssignment ("The variable " ^ v ^ " is not defined."))
|
||||
| Some a -> a
|
||||
None -> Error (`AbsentAssignment ("The variable " ^ v ^ " is not defined."))
|
||||
| Some a -> Ok a
|
||||
)
|
||||
| Integer n -> n
|
||||
| Integer n -> Ok n
|
||||
| Plus (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val + exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val + exp_a2val)
|
||||
)
|
||||
| Minus (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val - exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val - exp_a2val)
|
||||
)
|
||||
| Times (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val * exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val * exp_a2val)
|
||||
)
|
||||
| Division (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
try
|
||||
exp_a1val / exp_a2val
|
||||
with Division_by_zero -> raise (DivisionByZero "Dividing by zero")
|
||||
Ok (exp_a1val / exp_a2val)
|
||||
with Division_by_zero -> Error (`DivisionByZero "Dividing by zero")
|
||||
)
|
||||
| Modulo (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val mod exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val mod exp_a2val)
|
||||
)
|
||||
| Power (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
Utility.pow exp_a1val exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (Utility.pow exp_a1val exp_a2val)
|
||||
)
|
||||
| PowerMod (exp_a1, exp_a2, exp_a3) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
let exp_a3val = evaluate_a mem exp_a3 in
|
||||
Utility.powmod exp_a1val exp_a3val exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
let* exp_a3val = evaluate_a mem exp_a3 in
|
||||
Ok (Utility.powmod exp_a1val exp_a3val exp_a2val)
|
||||
)
|
||||
| Rand (exp_a) -> (
|
||||
Random.int (evaluate_a mem exp_a)
|
||||
let* exp_aval = evaluate_a mem exp_a in
|
||||
Ok (Random.int exp_aval)
|
||||
)
|
||||
and evaluate_b (mem: memory) (exp_b: b_exp) =
|
||||
|
||||
|
||||
and evaluate_b (mem: memory) (exp_b: b_exp) : (bool, [> error]) result =
|
||||
match exp_b with
|
||||
Boolean b -> b
|
||||
Boolean b -> Ok b
|
||||
| BAnd (exp_b1, exp_b2) -> (
|
||||
let exp_b1val = evaluate_b mem exp_b1 in
|
||||
let exp_b2val = evaluate_b mem exp_b2 in
|
||||
exp_b1val && exp_b2val
|
||||
let* exp_b1val = evaluate_b mem exp_b1 in
|
||||
let* exp_b2val = evaluate_b mem exp_b2 in
|
||||
Ok (exp_b1val && exp_b2val)
|
||||
)
|
||||
| BOr (exp_b1, exp_b2) -> (
|
||||
let exp_b1val = evaluate_b mem exp_b1 in
|
||||
let exp_b2val = evaluate_b mem exp_b2 in
|
||||
exp_b1val || exp_b2val
|
||||
let* exp_b1val = evaluate_b mem exp_b1 in
|
||||
let* exp_b2val = evaluate_b mem exp_b2 in
|
||||
Ok (exp_b1val || exp_b2val)
|
||||
)
|
||||
| BNot (exp_b) -> (
|
||||
not (evaluate_b mem exp_b)
|
||||
let* exp_bval = evaluate_b mem exp_b in
|
||||
Ok (not exp_bval)
|
||||
)
|
||||
| BCmp (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val = exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val = exp_a2val)
|
||||
)
|
||||
| BCmpLess (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val < exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val < exp_a2val)
|
||||
)
|
||||
| BCmpLessEq (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val <= exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val <= exp_a2val)
|
||||
)
|
||||
| BCmpGreater (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val > exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val > exp_a2val)
|
||||
)
|
||||
| BCmpGreaterEq (exp_a1, exp_a2) -> (
|
||||
let exp_a1val = evaluate_a mem exp_a1 in
|
||||
let exp_a2val = evaluate_a mem exp_a2 in
|
||||
exp_a1val >= exp_a2val
|
||||
let* exp_a1val = evaluate_a mem exp_a1 in
|
||||
let* exp_a2val = evaluate_a mem exp_a2 in
|
||||
Ok (exp_a1val >= exp_a2val)
|
||||
)
|
||||
|
||||
|
||||
let reduce (program: p_exp) (iin : int) =
|
||||
let reduce (program: p_exp) (iin : int) : (int, [> error]) result =
|
||||
match program with
|
||||
Main (vin, vout, expression) -> (
|
||||
let mem : memory = {assignments = (VariableMap.empty |> VariableMap.add vin iin)} in
|
||||
match VariableMap.find_opt vout (evaluate mem expression).assignments with
|
||||
None -> raise (AbsentAssignment ("The output variable is not defined (" ^ vout ^ ")"))
|
||||
| Some a -> a
|
||||
let* resultmem : memory = evaluate mem expression in
|
||||
match VariableMap.find_opt vout resultmem.assignments with
|
||||
None -> Error (`AbsentAssignment ("The output variable is not defined (" ^ vout ^ ")"))
|
||||
| Some a -> Ok a
|
||||
)
|
||||
|
||||
@ -1,3 +1,3 @@
|
||||
open Types
|
||||
|
||||
val reduce : p_exp -> int -> int
|
||||
val reduce : p_exp -> int -> (int, [> Types.error]) result
|
||||
|
||||
@ -38,5 +38,7 @@ type memory = {
|
||||
assignments: int VariableMap.t
|
||||
}
|
||||
|
||||
exception AbsentAssignment of string
|
||||
exception DivisionByZero of string
|
||||
type error = [
|
||||
`AbsentAssignment of string
|
||||
| `DivisionByZero of string
|
||||
]
|
||||
|
||||
@ -38,5 +38,7 @@ type memory = {
|
||||
assignments: int VariableMap.t
|
||||
}
|
||||
|
||||
exception AbsentAssignment of string
|
||||
exception DivisionByZero of string
|
||||
type error = [
|
||||
`AbsentAssignment of string
|
||||
| `DivisionByZero of string
|
||||
]
|
||||
|
||||
Reference in New Issue
Block a user