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