Parsing has never been this much fun
[hcoop/domtool2.git] / src / domtool.grm
index 79d13a1..3384492 100644 (file)
@@ -27,10 +27,10 @@ open Ast
  | SYMBOL of string | CSYMBOL of string
  | STRING of string
  | INT of int
- | ARROW | DARROW | COLON
+ | ARROW | DARROW | COLON | CARET | BANG | AND
  | LPAREN | RPAREN | LBRACK | RBRACK | LBRACE | RBRACE
  | EQ | COMMA | BSLASH | SEMI | LET | IN | END
-
+ | ROOT
 
 %nonterm 
    file of exp
@@ -41,6 +41,9 @@ open Ast
  | elistNe of exp list
  | clist of exp list
  | typ of typ
+ | ctxt of context
+ | recd of record
+ | recdNe of record
 
 %verbose                                (* print summary of errors *)
 %pos int                                (* positions *)
@@ -52,17 +55,20 @@ open Ast
 %name Domtool
 
 %right SEMI
+%nonassoc COLON
 %nonassoc IN
-%right ARROW
+%right ARROW DARROW
 %right COMMA
 %nonassoc EQ
+%right AND
+%nonassoc CARET BANG
 
 %%
 
 file   : exp                               (exp)
 
 exp    : apps                              (apps)
-       | BSLASH SYMBOL COLON typ ARROW exp (ELam (SYMBOL, typ, exp), (BSLASHleft, expright))
+       | BSLASH SYMBOL COLON LPAREN typ RPAREN ARROW exp (ELam (SYMBOL, typ, exp), (BSLASHleft, expright))
        | CSYMBOL EQ exp                    (ESet (CSYMBOL, exp), (CSYMBOLleft, expright))
        | exp SEMI exp                      (let
                                                val ls = case #1 exp2 of
@@ -86,8 +92,11 @@ term   : LPAREN exp RPAREN                 (exp)
                                                           | (_, ESeq ls) => exp1 :: ls
                                                           | _ => [exp1, exp2]
                                            in
-                                               (ESeq ls, (exp1left, exp2right))
+                                               (ELocal (ESeq ls, (exp1left, exp2right)),
+                                                (exp1left, exp2right))
                                            end)
+       | SYMBOL                            (EVar SYMBOL, (SYMBOLleft, SYMBOLright))
+       | CSYMBOL                           (EEnv CSYMBOL, (CSYMBOLleft, CSYMBOLright))
 
 elist  :                                   ([])
        | elistNe                           (elistNe)
@@ -96,3 +105,24 @@ elistNe: exp                               ([exp])
        | exp COMMA elistNe                 (exp :: elistNe)
 
 typ    : SYMBOL                            (TBase SYMBOL, (SYMBOLleft, SYMBOLright))
+       | LBRACK typ RBRACK                 (TList typ, (LBRACKleft, RBRACKright))
+       | typ ARROW typ                     (TArrow (typ1, typ2), (typleft, typright))
+       | LBRACK ctxt RBRACK recd DARROW recd (TAction (ctxt, recd1, recd2), (ctxtleft, recd2right))
+       | LBRACK ctxt RBRACK recd           (TAction (ctxt, recd, StringMap.empty),
+                                           (ctxtleft, recdright))
+       | LBRACK ctxt RBRACK                (TAction (ctxt, StringMap.empty, StringMap.empty),
+                                           (ctxtleft, ctxtright))
+       | LPAREN typ RPAREN                 (typ)
+
+recd   : LBRACE RBRACE                     (StringMap.empty)
+       | LBRACE recdNe RBRACE              (recdNe)
+
+recdNe : CSYMBOL COLON typ                 (StringMap.insert (StringMap.empty, CSYMBOL, typ))
+       | CSYMBOL COLON typ COMMA recdNe    (StringMap.insert (recdNe, CSYMBOL, typ))
+
+ctxt   : ROOT                              (CRoot, (ROOTleft, ROOTright))
+       | CSYMBOL                           (CConst CSYMBOL, (CSYMBOLleft, CSYMBOLright))
+       | CARET ctxt                        (CPrefix ctxt, (CARETleft, ctxtright))
+       | BANG ctxt                         (CNot ctxt, (BANGleft, ctxtright))
+       | ctxt AND ctxt                     (CAnd (ctxt1, ctxt2), (ctxt1left, ctxt2right))
+       | LPAREN ctxt RPAREN                (ctxt)