Sketch-out a dummy escape-finding module
[tiger.ml.git] / compiler / src / lib / tiger / tiger_semant.ml
1 module List = ListLabels
2
3 module A = Tiger_absyn
4 module Dag = Tiger_dag
5 module Env = Tiger_env
6 module E = Tiger_error
7 module Escape = Tiger_semant_escape
8 module Pos = Tiger_position
9 module Sym = Tiger_symbol
10 module Translate = Tiger_translate
11 module Type = Tiger_env_type
12 module Value = Tiger_env_value
13
14 (* The only reason for having this seemingly-superfluous inner module is to
15 * have this nice signature as a summary of what each function does. *)
16 module Semant : sig
17 type expty =
18 { exp : Translate.exp
19 ; ty : Type.t
20 }
21
22 (* Violating normal naming convention just to make it easier to follow
23 * Appel's
24 *)
25 val transExp : env:Env.t -> A.exp -> expty
26
27 (* transVar does not seem to be needed, as trvar handles all our cases.
28 * Am I wrong?
29 *
30 * val transVar : env:Env.t -> A.var -> expty
31 *
32 *)
33 end = struct
34 type expty =
35 { exp : Translate.exp
36 ; ty : Type.t
37 }
38
39 let rec actual_ty ty ~pos =
40 match ty with
41 | Type.Name (name, ty_opt_ref) ->
42 (match !ty_opt_ref with
43 | None ->
44 E.raise (E.Unknown_type {ty_id=name; pos})
45 | Some ty ->
46 actual_ty ty ~pos
47 )
48 | Type.Unit
49 | Type.Nil
50 | Type.Int
51 | Type.String
52 | Type.Record _
53 | Type.Array _ ->
54 ty
55
56 let return ty = {exp = (); ty}
57 let return_unit = return Type.Unit
58 let return_nil = return Type.Nil
59 let return_int = return Type.Int
60 let return_string = return Type.String
61
62 let env_get_typ ~sym ~env ~pos : Type.t =
63 match Env.get_typ env sym with
64 | Some ty -> ty
65 | None -> E.raise (E.Unknown_type {ty_id=sym; pos})
66
67 let env_get_typ_actual ~sym ~env ~pos : Type.t =
68 actual_ty (env_get_typ ~sym ~env ~pos) ~pos
69
70 let env_get_val ~sym ~env ~pos : Value.t =
71 match Env.get_val env sym with
72 | Some ty -> ty
73 | None -> E.raise (E.Unknown_id {id=sym; pos})
74
75 let check_same {exp=_; ty=ty_left} {exp=_; ty=ty_right} ~pos : unit =
76 if Type.is_equal ty_left ty_right then
77 ()
78 else
79 E.raise (E.Wrong_type {expected=ty_left; given=ty_right; pos})
80
81 let check_int expty ~pos : unit =
82 check_same return_int expty ~pos
83
84 let paths_of_typedecs typedecs : (Sym.t * Sym.t * Pos.t) list list =
85 let (path, paths) =
86 List.fold_left typedecs ~init:([], []) ~f:(
87 fun (path, paths) (A.TypeDec {name=child; ty; pos}) ->
88 match ty with
89 | A.NameTy {symbol=parent; _} ->
90 (((parent, child, pos) :: path), paths)
91 | A.RecordTy _
92 | A.ArrayTy _ ->
93 ([], path :: paths)
94 )
95 in
96 List.map (path :: paths) ~f:List.rev
97
98 let check_cycles (typedecs : A.typedec list) : unit =
99 let non_empty_paths =
100 List.filter
101 (paths_of_typedecs typedecs)
102 ~f:(function [] -> false | _ -> true)
103 in
104 List.iter non_empty_paths ~f:(
105 fun path ->
106 match Dag.of_list (List.map path ~f:(fun (p, c, _) -> (p, c))) with
107 | Ok _ ->
108 ()
109 | Error `Cycle ->
110 let (_, from_id, from_pos) = List.hd path in
111 let (_, to_id, to_pos) = List.hd (List.rev path) in
112 E.raise (E.Cycle_in_type_decs {from_id; from_pos; to_id; to_pos})
113 )
114
115 let rec transExp ~env exp =
116 let rec trexp exp =
117 (match exp with
118 | A.NilExp ->
119 return_nil
120 | A.IntExp _ ->
121 return_int
122 | A.StringExp {string=_; _} ->
123 return_string
124 | A.CallExp {func; args; pos} ->
125 (match env_get_val ~sym:func ~env ~pos with
126 | Value.Fun {formals; result} ->
127 let expected = List.length formals in
128 let given = List.length args in
129 if given = expected then
130 begin
131 List.iter2 formals args ~f:(fun ty_expected exp_given ->
132 check_same
133 (return (actual_ty ~pos ty_expected))
134 (trexp exp_given)
135 ~pos;
136 );
137 return (actual_ty ~pos result)
138 end
139 else
140 E.raise (E.Wrong_number_of_args {func; expected; given; pos})
141 | Value.Var _ ->
142 E.raise (E.Id_not_a_function {id=func; pos})
143 )
144 | A.OpExp {oper; left; right; pos} ->
145 trop oper ~left ~right ~pos
146 | A.RecordExp {fields=field_exps; typ; pos} ->
147 let ty = env_get_typ_actual ~sym:typ ~env ~pos in
148 Type.if_record
149 ty
150 ~f:(fun field_tys ->
151 List.iter field_exps ~f:(fun (field, exp, pos) ->
152 (match List.assoc_opt field field_tys with
153 | Some field_ty ->
154 check_same (return (actual_ty ~pos field_ty)) (trexp exp) ~pos
155 | None ->
156 E.raise
157 (E.No_such_field_in_record {field; record=ty; pos})
158 )
159 )
160 )
161 ~otherwise:(fun () ->
162 E.raise (E.Wrong_type_used_as_record {ty_id=typ; ty; pos})
163 );
164 return (actual_ty ~pos ty)
165 | A.SeqExp [] ->
166 return_unit
167 | A.SeqExp exps ->
168 let last xs =
169 xs
170 |> List.rev (* Yes, redundant, but clean-looking ;-P *)
171 |> List.hd (* Empty is matched in above SeqExp match case *)
172 in
173 exps
174 |> List.map ~f:(fun (exp, _) -> trexp exp)
175 |> last
176 | A.AssignExp {var; exp; pos} ->
177 check_same (trvar var) (trexp exp) ~pos;
178 (* TODO: Add var->exp to val env? *)
179 return_unit
180 | A.IfExp {test; then'; else'; pos} ->
181 (* test : must be int, because we have no bool *)
182 (* then : must equal else *)
183 (* else : must equal then or be None *)
184 check_int (trexp test) ~pos;
185 (match (trexp then', else') with
186 | expty_then, None ->
187 expty_then
188 | expty_then, Some else' ->
189 let expty_else = trexp else' in
190 check_same expty_then expty_else ~pos;
191 expty_then
192 )
193 | A.WhileExp {test; body; pos} ->
194 (* test : must be int, because we have no bool *)
195 check_int (trexp test) ~pos;
196 let (loop, env) = Env.loop_begin env in
197 (* Only care if an error is raised *)
198 ignore (transExp ~env body);
199 ignore (Env.loop_end env loop);
200 return_unit
201 | A.ForExp {var; lo; hi; body; pos; escape=_} ->
202 check_int (trexp lo) ~pos;
203 check_int (trexp hi) ~pos;
204 let (loop, env) = Env.loop_begin env in
205 let env = Env.set_val env var (Value.Var {ty = Type.Int}) in
206 (* Only care if an error is raised *)
207 ignore (transExp ~env body);
208 ignore (Env.loop_end env loop);
209 return_unit
210 | A.BreakExp pos ->
211 (match Env.loop_current env with
212 | Some _ -> ()
213 | None -> E.raise (E.Break_outside_loop pos)
214 );
215 return_unit
216 | A.LetExp {decs; body; pos=_} ->
217 (* (1) decs augment env *)
218 (* (2) body checked against the new env *)
219 let env =
220 List.fold_left decs ~init:env ~f:(fun env dec -> transDec dec ~env)
221 in
222 transExp body ~env
223 | A.ArrayExp {typ; size; init; pos} ->
224 check_int (trexp size) ~pos;
225 let ty = env_get_typ_actual ~sym:typ ~env ~pos in
226 Type.if_array
227 ty
228 ~f:(fun ty_elements ->
229 check_same (return (actual_ty ~pos ty_elements)) (trexp init) ~pos
230 )
231 ~otherwise:(fun () ->
232 E.raise (E.Wrong_type_used_as_array {ty_id=typ; ty; pos})
233 );
234 return (actual_ty ~pos ty)
235 | A.VarExp var ->
236 trvar var
237 )
238 and trvar =
239 (function
240 | A.SimpleVar {symbol=sym; pos} ->
241 (match env_get_val ~sym ~env ~pos with
242 | Value.Fun _ -> E.raise (E.Id_is_a_function {id=sym; pos})
243 | Value.Var {ty} -> return (actual_ty ~pos ty)
244 )
245 | A.FieldVar {var; symbol; pos} ->
246 let {exp=_; ty} = trvar var in
247 Type.if_record
248 ty
249 ~f:(fun fields ->
250 (match List.assoc_opt symbol fields with
251 | None ->
252 E.raise
253 (E.No_such_field_in_record {field=symbol; record=ty; pos})
254 | Some ty ->
255 return (actual_ty ~pos ty)
256 )
257 )
258 ~otherwise:(fun () -> E.raise (E.Exp_not_a_record {ty; pos}))
259 | A.SubscriptVar {var; exp; pos} ->
260 let {exp=_; ty} = trvar var in
261 check_int (trexp exp) ~pos;
262 Type.if_array
263 ty
264 ~f:(fun ty_elements -> return (actual_ty ~pos ty_elements))
265 ~otherwise:(fun () -> E.raise (E.Exp_not_an_array {ty; pos}))
266 )
267 and trop oper ~left ~right ~pos =
268 (* TODO: Refactor trop - all opers return bool/int *)
269 let expty_left = trexp left in
270 let expty_right = trexp right in
271 check_same expty_left expty_right ~pos;
272 let {exp=_; ty} = expty_left in
273 let module T = Type in
274 (match oper with
275 (* Arithmetic: int *)
276 | A.PlusOp
277 | A.MinusOp
278 | A.TimesOp
279 | A.DivideOp ->
280 check_int expty_left ~pos;
281 return_int
282 (* Equality: int, string, array, record *)
283 | A.EqOp
284 | A.NeqOp ->
285 if (T.is_int ty)
286 || (T.is_string ty)
287 || (T.is_array ty)
288 || (T.is_record ty)
289 then
290 return_int (* Because we have no bool type *)
291 else
292 E.raise (E.Invalid_operand_type
293 { oper
294 ; valid = ["int"; "string"; "array"; "record"]
295 ; given = ty
296 ; pos
297 })
298 (* Order: int, string *)
299 | A.LtOp
300 | A.LeOp
301 | A.GtOp
302 | A.GeOp ->
303 if (T.is_int ty)
304 || (T.is_string ty)
305 then
306 return_int (* Because we have no bool type *)
307 else
308 E.raise (E.Invalid_operand_type
309 { oper
310 ; valid = ["int"; "string"]
311 ; given = ty
312 ; pos
313 })
314 )
315 in
316 trexp exp
317 and transDec ~(env : Env.t) (dec : A.dec) : Env.t =
318 (match dec with
319 | A.VarDec {name; typ=typ_opt; init; pos=pos_outter; escape=_} ->
320 let ty =
321 (match (typ_opt, transExp ~env init) with
322 | None, {ty; exp=()} ->
323 ty
324 | Some (sym, pos_inner), expty_init ->
325 let ty = env_get_typ_actual ~sym ~env ~pos:pos_inner in
326 check_same (return ty) expty_init ~pos:pos_outter;
327 ty
328 )
329 in
330 Env.set_val env name (Value.Var {ty})
331 | A.TypeDecs typedecs ->
332 check_cycles typedecs;
333 let env =
334 List.fold_left typedecs ~init:env ~f:(
335 fun env (A.TypeDec {name; ty=_; pos=_}) ->
336 Env.set_typ env name (Type.Name (name, ref None))
337 )
338 in
339 List.iter typedecs ~f:(fun (A.TypeDec {name=ty_name; ty=ty_exp; pos}) ->
340 let ty = transTy ~env ~ty_name ~ty_exp in
341 (match env_get_typ ~sym:ty_name ~env ~pos with
342 | Type.Name (_, ty_opt_ref) ->
343 ty_opt_ref := Some ty
344 | Type.Unit
345 | Type.Nil
346 | Type.Int
347 | Type.String
348 | Type.Record _
349 | Type.Array _ ->
350 ()
351 )
352 );
353 env
354 | A.FunDecs fundecs ->
355 let env_with_fun_heads_only =
356 List.fold_left fundecs ~init:env ~f:(
357 fun env (A.FunDec {name; params; result; body=_; pos=_}) ->
358 let formals =
359 List.map params ~f:(
360 fun (A.Field {name=_; typ; pos; escape=_}) ->
361 env_get_typ_actual ~env ~sym:typ ~pos
362 )
363 in
364 let result =
365 match result with
366 | Some (s, p) -> env_get_typ_actual ~sym:s ~env ~pos:p
367 | None -> Type.Unit
368 in
369 Env.set_val env name (Value.Fun {formals; result})
370 )
371 in
372 List.iter fundecs ~f:(
373 fun (A.FunDec {name=_; params; result=_; body; pos=_}) ->
374 let env_with_fun_heads_and_local_vars =
375 List.fold_left params ~init:env_with_fun_heads_only ~f:(
376 fun env (A.Field {name=var_name; escape=_; typ; pos}) ->
377 let var_ty = env_get_typ_actual ~env ~sym:typ ~pos in
378 Env.set_val env var_name (Value.Var {ty = var_ty})
379 )
380 in
381 (* we only care if an exception is raised *)
382 ignore (transExp ~env:env_with_fun_heads_and_local_vars body);
383 );
384 env_with_fun_heads_only
385 )
386 and transTy ~(env : Env.t) ~ty_name ~(ty_exp : A.ty) : Type.t =
387 (match ty_exp with
388 | A.NameTy {symbol=sym; pos} ->
389 env_get_typ ~sym ~env ~pos
390 | A.RecordTy fields ->
391 let fields =
392 List.map fields ~f:(fun (A.Field {name; escape=_; typ; pos}) ->
393 let ty = env_get_typ ~sym:typ ~env ~pos in
394 (name, ty)
395 )
396 in
397 Type.new_record ~name:ty_name ~fields
398 | A.ArrayTy {symbol=sym; pos} ->
399 let element_ty = env_get_typ ~sym ~env ~pos in
400 Type.new_array ~name:ty_name ~ty:element_ty
401 )
402 end
403
404 open Semant
405
406 let transProg absyn =
407 Escape.find absyn;
408 let {exp = _; ty = _} = transExp absyn ~env:Env.base in
409 ()
This page took 0.080759 seconds and 4 git commands to generate.