]> Joshua Wise's Git repositories - snipe.git/blob - parse/ast.sml
Add cast syntax.
[snipe.git] / parse / ast.sml
1 (* L3 Compiler
2  * Abstract Syntax Trees
3  * Author: Alex Vaynberg
4  * Modified: Frank Pfenning <fp@cs.cmu.edu>
5  * Modified: Joshua Wise <jwise@andrew.cmu.edu>
6  * Modified: Chris Lu <czl@andrew.cmu.edu>
7  *
8  * Uses pretty printing library
9  * structure PP  -- see util/pp.sml
10  *)
11
12 signature AST =
13 sig
14   type ident = Symbol.symbol
15   
16   datatype oper = 
17      PLUS
18    | MINUS
19    | TIMES
20    | DIVIDEDBY
21    | MODULO
22    | NEGATIVE                   (* unary minus *)
23    | LSH
24    | RSH
25    | LOGOR
26    | LOGAND
27    | BITAND
28    | BITXOR
29    | BITOR
30    | BITNOT
31    | BANG                       (* logical not *)
32    | NEQ
33    | EQ
34    | LT
35    | LE
36    | GE
37    | GT
38
39   datatype exp =
40      Var of ident
41    | Cast of Type.vtype * exp
42    | ConstExp of Word32.word
43    | StringExp of string
44    | OpExp of oper * exp list
45    | Marked of (* Kane *) exp Mark.marked
46    | FuncCall of ident * (exp list)
47    | Member of exp * ident
48    | DerefMember of exp * ident
49    | Dereference of exp
50    | ArrIndex of exp * exp
51    | New of Type.vtype
52    | NewArr of Type.vtype * exp
53    | Null
54    | Conditional of exp * exp * exp
55   and stm =
56      Assign of exp * exp
57    | AsnOp of oper * exp * exp
58    | Effect of exp (* Just side effect the expression *)
59    | Return of exp
60    | Nop
61    | Break
62    | Continue
63    | If of exp * stm list * stm list option
64    | For of stm option * exp * stm option * stm list
65    | While of exp * stm list
66    | MarkedStm of stm Mark.marked
67
68   datatype function =
69      Extern of Type.vtype * (Type.variable list)
70    | Function of Type.vtype * (Type.variable list) * (Type.variable list) * stm list
71    | MarkedFunction of function Mark.marked
72   
73   type program = Type.typedef Symbol.table * function Symbol.table
74
75   (* print as source, with redundant parentheses *)
76   structure Print :
77   sig
78     val pp_exp : exp -> string
79     val pp_stm : stm -> string
80     val pp_program : program -> string
81   end
82 end
83
84 structure Ast :> AST =
85 struct
86   type ident = Symbol.symbol
87
88   datatype oper = 
89      PLUS
90    | MINUS
91    | TIMES
92    | DIVIDEDBY
93    | MODULO
94    | NEGATIVE                   (* unary minus *)
95    | LSH
96    | RSH
97    | LOGOR
98    | LOGAND
99    | BITAND
100    | BITXOR
101    | BITOR
102    | BITNOT
103    | BANG
104    | NEQ
105    | EQ
106    | LT
107    | LE
108    | GE
109    | GT
110
111   datatype exp =
112      Var of ident
113    | Cast of Type.vtype * exp
114    | ConstExp of Word32.word
115    | StringExp of string
116    | OpExp of oper * exp list
117    | Marked of exp Mark.marked
118    | FuncCall of ident * (exp list)
119    | Member of exp * ident
120    | DerefMember of exp * ident
121    | Dereference of exp
122    | ArrIndex of exp * exp
123    | New of Type.vtype
124    | NewArr of Type.vtype * exp
125    | Null
126    | Conditional of exp * exp * exp
127   and stm =
128      Assign of exp * exp
129    | AsnOp of oper * exp * exp
130    | Effect of exp (* Just side effect the expression *)
131    | Return of exp
132    | Nop
133    | Break
134    | Continue
135    | If of exp * stm list * stm list option
136    | For of stm option * exp * stm option * stm list
137    | While of exp * stm list
138    | MarkedStm of stm Mark.marked
139
140   datatype function =
141      Extern of Type.vtype * (Type.variable list)
142    | Function of Type.vtype * (Type.variable list) * (Type.variable list) * stm list
143    | MarkedFunction of function Mark.marked
144   
145   type program = Type.typedef Symbol.table * function Symbol.table
146
147   (* print programs and expressions in source form
148    * using redundant parentheses to clarify precedence
149    *)
150   structure Print =
151   struct
152     fun pp_ident id = Symbol.name id
153
154     fun pp_oper PLUS = "+"
155       | pp_oper MINUS = "-"
156       | pp_oper TIMES = "*"
157       | pp_oper DIVIDEDBY = "/"
158       | pp_oper MODULO = "%"
159       | pp_oper NEGATIVE = "-"
160       | pp_oper LSH = "<<"
161       | pp_oper RSH = ">>"
162       | pp_oper LOGAND = "&&"
163       | pp_oper LOGOR = "||"
164       | pp_oper BITAND = "&"
165       | pp_oper BITXOR = "^"
166       | pp_oper BITOR = "|"
167       | pp_oper BITNOT = "~"
168       | pp_oper BANG = "!"
169       | pp_oper NEQ = "!="
170       | pp_oper EQ = "=="
171       | pp_oper LT = "<"
172       | pp_oper LE = "<="
173       | pp_oper GT = ">"
174       | pp_oper GE = ">="
175
176     fun pp_exp (Var(id)) = pp_ident id
177       | pp_exp (Cast(ty, exp)) = "["^(Type.Print.pp_type ty)^"]"^(pp_exp exp)
178       | pp_exp (ConstExp(c)) = Word32Signed.toString c
179       | pp_exp (StringExp(s)) = "\"" ^ s ^ "\""
180       | pp_exp (OpExp(oper, [e])) =
181           pp_oper oper ^ "(" ^ pp_exp e ^ ")"
182       | pp_exp (OpExp(oper, [e1,e2])) =
183           "(" ^ pp_exp e1 ^ " " ^ pp_oper oper
184           ^ " " ^ pp_exp e2 ^ ")"
185       | pp_exp (OpExp(oper, _)) =
186           pp_oper oper
187       | pp_exp (FuncCall(id, l)) = pp_ident id ^ "(" ^ pp_expl l ^ ")"
188       | pp_exp (Marked(marked_exp)) =
189           pp_exp (Mark.data marked_exp)
190       | pp_exp (Member(e, i)) = pp_exp e ^ "." ^ pp_ident i
191       | pp_exp (DerefMember(e, i)) = pp_exp e ^ "->" ^ pp_ident i
192       | pp_exp (Dereference(e)) = "*(" ^ pp_exp e ^ ")"
193       | pp_exp (ArrIndex(e1, e2)) = pp_exp e1 ^ "[" ^pp_exp e2 ^ "]"
194       | pp_exp (New t) = "new(" ^ Type.Print.pp_type t ^ ")"
195       | pp_exp (NewArr (t, s)) = "new(" ^ Type.Print.pp_type t ^ "[" ^ pp_exp s ^ "])"
196       | pp_exp Null = "NULL"
197       | pp_exp (Conditional (q, e1, e2)) = "("^(pp_exp q)^"?"^(pp_exp e1)^":"^(pp_exp e2)^")"
198     
199     and pp_expl nil = ""
200       | pp_expl (e::a::l) = (pp_exp e) ^ ", " ^ (pp_expl (a::l))
201       | pp_expl (e::l) = (pp_exp e) ^ (pp_expl l)
202
203     and pp_stm (Assign (e1,e2)) =
204           pp_exp e1 ^ " = " ^ pp_exp e2 ^ ";\n"
205       | pp_stm (AsnOp (oop, e1, e2)) =
206           pp_exp e1 ^ " " ^ pp_oper oop ^ "= " ^ pp_exp e2 ^ ";\n"
207       | pp_stm (Effect (e)) = 
208           pp_exp e ^ ";\n"
209       | pp_stm (Return e) =
210           "return " ^ pp_exp e ^ ";\n"
211       | pp_stm Nop = ";\n"
212       | pp_stm Break = "break;\n"
213       | pp_stm Continue = "continue;\n"
214       | pp_stm (If (e, s, NONE)) = "if ("^pp_exp e^")\n"^pp_block s
215       | pp_stm (If (e, s, SOME s2)) = "if ("^pp_exp e^")\n"^pp_block s^"else\n"^pp_block s2
216       | pp_stm (While (e, s)) = "while ("^pp_exp e^")\n"^pp_block s
217       | pp_stm (For (so1, e, so2, s)) = "for ("^ (if (isSome so1) then pp_stm (valOf so1) else "") ^ pp_exp e ^ (if(isSome so2) then pp_stm (valOf so2) else "") ^ ")\n" ^ pp_block s
218       | pp_stm (MarkedStm m) = pp_stm (Mark.data m)
219
220     and pp_block (nil) = ";"
221       | pp_block (a::nil) = pp_stm a
222       | pp_block (l) = let
223           val contents = map pp_stm l
224         in
225           "{\n" ^ String.concat contents ^ "}\n"
226         end
227
228     and pp_stms nil = ""
229       | pp_stms (s::ss) = pp_stm s ^ "\n" ^ pp_stms ss
230
231     and pp_params nil = ""
232       | pp_params ((i, t)::a::l) = (pp_ident i) ^ " : " ^ (Type.Print.pp_type t) ^ ", " ^ (pp_params (a::l))
233       | pp_params ((i, t)::l) = (pp_ident i) ^ " : " ^ (Type.Print.pp_type t) ^ (pp_params l)
234     
235     and pp_vars nil = ""
236       | pp_vars ((i, t)::l) = "var " ^ (pp_ident i) ^ " : " ^ (Type.Print.pp_type t) ^ ";\n" ^ (pp_vars l)
237
238     and pp_function (n, Extern(t, pl)) = "extern " ^ (Type.Print.pp_type t) ^ " " ^ (pp_ident n) ^ "(" ^ (pp_params pl) ^ ");\n"
239       | pp_function (n, Function(t, pl, vl, stms)) = (Type.Print.pp_type t) ^ " " ^ (pp_ident n) ^ "(" ^ (pp_params pl) ^ ")\n{\n" ^ (pp_vars vl) ^ (String.concat (map pp_stm stms)) ^ "\n}\n"
240       | pp_function (n, MarkedFunction d) = pp_function (n, Mark.data d)
241
242     and pp_program (types, funs) = String.concat ((map Type.Print.pp_typedef (Symbol.elemsi types)) @ (map pp_function (Symbol.elemsi funs)))
243   end
244 end
This page took 0.035967 seconds and 4 git commands to generate.