Indent stringinfied AST
[tiger.ml.git] / compiler / src / lib / tiger / tiger_absyn.ml
CommitLineData
5597e56d 1open Printf
28875fec 2
5597e56d
SK
3module List = ListLabels
4module String = StringLabels
5
6module Sym = Tiger_symbol
7module Pos = Tiger_position
28875fec 8
e7b4c94e
SK
9module Indent : sig
10 type t
11 val init : enabled:bool -> unit:string -> t
12 val next : t -> t
13 val to_string : t -> string
14end = struct
15 type t =
16 { unit : string option
17 ; levels : int
18 }
19
20 let init ~enabled ~unit =
21 { unit = if enabled then Some unit else None
22 ; levels = 0
23 }
24
25 let next t =
26 {t with levels = succ t.levels}
27
28 let to_string = function
29 | {unit=None; _} ->
30 ""
31 | {unit=Some u; levels} ->
32 let rec add = function
33 | 0 -> ""
34 | n -> u ^ (add (pred n))
35 in
36 "\n" ^ (add levels)
37end
38
28875fec
SK
39type oper =
40 | PlusOp
41 | MinusOp
42 | TimesOp
43 | DivideOp
44 | EqOp
45 | NeqOp
46 | LtOp
47 | LeOp
48 | GtOp
49 | GeOp
50
51type exp =
28875fec
SK
52 | NilExp
53 | IntExp of
54 int
55 | StringExp of
56 { string : string
5597e56d 57 ; pos : Pos.t
28875fec
SK
58 }
59 | CallExp of
5597e56d 60 { func : Sym.t
28875fec 61 ; args : exp list
5597e56d 62 ; pos : Pos.t
28875fec
SK
63 }
64 | OpExp of
65 { left : exp
66 ; oper : oper
67 ; right : exp
5597e56d 68 ; pos : Pos.t
28875fec
SK
69 }
70 | RecordExp of
5597e56d
SK
71 { fields : (Sym.t * exp * Pos.t) list
72 ; typ : Sym.t
73 ; pos : Pos.t
28875fec
SK
74 }
75 | SeqExp of
5597e56d 76 (exp * Pos.t) list
28875fec
SK
77 | AssignExp of
78 { var : var
79 ; exp : exp
5597e56d 80 ; pos : Pos.t
28875fec
SK
81 }
82 | IfExp of
83 { test : exp
84 ; then' : exp
85 ; else' : exp option
5597e56d 86 ; pos : Pos.t
28875fec
SK
87 }
88 | WhileExp of
89 { test : exp
90 ; body : exp
5597e56d 91 ; pos : Pos.t
28875fec
SK
92 }
93 | ForExp of
5597e56d 94 { var : Sym.t
28875fec
SK
95 ; escape : bool ref (* Whoa - why a mutable cell in AST? *)
96 ; lo : exp
97 ; hi : exp
98 ; body : exp
5597e56d 99 ; pos : Pos.t
28875fec
SK
100 }
101 | BreakExp of
5597e56d 102 Pos.t
28875fec
SK
103 | LetExp of
104 { decs : dec list
105 ; body : exp
5597e56d 106 ; pos : Pos.t
28875fec
SK
107 }
108 | ArrayExp of
5597e56d 109 { typ : Sym.t
28875fec
SK
110 ; size : exp
111 ; init : exp
5597e56d 112 ; pos : Pos.t
28875fec 113 }
5597e56d
SK
114 | VarExp of
115 var
28875fec
SK
116and var =
117 | SimpleVar of
5597e56d
SK
118 { symbol : Sym.t
119 ; pos : Pos.t
28875fec
SK
120 }
121 | FieldVar of
122 { var : var
5597e56d
SK
123 ; symbol : Sym.t
124 ; pos : Pos.t
28875fec
SK
125 }
126 | SubscriptVar of
127 { var : var
128 ; exp : exp
5597e56d 129 ; pos : Pos.t
28875fec
SK
130 }
131and dec =
132 | FunDecs of (* "FunctionDec" in Appel's code *)
133 fundec list
134 | VarDec of
5597e56d 135 { name : Sym.t
28875fec 136 ; escape : bool ref (* Again, why mutable? *)
5597e56d 137 ; typ : (Sym.t * Pos.t) option
28875fec 138 ; init : exp
5597e56d 139 ; pos : Pos.t
28875fec
SK
140 }
141 | TypeDecs of (* "TypeDec" in Appel's code *)
142 typedec list
143and ty =
144 | NameTy of
5597e56d
SK
145 { symbol : Sym.t
146 ; pos : Pos.t
28875fec
SK
147 }
148 | RecordTy of
149 field list
150 | ArrayTy of
5597e56d
SK
151 { symbol : Sym.t
152 ; pos : Pos.t
28875fec
SK
153 }
154and field =
155 | Field of
5597e56d 156 { name : Sym.t
28875fec 157 ; escape : bool ref
5597e56d
SK
158 ; typ : Sym.t
159 ; pos : Pos.t
28875fec
SK
160 }
161and typedec =
162 | TypeDec of (* An anonymous record in Appel's code *)
5597e56d 163 { name : Sym.t
28875fec 164 ; ty : ty
5597e56d 165 ; pos : Pos.t
28875fec
SK
166 }
167and fundec =
168 | FunDec of
5597e56d 169 { name : Sym.t
28875fec 170 ; params : field list
5597e56d 171 ; result : (Sym.t * Pos.t) option
28875fec 172 ; body : exp
5597e56d 173 ; pos : Pos.t
28875fec
SK
174 }
175
176type t = exp
177
e7b4c94e
SK
178let op_to_string op =
179 match op with
5597e56d
SK
180 | PlusOp -> "PlusOp"
181 | MinusOp -> "MinusOp"
182 | TimesOp -> "TimesOp"
183 | DivideOp -> "DivideOp"
184 | EqOp -> "EqOp"
185 | NeqOp -> "NeqOp"
186 | LtOp -> "LtOp"
187 | LeOp -> "LeOp"
188 | GtOp -> "GtOp"
189 | GeOp -> "GeOp"
190
e7b4c94e
SK
191let xs_to_string ?(sep=",") ~f ~indent xs =
192 let i = Indent.to_string indent in
193 xs |> List.map ~f:(fun x -> i ^ (f x)) |> String.concat ~sep
194
195let mexp name params ~indent =
196 let params = xs_to_string ~f:(fun x -> x) ~indent params in
197 sprintf "%s[%s]" name params
198
199let field_to_string ~indent (Field {name; typ; _}) =
200 let name = Sym.to_string name in
201 let typ = Sym.to_string typ in
202 let indent = Indent.to_string indent in
203 sprintf "%s%s : %s" indent name typ
5597e56d 204
e7b4c94e
SK
205let fields_to_string fields ~indent =
206 let fields = List.map fields ~f:(field_to_string ~indent) in
207 mexp "" fields ~indent
5597e56d 208
e7b4c94e
SK
209let rec exp_to_string ~indent exp =
210 let indent = Indent.next indent in
211 let mexp = mexp ~indent in
5597e56d
SK
212 (match exp with
213 | NilExp ->
e7b4c94e 214 mexp "NilExp" []
5597e56d 215 | IntExp i ->
e7b4c94e 216 mexp "IntExp" [(string_of_int i)]
5597e56d 217 | StringExp {string; _} ->
e7b4c94e 218 mexp "StringExp" [sprintf "%S" string]
5597e56d
SK
219 | CallExp {func; args; _} ->
220 let func = Sym.to_string func in
e7b4c94e
SK
221 let args = List.map args ~f:(exp_to_string ~indent) in
222 mexp "CallExp" [func; mexp "" args]
5597e56d 223 | OpExp {left; oper; right; _} ->
e7b4c94e
SK
224 let op_exp =
225 let indent = Indent.next indent in
226 let oper = op_to_string oper in
227 let left = exp_to_string ~indent left in
228 let right = exp_to_string ~indent right in
229 mexp oper [left; right]
230 in
231 mexp "OpExp" [op_exp]
5597e56d
SK
232 | RecordExp {fields; typ; _} ->
233 let fields =
e7b4c94e
SK
234 List.map fields ~f:(fun (sym, exp, _) ->
235 sprintf
236 "%s = %s"
237 (Sym.to_string sym)
238 (exp_to_string ~indent exp)
239 )
5597e56d
SK
240 in
241 let typ = Sym.to_string typ in
e7b4c94e 242 mexp "RecordExp" [typ; mexp "" fields]
5597e56d
SK
243 | SeqExp exps ->
244 exps
e7b4c94e
SK
245 |> List.map ~f:(fun (e, _) -> exp_to_string e ~indent)
246 |> mexp "SeqExp"
5597e56d 247 | AssignExp {var; exp; _} ->
e7b4c94e
SK
248 let var = var_to_string ~indent var in
249 let exp = exp_to_string ~indent exp in
250 mexp "AssignExp" [var; exp]
5597e56d 251 | IfExp {test; then'; else'; _} ->
e7b4c94e
SK
252 let test = exp_to_string ~indent test in
253 let then' = exp_to_string ~indent then' in
5597e56d 254 (match else' with
e7b4c94e
SK
255 | None ->
256 mexp "IfThen" [test; then']
257 | Some e ->
258 mexp "IfThenElse" [test; then'; (exp_to_string ~indent e)]
5597e56d
SK
259 )
260 | WhileExp {test; body; _} ->
e7b4c94e
SK
261 let test = exp_to_string ~indent test in
262 let body = exp_to_string ~indent body in
263 mexp "WhileExp" [test; body]
5597e56d 264 | ForExp {var; lo; hi; body; _} ->
e7b4c94e
SK
265 mexp "ForExp"
266 [ (Sym.to_string var)
267 ; (exp_to_string ~indent lo)
268 ; (exp_to_string ~indent hi)
269 ; (exp_to_string ~indent body)
270 ]
5597e56d 271 | BreakExp _ ->
e7b4c94e 272 mexp "BreakExp" []
5597e56d 273 | LetExp {decs; body; _} ->
e7b4c94e
SK
274 let decs = List.map decs ~f:(dec_to_string ~indent) in
275 let body = exp_to_string ~indent body in
276 mexp "LetExp" [mexp "" decs; body]
5597e56d
SK
277 | ArrayExp {typ; size; init; _} ->
278 let typ = Sym.to_string typ in
e7b4c94e
SK
279 let size = exp_to_string ~indent size in
280 let init = exp_to_string ~indent init in
281 mexp "ArrayExp" [typ; size; init]
5597e56d 282 | VarExp var ->
e7b4c94e 283 mexp "VarExp" [(var_to_string ~indent var)]
5597e56d 284 )
e7b4c94e
SK
285and var_to_string ~indent var =
286 let indent = Indent.next indent in
287 let mexp = mexp ~indent in
288 match var with
5597e56d 289 | SimpleVar {symbol; _} ->
e7b4c94e 290 mexp "SimpleVar" [(Sym.to_string symbol)]
5597e56d 291 | FieldVar {var; symbol; _} ->
e7b4c94e
SK
292 mexp "FieldVar"
293 [ (var_to_string ~indent var)
294 ; (Sym.to_string symbol)
295 ]
5597e56d 296 | SubscriptVar {var; exp; _} ->
e7b4c94e
SK
297 mexp "SubscriptVar[%s]"
298 [ (var_to_string ~indent var)
299 ; (exp_to_string ~indent exp)
300 ]
301and dec_to_string ~indent dec =
302 let indent = Indent.next indent in
303 let mexp = mexp ~indent in
304 match dec with
5597e56d
SK
305 | VarDec {name; typ; init; _} ->
306 let name = Sym.to_string name in
e7b4c94e 307 let init = exp_to_string ~indent init in
5597e56d
SK
308 (match typ with
309 | Some (typ, _) ->
310 let typ = Sym.to_string typ in
e7b4c94e 311 mexp "VarDec" [name; typ; init]
5597e56d 312 | None ->
e7b4c94e 313 mexp "VarDec" [name; init]
5597e56d
SK
314 )
315 | TypeDecs type_decs ->
e7b4c94e
SK
316 mexp "TypeDecs"
317 (List.map type_decs ~f:(type_dec_to_string ~indent))
5597e56d 318 | FunDecs fun_decs ->
e7b4c94e
SK
319 mexp "FunDecs"
320 (List.map fun_decs ~f:(fun_dec_to_string ~indent))
321and fun_dec_to_string ~indent fun_dec =
322 let indent = Indent.next indent in
323 let mexp = mexp ~indent in
324 match fun_dec with
5597e56d
SK
325 | FunDec {name; params; body; _} ->
326 let name = Sym.to_string name in
e7b4c94e
SK
327 let params = fields_to_string ~indent params in
328 let body = exp_to_string ~indent body in
329 mexp "FunDec" [name; params; body]
330and type_dec_to_string ~indent type_dec =
331 let indent = Indent.next indent in
332 let mexp = mexp ~indent in
333 match type_dec with
5597e56d 334 | TypeDec {name; ty; _} ->
e7b4c94e
SK
335 mexp "TypeDec"
336 [ (Sym.to_string name)
337 ; (ty_to_string ~indent ty)
338 ]
339and ty_to_string ~indent ty =
340 let mexp = mexp ~indent in
341 match ty with
342 | NameTy {symbol; _} -> mexp "NameTy" [(Sym.to_string symbol)]
343 | ArrayTy {symbol; _} -> mexp "ArrayTy" [(Sym.to_string symbol)]
344 | RecordTy fields -> mexp "RecordTy" [(fields_to_string ~indent fields)]
5597e56d 345
e7b4c94e
SK
346let to_string =
347 let unit = String.make 4 ' ' in
348 let indent = Indent.init ~enabled:true ~unit in
349 exp_to_string ~indent
This page took 0.076822 seconds and 4 git commands to generate.