]> ruin.nu Git - proglang.git/blob - Parsyntax.y
f75fff6d2eebaa3458074b030d5c7b70b0de7f1d
[proglang.git] / Parsyntax.y
1 -- This Happy file was machine-generated by the BNF converter
2 {
3 module Parsyntax where
4 import Abssyntax
5 import Lexsyntax
6 import ErrM
7 }
8
9 %name pStms Stms
10 %name pExp Exp
11
12 -- no lexer declaration
13 %monad { Err } { thenM } { returnM }
14 %tokentype { Token }
15
16 %token 
17  '=' { PT _ (TS "=") }
18  ';' { PT _ (TS ";") }
19  '{' { PT _ (TS "{") }
20  '}' { PT _ (TS "}") }
21  '(' { PT _ (TS "(") }
22  ')' { PT _ (TS ")") }
23  '++' { PT _ (TS "++") }
24  '--' { PT _ (TS "--") }
25  '-' { PT _ (TS "-") }
26  '<' { PT _ (TS "<") }
27  '<=' { PT _ (TS "<=") }
28  '>' { PT _ (TS ">") }
29  '>=' { PT _ (TS ">=") }
30  '==' { PT _ (TS "==") }
31  '!=' { PT _ (TS "!=") }
32  '+' { PT _ (TS "+") }
33  '*' { PT _ (TS "*") }
34  '/' { PT _ (TS "/") }
35  'bool' { PT _ (TS "bool") }
36  'else' { PT _ (TS "else") }
37  'false' { PT _ (TS "false") }
38  'if' { PT _ (TS "if") }
39  'int' { PT _ (TS "int") }
40  'print' { PT _ (TS "print") }
41  'readBool' { PT _ (TS "readBool") }
42  'readInt' { PT _ (TS "readInt") }
43  'true' { PT _ (TS "true") }
44  'while' { PT _ (TS "while") }
45
46 L_ident  { PT _ (TV $$) }
47 L_integ  { PT _ (TI $$) }
48 L_err    { _ }
49
50
51 %%
52
53 Ident   :: { Ident }   : L_ident  { Ident $1 }
54 Integer :: { Integer } : L_integ  { (read $1) :: Integer }
55
56 Bool :: { Bool }
57 Bool : 'true' { True } 
58   | 'false' { False }
59
60
61 Stm :: { Stm }
62 Stm : Type Ident '=' Exp ';' { SDecl $1 $2 $4 } 
63   | Type Ident ';' { decl_ $1 $2 }
64   | Exp ';' { SExp $1 }
65   | '{' ListStm '}' { SBlock (reverse $2) }
66   | 'if' '(' Exp ')' Stm { if_ $3 $5 }
67   | 'if' '(' Exp ')' Stm 'else' Stm { SIf $3 $5 $7 }
68   | 'while' '(' Exp ')' Stm { SWhile $3 $5 }
69   | 'print' Exp ';' { SPrint $2 }
70
71
72 Exp :: { Exp }
73 Exp : Ident '=' Exp { EAss $1 $3 } 
74   | Exp1 BOp Exp1 { BExp $1 $2 $3 }
75   | Exp1 { $1 }
76
77
78 Exp1 :: { Exp }
79 Exp1 : Exp1 Op1 Exp2 { op1_ $1 $2 $3 } 
80   | Exp2 { $1 }
81
82
83 Exp2 :: { Exp }
84 Exp2 : Exp2 Op2 Exp3 { op2_ $1 $2 $3 } 
85   | Exp3 { $1 }
86
87
88 Exp3 :: { Exp }
89 Exp3 : Ident '++' { postIncr_ $1 } 
90   | Ident '--' { postDecr_ $1 }
91   | Ident { EVar $1 }
92   | Integer { EInt $1 }
93   | '-' Exp3 { ENeg $2 }
94   | Bool { EBool $1 }
95   | 'readInt' { EReadI }
96   | 'readBool' { EReadB }
97   | '(' Exp ')' { $2 }
98
99
100 ListStm :: { [Stm] }
101 ListStm : {- empty -} { [] } 
102   | ListStm Stm { flip (:) $1 $2 }
103
104
105 Stms :: { Stms }
106 Stms : ListStm { Program (reverse $1) } 
107
108
109 BOp :: { BOp }
110 BOp : '<' { Lt } 
111   | '<=' { ELt }
112   | '>' { Gt }
113   | '>=' { EGt }
114   | '==' { Eq }
115   | '!=' { NEq }
116
117
118 Op1 :: { Op }
119 Op1 : '+' { Plus } 
120   | '-' { Minus }
121
122
123 Op2 :: { Op }
124 Op2 : '*' { Times } 
125   | '/' { Div }
126
127
128 Op :: { Op }
129 Op : Op1 { $1 } 
130   | Op2 { $1 }
131
132
133 Type :: { Type }
134 Type : 'int' { TInt } 
135   | 'bool' { TBool }
136
137
138
139 {
140
141 returnM :: a -> Err a
142 returnM = return
143
144 thenM :: Err a -> (a -> Err b) -> Err b
145 thenM = (>>=)
146
147 happyError :: [Token] -> Err a
148 happyError ts =
149   Bad $ "syntax error at " ++ tokenPos ts ++ if null ts then [] else (" before " ++ unwords (map prToken (take 4 ts)))
150
151 myLexer = tokens
152 decl_ t_ v_ = SDecl t_ v_ EDefault
153 if_ e_ s_ = SIf e_ s_ SNoop
154 op1_ e1_ o_ e2_ = OpExp e1_ o_ e2_
155 op2_ e1_ o_ e2_ = OpExp e1_ o_ e2_
156 postIncr_ i_ = EPost i_ Plus
157 postDecr_ i_ = EPost i_ Minus
158 }
159