aboutsummaryrefslogtreecommitdiff
path: root/lab4/src
diff options
context:
space:
mode:
Diffstat (limited to 'lab4/src')
-rw-r--r--lab4/src/main/scala/jsy/lab4/Lab4.scala362
-rw-r--r--lab4/src/main/scala/jsy/lab4/Lab4.worksheet.sc39
-rw-r--r--lab4/src/main/scala/jsy/lab4/Lab4.worksheet.ts35
-rw-r--r--lab4/src/main/scala/jsy/lab4/Parser.scala437
-rw-r--r--lab4/src/main/scala/jsy/lab4/ast.scala240
-rw-r--r--lab4/src/main/scala/jsy/util/JsyApplication.scala191
-rw-r--r--lab4/src/test/resources/lab4/test4001_id.ans4
-rw-r--r--lab4/src/test/resources/lab4/test4001_id.jsy1
-rw-r--r--lab4/src/test/resources/lab4/test4002_multiparamfun.ans6
-rw-r--r--lab4/src/test/resources/lab4/test4002_multiparamfun.jsy1
-rw-r--r--lab4/src/test/resources/lab4/test4007_objliteral.ans4
-rw-r--r--lab4/src/test/resources/lab4/test4007_objliteral.jsy1
-rw-r--r--lab4/src/test/resources/lab4/test4010_deref.ans4
-rw-r--r--lab4/src/test/resources/lab4/test4010_deref.jsy1
-rw-r--r--lab4/src/test/resources/lab4/test4029_simplerec.ans11
-rw-r--r--lab4/src/test/resources/lab4/test4029_simplerec.jsy2
-rw-r--r--lab4/src/test/scala/jsy/lab4/Lab4Spec.scala217
-rw-r--r--lab4/src/test/scala/jsy/tester/JavascriptyTester.scala23
18 files changed, 1579 insertions, 0 deletions
diff --git a/lab4/src/main/scala/jsy/lab4/Lab4.scala b/lab4/src/main/scala/jsy/lab4/Lab4.scala
new file mode 100644
index 0000000..d3f16b2
--- /dev/null
+++ b/lab4/src/main/scala/jsy/lab4/Lab4.scala
@@ -0,0 +1,362 @@
+package jsy.lab4
+
+object Lab4 extends jsy.util.JsyApplication {
+ import ast._
+
+ /*
+ * CSCI 3155: Lab 4
+ * Jack Sangdahl
+ */
+
+ /* Helper functions */
+ def mapFirst[A](f: A => Option[A])(l: List[A]): List[A] = l match {
+ case Nil => l
+ case h :: t =>
+ f(h) match {
+ case Some(x) => x :: t
+ case None => h :: mapFirst(f)(t)
+ }
+ }
+
+ /*
+ * Helper function that implements the semantics of inequality
+ * operators Lt, Le, Gt, and Ge on values.
+ */
+ def doInequality(bop: Bop, v1: Expr, v2: Expr): Boolean = {
+ require(isValue(v1), s"doInequality: v1 ${v1} is not a value")
+ require(isValue(v2), s"doInequality: v2 ${v2} is not a value")
+ require(bop == Lt || bop == Le || bop == Gt || bop == Ge)
+ ((v1, v2): @unchecked) match {
+ case (S(s1), S(s2)) =>
+ (bop: @unchecked) match {
+ case Lt => s1 < s2
+ case Le => s1 <= s2
+ case Gt => s1 > s2
+ case Ge => s1 >= s2
+ }
+ case (N(n1), N(n2)) =>
+ (bop: @unchecked) match {
+ case Lt => n1 < n2
+ case Le => n1 <= n2
+ case Gt => n1 > n2
+ case Ge => n1 >= n2
+ }
+ }
+ }
+
+ /* Small-Step Interpreter */
+
+ /* Scope-respecting substitution substituting v for free uses of variable x iin e. */
+ def substitute(v: Expr, x: String, e: Expr): Expr = {
+ def subst(e: Expr): Expr = e match {
+ case N(_) | B(_) | Undefined | S(_) => e
+ case Print(e1) => Print(subst(e1))
+ case Unary(uop, e1) => Unary(uop, subst(e1))
+ case Binary(bop, e1, e2) => Binary(bop, subst(e1), subst(e2))
+ case If(e1, e2, e3) => If(subst(e1), subst(e2), subst(e3))
+ case Var(y) => if (x == y) v else e
+ case ConstDecl(y, e1, e2) =>
+ if (x == y) ConstDecl(y, subst(e1), e2)
+ else ConstDecl(y, subst(e1), subst(e2))
+ case Fun(xopt, yts, tretopt, e1) =>
+ xopt match {
+ case Some(y) if (x == y) => e
+ case _ =>
+ if (yts.exists { case (y, _) => y == x })
+ Fun(xopt, yts, tretopt, e1)
+ else Fun(xopt, yts, tretopt, subst(e1))
+ }
+ case Call(e0, es) => Call(subst(e0), es.map(subst))
+ case Obj(fields) => Obj(fields.map { case (f, e1) => (f, subst(e1)) })
+ case GetField(e1, f) => GetField(subst(e1), f)
+ }
+ subst(e)
+ }
+
+ /* Type Inference */
+ type TEnv = Map[String, Typ]
+ def lookup[A](env: Map[String, A], x: String): A = env(x)
+ def extend[A](env: Map[String, A], x: String, a: A): Map[String, A] = {
+ env + (x -> a)
+ }
+
+ def hastype(env: TEnv, e: Expr): Typ = {
+ def err[T](tgot: Typ, e1: Expr): T = throw StaticTypeError(tgot, e1, e)
+
+ e match {
+ case Print(e1) => hastype(env, e1); TUndefined
+ case N(_) => TNumber
+ case B(_) => TBool
+ case Undefined => TUndefined
+ case S(_) => TString
+ case Var(x) => lookup(env, x)
+ case Unary(Neg, e1) =>
+ hastype(env, e1) match {
+ case TNumber => TNumber
+ case tgot => err(tgot, e1)
+ }
+ case Unary(Not, e1) =>
+ hastype(env, e1) match {
+ case TBool => TBool
+ case tgot => err(tgot, e1)
+ }
+ case Binary(Plus, e1, e2) =>
+ (hastype(env, e1), hastype(env, e2)) match {
+ case (TNumber, TNumber) => TNumber
+ case (TString, TString) => TString
+ case (tgot1, tgot2) => err(tgot1, e1)
+ }
+ case Binary(Minus | Times | Div, e1, e2) =>
+ (hastype(env, e1), hastype(env, e2)) match {
+ case (TNumber, TNumber) => TNumber
+ case (tgot1, tgot2) => err(tgot1, e1)
+ }
+ case Binary(Eq | Ne, e1, e2) =>
+ (hastype(env, e1), hastype(env, e2)) match {
+ case (TNumber, TNumber) => TBool
+ case (TString, TString) => TBool
+ case (tgot1, tgot2) => err(tgot1, e1)
+ }
+ case Binary(Lt | Le | Gt | Ge, e1, e2) =>
+ (hastype(env, e1), hastype(env, e2)) match {
+ case (TNumber, TNumber) => TBool
+ case (TString, TString) => TBool
+ case (tgot1, tgot2) => err(tgot1, e1)
+ }
+ case Binary(And | Or, e1, e2) =>
+ (hastype(env, e1), hastype(env, e2)) match {
+ case (TBool, TBool) => TBool
+ case (tgot1, tgot2) => err(tgot1, e1)
+ }
+ case Binary(Seq, e1, e2) =>
+ hastype(env, e1)
+ hastype(env, e2)
+ case If(e1, e2, e3) =>
+ hastype(env, e1) match {
+ case TBool =>
+ val t2 = hastype(env, e2)
+ val t3 = hastype(env, e3)
+ if (t2 == t3) t2
+ else err(t2, e2)
+ case tgot => err(tgot, e1)
+ }
+ case ConstDecl(x, e1, e2) =>
+ val t1 = hastype(env, e1)
+ val env1 = extend(env, x, t1)
+ hastype(env1, e2)
+ case Obj(fields) =>
+ TObj(fields.map { case (f, e1) => (f, hastype(env, e1)) })
+ case GetField(e1, f) =>
+ hastype(env, e1) match {
+ case TObj(fieldTypes) =>
+ fieldTypes.getOrElse(f, err(TObj(fieldTypes), e1))
+ case tgot => err(tgot, e1)
+ }
+ case Fun(xopt, yts, tretopt, e1) => {
+ val env1 = (xopt, tretopt) match {
+ case (Some(fname), Some(tret)) =>
+ extend(
+ env,
+ fname,
+ TFun(yts.map { case (y, typ) => (y, typ) }, tret)
+ )
+ case _ => env
+ }
+ val env2 = yts.foldLeft(env1) { case (accEnv, (y, ty)) =>
+ extend(accEnv, y, ty)
+ }
+ val t1 = hastype(env2, e1)
+ tretopt match {
+ case Some(tret) =>
+ if (t1 == tret) TFun(yts.map { case (y, typ) => (y, typ) }, tret)
+ else err(t1, e1)
+ case None => TFun(yts.map { case (y, typ) => (y, typ) }, t1)
+ }
+ }
+ case Call(e0, args) =>
+ hastype(env, e0) match {
+ case TFun(params, tret) if (params.length == args.length) =>
+ (params zip args).foreach { case ((_, paramType), argExpr) =>
+ val argType = hastype(env, argExpr)
+ if (argType != paramType) err(argType, argExpr)
+ }
+ tret
+ case tgot => err(tgot, e0)
+ }
+
+ }
+ }
+
+ /* A small-step transition. */
+ def step(e: Expr): Expr = {
+ require(!isValue(e), s"step: e ${e} to step is a value")
+
+ e match {
+ case Print(v1) if isValue(v1) => println(pretty(v1)); Undefined
+ case Unary(Neg, N(n1)) => N(-n1)
+ case Unary(Not, B(b1)) => B(!b1)
+ case Binary(Seq, v1, e2) if isValue(v1) => e2
+ case Binary(Plus, S(s1), S(s2)) => S(s1 + s2)
+ case Binary(Plus, N(n1), N(n2)) => N(n1 + n2)
+ case Binary(bop @ (Lt | Le | Gt | Ge), v1, v2)
+ if isValue(v1) && isValue(v2) =>
+ B(doInequality(bop, v1, v2))
+ case Binary(Eq, v1, v2) if isValue(v1) && isValue(v2) => B(v1 == v2)
+ case Binary(Ne, v1, v2) if isValue(v1) && isValue(v2) => B(v1 != v2)
+ case Binary(And, B(b1), e2) => if (b1) e2 else B(false)
+ case Binary(Or, B(b1), e2) => if (b1) B(true) else e2
+ case ConstDecl(x, v1, e2) if isValue(v1) => substitute(v1, x, e2)
+ case Call(v1, args) if isValue(v1) && (args forall isValue) =>
+ v1 match {
+ case Fun(p, params, _, e1) => {
+ val e1p = (params, args).zipped.foldRight(e1) { case ((p, a), e1) =>
+ substitute(a, p._1, e1)
+ }
+ p match {
+ case None => e1p
+ case Some(x1) => substitute(v1, x1, e1p)
+ }
+ }
+ case _ => throw new StuckError(e)
+ }
+ case Binary(Minus, N(n1), N(n2)) => N(n1 - n2)
+ case Binary(Times, N(n1), N(n2)) => N(n1 * n2)
+ case Binary(Div, N(n1), N(n2)) => N(n1 / n2)
+ case If(B(true), e1, e2) => e1
+ case If(B(false), e1, e2) => e2
+ case Print(e1) => Print(step(e1))
+ case Unary(uop, e1) => Unary(uop, step(e1))
+ case Binary(bop, v1, e2) if isValue(v1) => Binary(bop, v1, step(e2))
+ case Binary(bop, e1, e2) => Binary(bop, step(e1), e2)
+ case If(e1, e2, e3) => If(step(e1), e2, e3)
+ case ConstDecl(x, e1, e2) => ConstDecl(x, step(e1), e2)
+ case Call(Fun(name, params, t, e1), args) if args.forall(isValue) => {
+ val x = name match {
+ case Some(y) => substitute(Fun(name, params, t, e1), y, e1)
+ case None => e1
+ }
+ params.zip(args).foldLeft(x) { (e2, t2) =>
+ substitute(t2._2, t2._1._1, e2)
+ }
+ }
+ case Call(Fun(name, params, t, e1), args) => {
+ Call(
+ Fun(name, params, t, e1),
+ mapFirst((arg: Expr) => {
+ if (isValue(arg)) None else Some(step(arg))
+ })(args)
+ )
+ }
+ case Call(func, args) => Call(step(func), args)
+ case GetField(obj, field) =>
+ obj match {
+ case Obj(f) =>
+ f.get(field) match {
+ case Some(x) => x
+ case None => throw new StuckError(e)
+ }
+ case e1 => GetField(step(e1), field)
+ }
+
+ /* Everything else is a stuck error. Should not happen if e is well-typed. */
+ case _ => throw StuckError(e)
+ }
+ }
+
+ /* External Interfaces */
+
+ /** Interface to run your type checker. */
+ def inferType(e: Expr): Typ = {
+ val t = hastype(Map.empty, e)
+ println(s"## ${e} : ${pretty(t)}")
+ t
+ }
+
+ /** Interface to run your small-step interpreter and print out the steps of
+ * evaluation if debugging.
+ */
+ def iterateStep(e: Expr): Expr = {
+ require(
+ closed(e),
+ "input Expr to iterateStep is not closed: free variables: %s".format(
+ freeVars(e)
+ )
+ )
+ def loop(e: Expr, n: Int): Expr = {
+ if (Some(n) == maxSteps) throw TerminationError(e, n)
+ if (isValue(e)) e
+ else {
+ println("## step %4d: %s".format(n, e))
+ loop(step(e), n + 1)
+ }
+ }
+ val v = loop(e, 0)
+ println(s"## value: %s".format(v))
+ v
+ }
+
+ /** Interface to type check from a string. This is convenient for unit
+ * testing.
+ */
+ def inferType(s: String): Typ = inferType(Parser.parse(s))
+
+ /** Interface to take a small-step from a string. This is convenient for unit
+ * testing.
+ */
+ def oneStep(s: String): Expr = step(Parser.parse(s))
+
+ /** Interface to run your small-step interpreter from a string. This is
+ * convenient for unit testing.
+ */
+ def iterateStep(s: String): Expr = iterateStep(Parser.parse(s))
+
+ // Interface for main
+
+ // this.debug = true // uncomment this if you want to print debugging information
+ this.maxSteps = Some(
+ 1000
+ ) // comment this out or set to None to not bound the number of steps.
+ this.keepGoing =
+ true // comment this out if you want to stop at first exception when processing a file
+
+ def processFile(file: java.io.File): Unit = {
+ if (debug) {
+ println("# ============================================================")
+ println("# File: " + file.getName)
+ println("# Parsing ...")
+ }
+
+ val exprin =
+ handle(None: Option[Expr]) {
+ Some {
+ Parser.parseFile(file)
+ }
+ } getOrElse {
+ return
+ }
+
+ val expr = exprin
+
+ if (debug) {
+ println("# ------------------------------------------------------------")
+ println("# Type checking %s ...".format(expr))
+ }
+
+ val welltyped = handle(false) {
+ val t = inferType(expr)
+ true
+ }
+ if (!welltyped) return
+
+ if (debug) {
+ println("# ------------------------------------------------------------")
+ println("# Stepping ...".format(expr))
+ }
+
+ handle(()) {
+ val v = iterateStep(expr)
+ println(pretty(v))
+ }
+ }
+
+}
diff --git a/lab4/src/main/scala/jsy/lab4/Lab4.worksheet.sc b/lab4/src/main/scala/jsy/lab4/Lab4.worksheet.sc
new file mode 100644
index 0000000..3e516a6
--- /dev/null
+++ b/lab4/src/main/scala/jsy/lab4/Lab4.worksheet.sc
@@ -0,0 +1,39 @@
+/*
+ * CSCI 3155: Lab 4 Worksheet
+ *
+ * This worksheet demonstrates how you could experiment
+ * interactively with your implementations in Lab4.scala.
+ */
+
+// Imports the parse function from jsy.lab3.Parser
+import jsy.lab4.Parser.{parse, parseFile}
+
+// Imports the ast nodes
+import jsy.lab4.ast._
+
+// Imports all of the functions form jsy.student.Lab4 (your implementations in Lab4.scala)
+import jsy.lab4.Lab4._
+
+// Parse functions with possibly multiple parameters and type annotations.
+parse("function fst(x: number, y: number): number { return x }")
+parse("function (x: number) { return x }")
+parse("function (f: (y: number) => number, x: number) { return f(x) }")
+
+// Parse objects
+parse("{ f: 0, g: true }")
+parse("x.f")
+
+// Run your type checker
+// - inferType calls your typeof
+//inferType("1 + 2")
+
+// Run your small-step interpreter
+// - iterateStep calls your iterate and your step
+//iterateStep("1 + 2")
+
+// Parse the JavaScripty expression in your worksheet
+val worksheetJsy = parseFile("src/main/scala/jsy/lab4/Lab4.worksheet.ts")
+
+// Interpret the JavaScripty expression in your worksheet
+//inferType(worksheetJsy)
+//iterateStep(worksheetJsy) \ No newline at end of file
diff --git a/lab4/src/main/scala/jsy/lab4/Lab4.worksheet.ts b/lab4/src/main/scala/jsy/lab4/Lab4.worksheet.ts
new file mode 100644
index 0000000..0f212c3
--- /dev/null
+++ b/lab4/src/main/scala/jsy/lab4/Lab4.worksheet.ts
@@ -0,0 +1,35 @@
+/*
+ * CSCI 3155: Lab 4 TypeScript Worksheet
+ *
+ * This worksheet is a place to experiment with TypeScript expressions.
+ */
+
+// The new language features in Lab 4 are types, multi-parameter functions,
+// and objects.
+
+const id_number = ((x: number) => x);
+
+const plus = ((x: number) => (y: number) => x + y);
+const plus_uncurried = ((x: number, y: number) => x + y);
+const plus_pair = ((pair: { x: number; y: number }) => pair.x + pair.y);
+
+const fst = ((x: number, y: number) => x);
+const fst_alt = function (x: number, y: number): number { return x; };
+const fst_pair = ((pair: { x: number; y: number }) => pair.x);
+
+const inc = plus(1);
+
+const do_numfun = function (f: (y: number) => number, x: number) { return f(x); };
+
+console.log(id_number(3));
+
+console.log(plus(3)(4));
+console.log(plus_uncurried(3, 4));
+console.log(plus_pair({ x: 3, y: 4 }))
+console.log(plus_pair({ x: 1 + 2, y: 3 + 4 }))
+
+console.log(fst(5, 6));
+console.log(fst_alt(5, 6));
+console.log(fst_pair({ x: 5, y: 6 }));
+
+console.log(do_numfun(inc, 2)); \ No newline at end of file
diff --git a/lab4/src/main/scala/jsy/lab4/Parser.scala b/lab4/src/main/scala/jsy/lab4/Parser.scala
new file mode 100644
index 0000000..5db3b1f
--- /dev/null
+++ b/lab4/src/main/scala/jsy/lab4/Parser.scala
@@ -0,0 +1,437 @@
+/** */
+package jsy.lab4
+
+import jsy.lab4.ast._
+import scala.util.parsing.combinator._
+import scala.util.parsing.input.CharSequenceReader
+import scala.util.parsing.combinator.syntactical.StandardTokenParsers
+import scala.util.parsing.input.{StreamReader, Reader}
+import java.io.{InputStreamReader, FileInputStream}
+import java.io.InputStream
+import java.io.File
+import scala.util.parsing.input.Position
+import scala.util.parsing.input.NoPosition
+import scala.collection.immutable.TreeMap
+
+trait JSTokens extends token.StdTokens {
+ case class FloatLiteral(chars: String) extends Token {
+ override def toString = chars
+ }
+}
+
+class Lexer extends lexical.StdLexical with JSTokens {
+ override def token: this.Parser[Token] =
+ decimal ~ opt(exponent) ^^ { case dec ~ exp =>
+ FloatLiteral(List(Some(dec), exp).flatten.mkString)
+ } |
+ super.token
+
+ def decimal: this.Parser[String] =
+ rep1(digit) ~ opt('.' ~ rep(digit)) ^^ { case ws ~ fs =>
+ List(Some(ws), fs map { mkList }).flatten.flatten.mkString
+ }
+
+ def exponent: this.Parser[String] =
+ (accept('e') | accept('E')) ~ opt(accept('+') | accept('-')) ~ rep1(
+ digit
+ ) ^^ { case exp ~ sign ~ digits =>
+ List(
+ Some(List(exp)),
+ sign map { List(_) },
+ Some(digits)
+ ).flatten.flatten.mkString
+ }
+}
+
+trait TokenParser extends syntactical.StdTokenParsers {
+ type Tokens = JSTokens
+ val lexical = new Lexer
+
+ import lexical.FloatLiteral
+
+ def floatLit: this.Parser[String] =
+ elem("float", _.isInstanceOf[FloatLiteral]) ^^ (_.chars)
+}
+
+object Parser extends TokenParser {
+ /* Lexer Set Up */
+ lexical.reserved ++= List(
+ "jsy",
+ "undefined",
+ "true",
+ "false",
+ "print",
+ "console",
+ "log",
+ "const",
+ "function",
+ "return",
+ "number",
+ "bool",
+ "string",
+ "Undefined",
+ "null",
+ "Null",
+ "interface",
+ "var",
+ "name",
+ "ref",
+ "RegExp"
+ )
+ lexical.delimiters ++= List(
+ "-",
+ "!",
+ ";",
+ ",",
+ "+",
+ "*",
+ "/",
+ "=",
+ "===",
+ "!==",
+ "<",
+ "<=",
+ ">",
+ ">=",
+ "&&",
+ "||",
+ "(",
+ ")",
+ ".",
+ "{",
+ "}",
+ "?",
+ ":",
+ "=>"
+ )
+
+ /* Helpers */
+ def seqExpr(e1: Expr, e2: Expr): Expr = Binary(Seq, e1, e2)
+
+ /* EBNF
+ *
+ * prog ::= {stmt}
+ * stmt ::= block | decl | ; | expr
+ * block ::= '{' prog '}'
+ * decl ::= const x = expr
+ * expr ::= seq
+ * seq ::= cond{,cond}
+ * noseq ::= arrow
+ * arrow ::= x => noseq | cond
+ * cond ::= binary [? cond : cond]
+ * binary ::= unary{bop(_)unary}
+ * unary ::= uop unary | call
+ * call ::= term{(expr)}
+ * term ::= x | n | b | undefined | jsy.print(expr) | (expr)
+ */
+
+ sealed abstract class PStmt
+ case class ExprPStmt(e: Expr) extends PStmt
+ case class DeclPStmt(d: Expr => Expr) extends PStmt
+ case object EmpPStmt extends PStmt
+
+ def prog: this.Parser[Expr] =
+ stmts ^^ (s => s(None))
+
+ def stmts: this.Parser[Option[Expr] => Expr] =
+ rep(stmt) ^^ { (stmts: List[PStmt]) => (body: Option[Expr]) =>
+ (stmts foldRight body) {
+ case (EmpPStmt, eopt) => eopt
+ case (ExprPStmt(e), None) => Some(e)
+ case (ExprPStmt(e1), Some(e2)) => Some(seqExpr(e1, e2))
+ case (DeclPStmt(d), None) => Some(d(Undefined))
+ case (DeclPStmt(d), Some(e)) => Some(d(e))
+ } match {
+ case None => Undefined
+ case Some(e) => e
+ }
+ }
+
+ def stmt: this.Parser[PStmt] =
+ block ^^ ExprPStmt |
+ decl ^^ DeclPStmt |
+ expr ^^ ExprPStmt |
+ empty_stmt
+
+ def empty_stmt: this.Parser[PStmt] =
+ ";" ^^ (_ => EmpPStmt)
+
+ def block: this.Parser[Expr] =
+ "{" ~> prog <~ "}"
+
+ def decl: this.Parser[Expr => Expr] =
+ ("const" ~> ident) ~ withpos("=" ~> expr) ^^ {
+ case x ~ ((pos,e1)) => ((e2: Expr) => ConstDecl(x, e1, e2) setPos pos)
+ }
+
+ def expr: this.Parser[Expr] =
+ seq
+
+ def seq: this.Parser[Expr] =
+ noseq ~ withposrep("," ~> noseq) ^^ { case e0 ~ es =>
+ (es foldRight (None: Option[(Position, Expr)])) {
+ case ((posi, ei), None) => Some(posi, ei)
+ case ((posi, ei), Some((pos, e))) =>
+ Some(posi, seqExpr(ei, e) setPos pos)
+ } match {
+ case None => e0
+ case Some((pos, e)) => seqExpr(e0, e) setPos pos
+ }
+ }
+
+ def noseq: this.Parser[Expr] =
+ cond
+
+ def cond: this.Parser[Expr] =
+ binary(0) ~ opt(withpos(("?" ~> noseq) ~ (":" ~> noseq))) ^^ {
+ case e1 ~ None => e1
+ case e1 ~ Some((pos, e2 ~ e3)) => If(e1, e2, e3) setPos pos
+ }
+
+ // def funblock: this.Parser[Expr] =
+ // ("{" ~> stmts ~ ret <~ rep(empty_stmt) <~ "}") ^^ { case stmts ~ ret =>
+ // stmts(Some(ret))
+ // }
+
+ // def ret: this.Parser[Expr] =
+ // "return" ~> expr
+
+ // def cond: this.Parser[Expr] =
+ // binary(0) ~ opt(withpos(("?" ~> noseq) ~ (":" ~> noseq))) ^^ {
+ // case e1 ~ None => e1
+ // case e1 ~ Some((pos, e2 ~ e3)) => If(e1, e2, e3) setPos pos
+ // }
+
+ val binaryOperators: Vector[List[(String, (Expr, Expr) => Expr)]] = {
+ def createBinaryFunction(op: Bop): (Expr, Expr) => Expr = {
+ Binary(op, _, _)
+ }
+ Vector() ++ List(
+ List("||" -> createBinaryFunction(Or)),
+ List("&&" -> createBinaryFunction(And)),
+ List(
+ "===" -> createBinaryFunction(Eq),
+ "!==" -> createBinaryFunction(Ne)
+ ),
+ List(
+ "<" -> createBinaryFunction(Lt),
+ "<=" -> createBinaryFunction(Le),
+ ">" -> createBinaryFunction(Gt),
+ ">=" -> createBinaryFunction(Ge)
+ ),
+ List(
+ "+" -> createBinaryFunction(Plus),
+ "-" -> createBinaryFunction(Minus)
+ ),
+ List("*" -> createBinaryFunction(Times), "/" -> createBinaryFunction(Div))
+ )
+ }
+
+ def binary(level: Int): this.Parser[Expr] =
+ if (level >= binaryOperators.length)
+ unary
+ else
+ binary(level + 1) * bop(level)
+
+ def bop(level: Int): this.Parser[(Expr, Expr) => Expr] = {
+ def doBop(
+ opf: (String, (Expr, Expr) => Expr)
+ ): this.Parser[(Expr, Expr) => Expr] = {
+ val (op, f) = opf
+ withpos(op) ^^ { case (pos, _) => ((e1, e2) => f(e1, e2) setPos pos) }
+ }
+ val bopf0 :: bopfrest = binaryOperators(level)
+ (bopfrest.foldLeft(doBop(bopf0)))((acc, bopf) => acc | doBop(bopf))
+ }
+
+ def unary: this.Parser[Expr] =
+ positioned(uop ~ unary ^^ { case op ~ e => op(e) }) |
+ call
+
+ def uop: this.Parser[Expr => Expr] =
+ "-" ^^ (_ => (e: Expr) => Unary(Neg, e)) |
+ "!" ^^ (_ => (e: Expr) => Unary(Not, e))
+
+ def call: this.Parser[Expr] =
+ term ~ rep(callop | derefop) ^^ { case e0 ~ callderefs =>
+ (callderefs.foldLeft(e0)) { case (acc, mk) => mk(acc) }
+ }
+
+ def callop: this.Parser[Expr => Expr] =
+ withpos("(" ~> repsep(noseq, ",") <~ ")") ^^ {
+ case (pos, args) => (e0 => Call(e0, args) setPos pos)
+ }
+
+ def derefop: this.Parser[Expr => Expr] =
+ withpos("." ~> ident) ^^ {
+ case (pos, f) => (e0 => GetField(e0, f) setPos pos)
+ }
+
+ def term: this.Parser[Expr] =
+ positioned(
+ ident ^^ (s => Var(s)) |
+ floatLit ^^ (s => N(s.toDouble)) |
+ stringLit ^^ (s => S(s)) |
+ "true" ^^ (_ => B(true)) |
+ "false" ^^ (_ => B(false)) |
+ "undefined" ^^ (_ => Undefined) |
+ ("jsy" ~ "." ~ "print") ~> "(" ~> expr <~ ")" ^^ (e => Print(e)) |
+ ("console" ~ "." ~ "log") ~> "(" ~> expr <~ ")" ^^ (e => Print(e)) |
+ function |
+ record(",", Obj, noseq)
+ ) |
+ "(" ~> expr <~ ")" |
+ "{" ~> "{" ~> prog <~ "}" <~ "}" |
+ failure("atomic expression expected")
+
+ def function: this.Parser[Expr] =
+ ("function" ~> opt(ident)) ~ ("(" ~> repsep(
+ colonpair(ty),
+ ","
+ ) <~ ")") ~ opt(":" ~> ty) ~ ("{" ~> stmts ~ ret <~ rep(
+ empty_stmt
+ ) <~ "}") ^^ { case f ~ params ~ retty ~ (stmts ~ ret) =>
+ val body = stmts(Some(ret))
+ Fun(f, params, retty, body)
+ } |
+ ("(" ~> repsep(colonpair(ty), ",") <~ ")") ~ (withpos(
+ "=>" ~> noseq
+ )) ^^ { case params ~ ((pos, body)) =>
+ Fun(None, params, None, body) setPos pos
+ }
+
+ def ret: this.Parser[Expr] =
+ "return" ~> expr
+
+ def record[A](
+ sep: String,
+ node: Map[String, A] => A,
+ q: => this.Parser[A]
+ ): this.Parser[A] = {
+ lazy val p = q
+ "{" ~> repsep(colonpair(p), sep) <~ (opt(",") ~ "}") ^^ { flist =>
+ val fmap = flist.foldLeft(TreeMap.empty: TreeMap[String, A]) {
+ case (fmap, (f, e)) => fmap + (f -> e)
+ }
+ node(fmap)
+ }
+ }
+
+ def colonpair[A](q: => this.Parser[A]): this.Parser[(String, A)] = {
+ lazy val p = q
+ ident ~ (":" ~> p) ^^ { case f ~ e => (f, e) }
+ }
+
+ def ty: this.Parser[Typ] =
+ "number" ^^ (_ => TNumber) |
+ "bool" ^^ (_ => TBool) |
+ "string" ^^ (_ => TString) |
+ "Undefined" ^^ (_ => TUndefined) |
+ record(";", TObj, ty) |
+ tyfun |
+ failure("type expected")
+
+ def tyfun: this.Parser[Typ] =
+ ("(" ~> repsep(colonpair(ty), ",") <~ ")") ~ ("=>" ~> ty) ^^ {
+ case params ~ t2 => TFun(params, t2)
+ }
+
+ def withpos[T](q: => this.Parser[T]): this.Parser[(Position, T)] =
+ this.Parser { in =>
+ q(in) match {
+ case Success(t, in1) => Success((in.pos, t), in1)
+ case ns: NoSuccess => ns
+ }
+ }
+
+ def withposrep[T](q: => this.Parser[T]): this.Parser[List[(Position, T)]] =
+ rep(withpos(q))
+
+ def withposrep1[T](q: => this.Parser[T]): this.Parser[List[(Position, T)]] =
+ rep1(withpos(q))
+
+ private var parseSource: String = "<source>"
+
+ def formatErrorMessage(
+ pos: Position,
+ kind: String,
+ msg: String,
+ longString: Boolean = false
+ ): String =
+ if (pos != NoPosition)
+ if (longString)
+ "%s\n%s:%s:%s: %s\n%s".format(
+ kind,
+ parseSource,
+ pos.line,
+ pos.column,
+ msg,
+ pos.longString
+ )
+ else
+ "%s\n%s:%s:%s: %s".format(kind, parseSource, pos.line, pos.column, msg)
+ else
+ "%s\n%s: %s".format(kind, parseSource, msg)
+
+ class SyntaxError(msg: String, next: Input) extends Exception {
+ override def toString =
+ formatErrorMessage(next.pos, "SyntaxError", msg, true)
+ }
+
+ def parseTokens(tokens: lexical.Scanner): Expr = {
+ phrase(prog)(tokens) match {
+ case Success(e, _) => e
+ case NoSuccess(msg, next) => throw new SyntaxError(msg, next)
+ case Error(msg, next) => throw new SyntaxError(msg, next)
+ case Failure(msg, next) => throw new SyntaxError(msg, next)
+ }
+ }
+
+ def parseTypTokens(tokens: lexical.Scanner): Typ = {
+ phrase(ty)(tokens) match {
+ case Success(t, _) => t
+ case NoSuccess(msg, next) => throw new SyntaxError(msg, next)
+ case Error(msg, next) => throw new SyntaxError(msg, next)
+ case Failure(msg, next) => throw new SyntaxError(msg, next)
+ }
+ }
+
+ /** * External Interface **
+ */
+
+ def formatErrorMessage(e: Expr, kind: String, msg: String): String =
+ formatErrorMessage(e.pos, kind, msg)
+
+ def parse(s: String): Expr = {
+ parseTokens(new lexical.Scanner(s))
+ }
+
+ def parseTyp(s: String): Typ = {
+ parseTypTokens(new lexical.Scanner(s))
+ }
+
+ def parse(in: InputStream): Expr = {
+ val reader = StreamReader(new InputStreamReader(in))
+ parseTokens(new lexical.Scanner(reader))
+ }
+
+ def parseFile(filename: String): Expr = {
+ parseSource = filename
+ parse(new FileInputStream(filename))
+ }
+
+ def parseFile(file: File): Expr = {
+ parseSource = file.getName
+ parse(new FileInputStream(file))
+ }
+
+ implicit class StringExpr(s: String) {
+ val e = parse(s)
+ def a: Expr = e
+ }
+
+ implicit class StringTyp(s: String) {
+ val typ = parseTyp(s)
+ def t: Typ = typ
+ }
+}
diff --git a/lab4/src/main/scala/jsy/lab4/ast.scala b/lab4/src/main/scala/jsy/lab4/ast.scala
new file mode 100644
index 0000000..c4c3f83
--- /dev/null
+++ b/lab4/src/main/scala/jsy/lab4/ast.scala
@@ -0,0 +1,240 @@
+package jsy.lab4
+
+import scala.util.parsing.input.Positional
+
+/** @author
+ * Bor-Yuh Evan Chang
+ */
+object ast {
+ sealed trait Expr extends Positional // e ::=
+
+ /* Literals */
+ case class N(n: Double) extends Expr // e ::= n
+ case class B(b: Boolean) extends Expr // e ::= b
+ case class S(str: String) extends Expr // e ::= str
+ case object Undefined extends Expr // e ::= undefined
+
+ /* Unary and Binary Expressions */
+ case class Unary(uop: Uop, e1: Expr) extends Expr // e ::= uop e1
+ case class Binary(bop: Bop, e1: Expr, e2: Expr) extends Expr // e ::= e1 bop e2
+
+ sealed trait Uop
+ case object Neg extends Uop /* -e1 */
+ case object Not extends Uop /* !e1 */
+
+ sealed trait Bop
+ /* Numbers */
+ case object Plus extends Bop /* e1 + e2 */
+ case object Minus extends Bop /* e1 - e2 */
+ case object Times extends Bop /* e1 * e2 */
+ case object Div extends Bop /* e1 / e2 */
+ case object Eq extends Bop /* e1 === e2 */
+ case object Ne extends Bop /* e1 !=== e2 */
+ case object Lt extends Bop /* e1 < e2 */
+ case object Le extends Bop /* e1 <= e2 */
+ case object Gt extends Bop /* e1 > e2 */
+ case object Ge extends Bop /* e1 >= e2 */
+ /* Booleans */
+ case object And extends Bop /* e1 && e2 */
+ case object Or extends Bop /* e1 || e2 */
+
+ /* Intraprocedural Control */
+ case class If(e1: Expr, e2: Expr, e3: Expr) extends Expr // e ::= e1 ? e2 : e3
+
+ /* Side-Effects */
+ case class Print(e1: Expr) extends Expr // e ::= console.log(e1)
+ case object Seq extends Bop // bop ::= ,
+
+ /* Variables */
+ case class Var(x: String) extends Expr // e ::= x
+ case class ConstDecl(x: String, e1: Expr, e2: Expr) extends Expr // e ::= const x = e1; e2
+
+ /* Functions */
+ case class Fun(
+ xopt: Option[String],
+ yts: List[(String, Typ)],
+ tretopt: Option[Typ],
+ e1: Expr
+ ) extends Expr // e::= xopt(yts)tretopt => e1
+ case class Call(e0: Expr, es: List[Expr]) extends Expr // e ::= e1([args])
+
+ /* Objects */
+ case class Obj(fes: Map[String, Expr]) extends Expr
+ case class GetField(e1: Expr, f: String) extends Expr
+
+ /* Types */
+ sealed trait Typ
+ case object TNumber extends Typ
+ case object TBool extends Typ
+ case object TString extends Typ
+ case object TUndefined extends Typ
+ case class TFun(params: List[(String, Typ)], tret: Typ) extends Typ {
+ override def equals(other: Any) = other.isInstanceOf[TFun] && {
+ other match {
+ case TFun(oparams, otret)
+ if otret == tret && oparams.length == params.length =>
+ (oparams zip params).forall { case ((_, omt), (_, mt)) => omt == mt }
+ case _ => false
+ }
+ }
+ }
+ case class TObj(fts: Map[String, Typ]) extends Typ
+
+ /* Define values. */
+ def isValue(e: Expr): Boolean = e match {
+ case N(_) | B(_) | Undefined | S(_) | Fun(_, _, _, _) => true
+ case Obj(fields) if (fields forall { case (_, ei) => isValue(ei) }) => true
+ case _ => false
+ }
+
+ /*
+ * Pretty-print values.
+ *
+ * We do not override the toString method so that the abstract syntax can be printed
+ * as is.
+ */
+ def pretty(v: Expr): String = {
+ require(isValue(v))
+ (v: @unchecked) match {
+ case N(n) => n.toString
+ case B(b) => b.toString
+ case Undefined => "undefined"
+ case S(s) => s
+ case Fun(p, _, _, _) =>
+ "[Fun%s]".format(p match {
+ case None => ""
+ case Some(s) => ": " + s
+ })
+ case Obj(fields) =>
+ val pretty_fields =
+ fields map {
+ case (f, S(s)) => f + ": '" + s + "'"
+ case (f, v) => f + ": " + pretty(v)
+ } reduceRightOption { (s, acc) =>
+ s + ",\n " + acc
+ }
+ "{ %s }".format(pretty_fields.getOrElse(""))
+ }
+ }
+
+ /*
+ * Pretty-print types.
+ *
+ * We do not override the toString method so that the abstract syntax can be printed
+ * as is.
+ */
+ def pretty(t: Typ): String = t match {
+ case TNumber => "number"
+ case TBool => "bool"
+ case TString => "string"
+ case TUndefined => "Undefined"
+ case TFun(params, tret) => {
+ val pretty_params =
+ params map { case (x, mt) =>
+ "%s: %s".format(x, pretty(mt))
+ } reduceRightOption { (s, acc) =>
+ s + ", " + acc
+ }
+ "(%s) => %s".format(pretty_params.getOrElse(""), pretty(tret))
+ }
+ case TObj(tfields) =>
+ val pretty_fields: Option[String] =
+ tfields map { case (f, t) =>
+ "%s: %s".format(f, pretty(t))
+ } reduceRightOption { (s, acc) =>
+ s + "; " + acc
+ }
+ "{ %s }".format(pretty_fields.getOrElse(""))
+ }
+
+
+ /* Get the free variables of e. */
+ def freeVarsVar(e: Expr): Set[Var] = {
+ def fv(e: Expr): Set[Var] = e match {
+ case vr @ Var(x) => Set(vr)
+ case ConstDecl(x, e1, e2) => fv(e1) | (fv(e2) - Var(x))
+ case Fun(p, params, _, e1) => {
+ val boundvars = (params map { case (x, _) => Var(x) }) ++ (p map Var)
+ fv(e1) -- boundvars
+ }
+ case N(_) | B(_) | Undefined | S(_) => Set.empty
+ case Unary(_, e1) => fv(e1)
+ case Binary(_, e1, e2) => fv(e1) | fv(e2)
+ case If(e1, e2, e3) => fv(e1) | fv(e2) | fv(e3)
+ case Call(e1, args) =>
+ fv(e1) | args.foldLeft(Set.empty: Set[Var]) {
+ ((acc: Set[Var], ei) => acc | fv(ei))
+ }
+ case Print(e1) => fv(e1)
+ case Obj(fields) =>
+ fields.foldLeft(Set.empty: Set[Var])({ case (acc, (_, ei)) =>
+ acc | fv(ei)
+ })
+ case GetField(e1, _) => fv(e1)
+ }
+ fv(e)
+ }
+ def freeVars(e: Expr): Set[String] = freeVarsVar(e) map { case Var(x) => x }
+
+ /* Check closed expressions. */
+ def closed(e: Expr): Boolean = freeVarsVar(e).isEmpty
+ def checkClosed(e: Expr): Unit = {
+ freeVarsVar(e).headOption.foreach { x => throw new UnboundVariableError(x) }
+ }
+
+ /*
+ * Unbound Variable Error exception. Throw this exception to signal an unbound variable.
+ */
+ case class UnboundVariableError(x: Var) extends Exception {
+ override def toString =
+ Parser.formatErrorMessage(
+ x.pos,
+ "UnboundVariableError",
+ "unbound variable %s".format(x.x)
+ )
+ }
+
+ /*
+ * Static Type Error exception. Throw this exception to signal a static
+ * type error.
+ *
+ * throw StaticTypeError(tbad, esub, e)
+ *
+ */
+ case class StaticTypeError(tbad: Typ, esub: Expr, e: Expr) extends Exception {
+ override def toString =
+ Parser.formatErrorMessage(
+ esub.pos,
+ "StaticTypeError",
+ "invalid type %s for sub-expression %s in %s".format(
+ pretty(tbad),
+ esub,
+ e
+ )
+ )
+ }
+
+ /*
+ * Stuck Error exception. Throw this exception to signal getting
+ * stuck in evaluation. This exception should not get raised if
+ * evaluating a well-typed expression.
+ *
+ * throw StuckError(e)
+ *
+ */
+ case class StuckError(e: Expr) extends Exception {
+ override def toString =
+ Parser.formatErrorMessage(e.pos, "StuckError", "in evaluating " + e)
+ }
+
+ /*
+ * Termination Error exception. Throw this exception to signal exceeding maximum number of allowed steps.
+ */
+ case class TerminationError(e: Expr, n: Int) extends Exception {
+ override def toString = Parser.formatErrorMessage(
+ e.pos,
+ "TerminationError",
+ s"exceeded ${n} steps in evaluating ${e}"
+ )
+ }
+}
diff --git a/lab4/src/main/scala/jsy/util/JsyApplication.scala b/lab4/src/main/scala/jsy/util/JsyApplication.scala
new file mode 100644
index 0000000..46b658d
--- /dev/null
+++ b/lab4/src/main/scala/jsy/util/JsyApplication.scala
@@ -0,0 +1,191 @@
+package jsy.util
+
+import java.io.{ByteArrayOutputStream, File}
+import java.nio.file.Files
+
+trait JsyApplication {
+ var debug = false /* set to false to disable debugging output */
+ var keepGoing = true /* set to true to keep going after exceptions */
+ var maxSteps: Option[Int] = None /* set to a number to bound the number of execution steps */
+
+ /*** Implement this method to process a file. ***/
+ def processFile(file: File): Unit
+
+ var anonOption = ("input",
+ { case filename :: Nil => new File(filename) }: PartialFunction[List[String], File],
+ "A file containing a JavaScripty program or a directory with .jsy files.")
+
+ var flagOptions = List(
+ ("debug", options.SetBool(b => debug = b, Some(b => debug == b)), "debugging"),
+ ("keep-going", options.SetBool(b => keepGoing = b, Some(b => keepGoing == b)), "keep going after exceptions"),
+ ("bound-steps", options.SetInt(
+ { i => maxSteps = i },
+ Some({
+ case true => maxSteps map { i => ": %d".format(i) }
+ case false => if (maxSteps == None) Some("") else None
+ })),
+ "bound for maximum number of execution steps before aborting")
+ )
+
+ def handle[T](default: T)(e: => T): T =
+ if (!keepGoing) e
+ else try e catch {
+ case exn: Throwable => println(exn.toString); default
+ }
+
+ def testJsy(file: File)(k: (File, File, => (Boolean, String)) => Unit): Unit = {
+ val jsyext = """[.]jsy$""".r
+ val ans: File = new File(jsyext.replaceAllIn(file.getPath, ".ans"))
+ k(file, ans, {
+ if (!ans.exists()) {
+ (false, s"Expected output file ${ans} does not exist.")
+ }
+ else {
+ val outstream = new ByteArrayOutputStream()
+ Console.withOut(outstream)(handle(()){ processFile(file)})
+
+ val encoding = java.nio.charset.StandardCharsets.UTF_8
+ val ansstring = new String(Files.readAllBytes(ans.toPath), encoding)
+
+ outstream.flush()
+ val outstring = new String(outstream.toString(encoding.toString))
+ outstream.close()
+
+ (ansstring == outstring, s"Computed output does not match expected output.\nComputed:\n${outstring}\nExpected:\n${ansstring}")
+ }
+ })
+ }
+
+ def isJsy(file: File): Boolean = {
+ val jsyext = """[.]jsy$""".r
+ jsyext findFirstIn file.getName match {
+ case Some(_) => true
+ case None => false
+ }
+ }
+
+ def doFile(doit: File => Unit, file: File) = {
+ def loop(file: File): Unit = {
+ if (file.isFile) {
+ doit(file)
+ }
+ else if (file.isDirectory) {
+ file.listFiles filter { f => f.isDirectory || isJsy(f) } foreach loop
+ }
+ else {
+ throw new IllegalArgumentException("File %s does not exist.".format(file))
+ }
+ }
+ loop(file)
+ }
+
+ def test(fileordir: File)(k: (File, File, => (Boolean, String)) => Unit): Unit = {
+ doFile({ f => testJsy(f)(k) }, fileordir)
+ }
+
+ def main(args: Array[String]): Unit = {
+ val opts = new options.Options("jsy", flagOptions, anonOption)
+ val file: File = opts.process(args)
+ doFile(processFile, file)
+ }
+}
+
+object options {
+ sealed abstract class Spec
+ case class SetBool(setter: Boolean => Unit, default: Option[Boolean => Boolean]) extends Spec
+ case class SetInt(setter: Option[Int] => Unit, default: Option[Boolean => Option[String]]) extends Spec
+
+ class Options[T](program: String, specs: List[(String, Spec, String)], anon: (String, PartialFunction[List[String], T], String)) {
+ val opts: Map[String, List[String] => Option[List[String]]] =
+ specs.foldLeft[Map[String, List[String] => Option[List[String]]]](Map.empty)((acc, spec) => spec match {
+ case (name, SetBool(setter, _), _) =>
+ acc +
+ (("--" + name) -> { (t: List[String]) => setter(true); Some(t) }) +
+ (("--no-" + name) -> { (t: List[String]) => setter(false); Some(t) })
+ case (name, SetInt(setter, _), _) =>
+ acc +
+ (("--" + name) -> { (t: List[String]) => t match {
+ case arg :: t =>
+ val argp: Int = try arg.toInt catch { case _: Throwable => usageErr() }
+ setter(Some(argp)); Some(t)
+ case _ => usageErr()
+ } }) +
+ (("--no-" + name) -> { (t: List[String]) => setter(None); Some(t) })
+ })
+
+ val (anonName, anonDo, anonDesc) = anon
+
+ val nameWidth: Int = opts.foldLeft(anonName.length){ case (acc, (n, _)) => acc max (n.length + 5) }
+
+ def padRight(s: String, w: Int): String = {
+ val nspaces = (w - s.length) max 0
+ s + (" " * nspaces)
+ }
+
+ def optline(name: String, text: String): String = {
+ "%-2s".format("") + padRight(name, nameWidth) + " %s%n".format(text)
+ }
+
+ val descriptions: String = {
+ (specs foldRight "")((spec, acc) => spec match {
+ case (name, SetBool(_, default), desc) => {
+ def defaultStr(b: Boolean): String =
+ default map (f => if (f(b)) " (default)" else "") getOrElse("")
+ optline("--" + name, "turn on %s".format(desc) + defaultStr(true)) +
+ optline("--no-" + name, "turn off %s".format(desc) + defaultStr(false)) +
+ acc
+ }
+ case (name, SetInt(_, default), desc) => {
+ def defaultStr(b: Boolean): String = {
+ val opt =
+ for {
+ f <- default
+ s <- f(b)
+ } yield " (default%s)".format(s)
+ opt.getOrElse("")
+ }
+ optline("--" + name + " <int>", "set %s".format(desc) + defaultStr(true)) +
+ optline("--no-" + name, "unset %s".format(desc) + defaultStr(false)) +
+ acc
+ }
+ })
+ }
+
+ val header =
+ """
+Usage: %s [options] %s
+
+""".format(program, anonName) +
+optline(anonName, anonDesc) + """
+Options:
+"""
+
+ private var currentArgs: List[String] = List()
+
+ def usageErr(): Nothing = {
+ val unprocessed = currentArgs match {
+ case Nil => ""
+ case _ => """
+Unprocessed Arguments:
+ """ + currentArgs.reduceRight({ _ + " " + _ }) + "%n".format()
+ }
+ print(header + descriptions + unprocessed)
+ sys.exit(1)
+ }
+
+ def process(args: Array[String]): T = {
+ def loop(l: List[String]): List[String] = {
+ currentArgs = l
+ l match {
+ case Nil => Nil
+ case h :: t => opts.get(h) match {
+ case None => l
+ case Some(doit) => { val tp = doit(t).getOrElse(t); loop(tp) }
+ }
+ }
+ }
+ val err: PartialFunction[List[String], T] = { case _ => usageErr() }
+ (anonDo orElse err)(loop(args.toList))
+ }
+ }
+} \ No newline at end of file
diff --git a/lab4/src/test/resources/lab4/test4001_id.ans b/lab4/src/test/resources/lab4/test4001_id.ans
new file mode 100644
index 0000000..b0ea4bc
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4001_id.ans
@@ -0,0 +1,4 @@
+## Call(Fun(None,List((x,TNumber)),None,Var(x)),List(N(4.0))) : number
+## step 0: Call(Fun(None,List((x,TNumber)),None,Var(x)),List(N(4.0)))
+## value: N(4.0)
+4.0
diff --git a/lab4/src/test/resources/lab4/test4001_id.jsy b/lab4/src/test/resources/lab4/test4001_id.jsy
new file mode 100644
index 0000000..3402469
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4001_id.jsy
@@ -0,0 +1 @@
+function(x: number) {return x } (4)
diff --git a/lab4/src/test/resources/lab4/test4002_multiparamfun.ans b/lab4/src/test/resources/lab4/test4002_multiparamfun.ans
new file mode 100644
index 0000000..302ccae
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4002_multiparamfun.ans
@@ -0,0 +1,6 @@
+## Call(Fun(None,List((x,TNumber), (y,TBool)),None,If(Var(y),Binary(Plus,Var(x),N(1.0)),Binary(Minus,Var(x),N(1.0)))),List(N(4.0), B(true))) : number
+## step 0: Call(Fun(None,List((x,TNumber), (y,TBool)),None,If(Var(y),Binary(Plus,Var(x),N(1.0)),Binary(Minus,Var(x),N(1.0)))),List(N(4.0), B(true)))
+## step 1: If(B(true),Binary(Plus,N(4.0),N(1.0)),Binary(Minus,N(4.0),N(1.0)))
+## step 2: Binary(Plus,N(4.0),N(1.0))
+## value: N(5.0)
+5.0
diff --git a/lab4/src/test/resources/lab4/test4002_multiparamfun.jsy b/lab4/src/test/resources/lab4/test4002_multiparamfun.jsy
new file mode 100644
index 0000000..9c38c07
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4002_multiparamfun.jsy
@@ -0,0 +1 @@
+function (x: number, y: bool) { return y ? x + 1 : x - 1 } (4, true)
diff --git a/lab4/src/test/resources/lab4/test4007_objliteral.ans b/lab4/src/test/resources/lab4/test4007_objliteral.ans
new file mode 100644
index 0000000..4b4cc1b
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4007_objliteral.ans
@@ -0,0 +1,4 @@
+## Obj(TreeMap(a -> N(5.0), b -> N(2.0))) : { a: number; b: number }
+## value: Obj(TreeMap(a -> N(5.0), b -> N(2.0)))
+{ a: 5.0,
+ b: 2.0 }
diff --git a/lab4/src/test/resources/lab4/test4007_objliteral.jsy b/lab4/src/test/resources/lab4/test4007_objliteral.jsy
new file mode 100644
index 0000000..b98f88d
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4007_objliteral.jsy
@@ -0,0 +1 @@
+{a: 5, b: 2} \ No newline at end of file
diff --git a/lab4/src/test/resources/lab4/test4010_deref.ans b/lab4/src/test/resources/lab4/test4010_deref.ans
new file mode 100644
index 0000000..69a991f
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4010_deref.ans
@@ -0,0 +1,4 @@
+## GetField(Obj(TreeMap(f -> N(3.0))),f) : number
+## step 0: GetField(Obj(TreeMap(f -> N(3.0))),f)
+## value: N(3.0)
+3.0
diff --git a/lab4/src/test/resources/lab4/test4010_deref.jsy b/lab4/src/test/resources/lab4/test4010_deref.jsy
new file mode 100644
index 0000000..83418ef
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4010_deref.jsy
@@ -0,0 +1 @@
+{ f: 3 }.f
diff --git a/lab4/src/test/resources/lab4/test4029_simplerec.ans b/lab4/src/test/resources/lab4/test4029_simplerec.ans
new file mode 100644
index 0000000..b773df9
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4029_simplerec.ans
@@ -0,0 +1,11 @@
+## ConstDecl(n,N(1.0),Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(N(1.0)))) : number
+## step 0: ConstDecl(n,N(1.0),Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(N(1.0))))
+## step 1: Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(N(1.0)))
+## step 2: If(Binary(Eq,N(1.0),N(0.0)),N(0.0),Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(Binary(Minus,N(1.0),N(1.0)))))
+## step 3: If(B(false),N(0.0),Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(Binary(Minus,N(1.0),N(1.0)))))
+## step 4: Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(Binary(Minus,N(1.0),N(1.0))))
+## step 5: Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(N(0.0)))
+## step 6: If(Binary(Eq,N(0.0),N(0.0)),N(0.0),Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(Binary(Minus,N(0.0),N(1.0)))))
+## step 7: If(B(true),N(0.0),Call(Fun(Some(f),List((n,TNumber)),Some(TNumber),If(Binary(Eq,Var(n),N(0.0)),N(0.0),Call(Var(f),List(Binary(Minus,Var(n),N(1.0)))))),List(Binary(Minus,N(0.0),N(1.0)))))
+## value: N(0.0)
+0.0
diff --git a/lab4/src/test/resources/lab4/test4029_simplerec.jsy b/lab4/src/test/resources/lab4/test4029_simplerec.jsy
new file mode 100644
index 0000000..61b2787
--- /dev/null
+++ b/lab4/src/test/resources/lab4/test4029_simplerec.jsy
@@ -0,0 +1,2 @@
+const n = 1;
+(function f(n: number): number { return n === 0 ? 0 : f(n - 1) })(1) \ No newline at end of file
diff --git a/lab4/src/test/scala/jsy/lab4/Lab4Spec.scala b/lab4/src/test/scala/jsy/lab4/Lab4Spec.scala
new file mode 100644
index 0000000..0c05aab
--- /dev/null
+++ b/lab4/src/test/scala/jsy/lab4/Lab4Spec.scala
@@ -0,0 +1,217 @@
+package jsy.lab4
+
+import org.scalatest.flatspec.AnyFlatSpec
+import Parser.parse
+import ast._
+import Lab4._
+
+class Lab4StudentSpec extends AnyFlatSpec {
+}
+
+class Lab4Spec extends AnyFlatSpec {
+
+ /***** hastype Tests *****/
+ {
+ val xtype = TNumber
+ val tenvx = extend(Map.empty, "x", xtype)
+
+ "TypeVar" should "perform TypeVar" in {
+ assertResult(xtype) {
+ hastype(tenvx, Var("x"))
+ }
+ }
+
+ "hastype/call-non-fun" should "yield a static type error" in {
+ for (e <- List(
+ ("3(4)"),
+ ("3(true)"),
+ ("(10 + 4 + 7 - true * 3)(true)"),
+ ("((function (x: number) { return 0 })(10))(true)")
+ )) {
+ intercept[StaticTypeError] {
+ inferType(e)
+ }
+ }
+ }
+
+ "hastype/arithmetic" should "type check JavaScripty arithmetic expressions according to the lab spec" in {
+ for ((e,t) <- List(
+ ("3 <= 4", TBool),
+ ("'3' < '4'", TBool),
+ ("3 + 4", TNumber),
+ ("'3' + '4'", TString),
+ ("3 - 4", TNumber),
+ ("3 * 4 + 1 - 4 / 12", TNumber),
+ ("undefined", TUndefined)
+ )) {
+ assertResult(t){ inferType(e) }
+ }
+ }
+
+ "hastype/functions-objects" should "type check JavaScripty function-object expressions according to the lab spec" in {
+ val f1 = parse("function (x: number) { return x }")
+ val o1 = parse("{f: 3, g: true, h: undefined}")
+ for ((e,t) <- List(
+ (f1, TFun(List(("x", TNumber)), TNumber)),
+ (o1, TObj(Map("f" -> TNumber, "g" -> TBool, "h" -> TUndefined))),
+ (Call(f1, List(N(3))), TNumber),
+ (GetField(o1, "g"), TBool)
+ )) {
+ assertResult(t){ inferType(e) }
+ }
+ }
+
+ "hastype/simple-programs" should "type check JavaScripty programs according to the lab spec" in {
+ assertResult(TNumber) { inferType(
+ """
+ const w = function w(y: number): number { return y === 0 ? 0.1 : y + w(y - 1) };
+ w(3)
+ """
+ )}
+ assertResult(TNumber) { inferType(
+ """
+ const x = 1;
+ const g = function(y: number) { return x; };
+ const h = function(x: number) { return g(2); };
+ h(3)
+ """
+ )}
+ }
+
+ "hastype/recursive-programs" should "type check recursive JavaScripty programs according to the lab spec" in {
+ assertResult(TNumber) { inferType(
+ """
+ const factorial = function f(n: number): number {
+ return n === 0 ? 1 : n * f(n - 1)
+ }
+ factorial(4)
+ """
+ )}
+ }
+ }
+
+
+ /***** substitute Tests *****/
+ {
+ "substitute" should "substitute a value for uses of a variable" in {
+ for ((r,e,v,x) <- List(
+ ("const x = 3; x", "const x = x; x", "3", "x"),
+ ("function (x: number) { return x + y }", "function (x: number) { return x + y }", "3", "x"),
+ ("function x(y: number) { return x + y }", "function x(y: number) { return x + y }", "3", "x")
+ )) {
+ assertResult(parse(r)){ substitute(parse(v), x, parse(e)) }
+ }
+ }
+ }
+
+
+ /***** step Tests *****/
+ {
+ "step" should "perform one step of evaluation according to the lab spec" in {
+ for ((r, s) <- List (
+ ("1", "4 - 3"),
+ ("3 + 4", "1, 3 + 4"),
+ ("(3) + 3", "(1 + 2) + 3"),
+ ("(2) + (3 / 4)", "(1 * 2) + (3 / 4)"),
+ ("(2 + 4)", "true ? (2 + 4) : (1 + 1)"),
+ ("const x = 2; x", "const x = 1 + 1; x"),
+ ("2", "const x = 2; x"),
+ ("3 + 3 + 4 + 5", "1 + 2 + 3 + 4 + 5"),
+ ("3", "(function (x: number) { return x })(3)"),
+// ("3 + 1", "(function (x: number) { return x })(3 + 1)")
+ )) {
+ assertResult(parse(r)){oneStep(s)}
+ }
+ }
+
+ "step/call-non-fun" should "yield a stuck error" in {
+ for (e <- List(
+ ("3(4)"),
+ ("3(true)"),
+ ("((function (x: number) { return 0 })(10))(true)")
+ )) {
+ intercept[StuckError] { iterateStep(e) }
+ }
+ }
+
+ "step/simple-programs" should "evaluate JavaScripty programs according to the lab spec" in {
+ assertResult(N(6.1)) { iterateStep(
+ """
+ const w = function w(y: number) { return y === 0 ? 0.1 : y + w(y - 1) }
+ w(3)
+ """
+ )}
+ assertResult(N(1)) { iterateStep(
+ """
+ const x = 1;
+ const g = function(y: number) { return x; };
+ const h = function(x: number) { return g(2); };
+ h(3)
+ """
+ )}
+ assertResult(N(1.1)) { iterateStep(
+ """
+ const g = function(x: number) { return function(y: number) { return x - y } };
+ g(1)(0) + 0.1
+ """
+ )}
+ assertResult(N(6)) { iterateStep(
+ """
+ const plus = function(x: number, y: number) { return x + y };
+ plus(1 + 2, 3)
+ """
+ )}
+ assertResult(N(6)) { iterateStep(
+ """
+ const plus = function(x: number) { return function(y: number) { return x + y } };
+ plus(1 + 2)(3)
+ """
+ )}
+ }
+
+ "step/recursive-programs" should "evaluate recursive JavaScripty programs according to the lab spec" in {
+ assertResult(N(6)) { iterateStep(
+ """
+ const factorial = function f(n: number) {
+ return n === 0 ? 1 : n * f(n - 1)
+ }
+ factorial(3)
+ """
+ )}
+ assertResult(S("aaa")) { iterateStep(
+ """
+ const repeat = function(s: string) {
+ return function loop(n: number) {
+ return n === 0 ? "" : s + loop(n - 1)
+ }
+ }
+ repeat("a")(3)
+ """
+ )}
+ }
+
+ "step/objects" should "evaluate JavaScripty objects according to the lab spec" in {
+ assertResult(N(7.0)) { iterateStep(
+ """
+ const pair = function(x: number, y: number) {
+ return {x: x, y: y}
+ };
+ const p = pair(3, 4);
+ p.x + p.y
+ """
+ )}
+ assertResult(N(5.0)) { iterateStep(
+ """
+ const suspension = function(f: (a: number) => number, n: number) {
+ return {f: f, n: n}
+ };
+ const s = suspension((a: number) => a + 1, 4);
+ s.f(s.n)
+ """
+ )}
+ }
+ }
+
+}
+
+class Lab4JsyTests extends jsy.tester.JavascriptyTester(None, "lab4", Lab4)
diff --git a/lab4/src/test/scala/jsy/tester/JavascriptyTester.scala b/lab4/src/test/scala/jsy/tester/JavascriptyTester.scala
new file mode 100644
index 0000000..48e789c
--- /dev/null
+++ b/lab4/src/test/scala/jsy/tester/JavascriptyTester.scala
@@ -0,0 +1,23 @@
+package jsy.tester
+import java.io.File
+import jsy.util.JsyApplication
+import org.scalatest._
+import flatspec._
+
+/*
+ * A ScalaTest interface for running system tests.
+ */
+class JavascriptyTester(rootPrefix: Option[String], testDirectory: String, jsy: JsyApplication) extends AnyFlatSpec {
+ val testResources = s"src${File.separator}test${File.separator}resources"
+ val testPrefix = rootPrefix match {
+ case None => testResources
+ case Some(p) => s"${p}${File.separator}${testResources}"
+ }
+ val testPath = s"${testPrefix}${File.separator}${testDirectory}"
+ jsy.test(new File(testPath)) { case (in,ans,assertion) =>
+ s"eval on ${in}" should s"match ${ans}" in {
+ val (b: Boolean, msg: String) = assertion
+ assert(b, msg)
+ }
+ }
+}