(* HCoop Domtool (http://hcoop.sourceforge.net/) * Copyright (c) 2006, Adam Chlipala * * This program is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * This program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program; if not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. *) (* Domtool configuration language type checking *) structure Tycheck :> TYCHECK = struct open Ast Print structure SM = StringMap type env = typ SM.map val empty = SM.empty local val unifCount = ref 0 in fun resetUnif () = unifCount := 0 fun newUnif () = let val c = !unifCount val name = if c < 26 then str (chr (ord #"A" + c)) else "UNIF" ^ Int.toString (c - 26) in unifCount := c + 1; TUnif (name, ref NONE) end end exception UnequalDomains fun eqRecord f (r1, r2) = (SM.appi (fn (k, v1) => case SM.find (r2, k) of NONE => raise UnequalDomains | SOME v2 => if f (v1, v2) then () else raise UnequalDomains) r1; SM.appi (fn (k, v2) => case SM.find (r1, k) of NONE => raise UnequalDomains | SOME v1 => if f (v1, v2) then () else raise UnequalDomains) r2; true) handle UnequalDomains => false fun eqPred ((p1, _), (p2, _)) = case (p1, p2) of (CRoot, CRoot) => true | (CConst s1, CConst s2) => s1 = s2 | (CPrefix p1, CPrefix p2) => eqPred (p1, p2) | (CNot p1, CNot p2) => eqPred (p1, p2) | (CAnd (p1, q1), CAnd (p2, q2)) => eqPred (p1, p2) andalso eqPred (q1, q2) | _ => false fun eqTy (t1All as (t1, _), t2All as (t2, _)) = case (t1, t2) of (TBase s1, TBase s2) => s1 = s2 | (TList t1, TList t2) => eqTy (t1, t2) | (TArrow (d1, r1), TArrow (d2, r2)) => eqTy (d1, d2) andalso eqTy (r1, r2) | (TAction (p1, d1, r1), TAction (p2, d2, r2)) => eqPred (p1, p2) andalso eqRecord eqTy (d1, d2) andalso eqRecord eqTy (r1, r2) | (TUnif (_, ref (SOME t1)), _) => eqTy (t1, t2All) | (_, TUnif (_, ref (SOME t2))) => eqTy (t1All, t2) | (TUnif (_, r1), TUnif (_, r2)) => r1 = r2 | (TError, TError) => true | _ => false datatype unification_error = UnifyPred of pred * pred | UnifyTyp of typ * typ | UnifyOccurs of string * typ exception Unify of unification_error datatype type_error = WrongType of string * exp * typ * typ * unification_error option | WrongForm of string * string * exp * typ * unification_error option | UnboundVariable of string fun preface (s, d) = printd (PD.hovBox (PD.PPS.Rel 0, [PD.string s, PD.space 1, d])) fun describe_unification_error t ue = case ue of UnifyPred (p1, p2) => (print "Reason: Incompatible predicates.\n"; preface ("Have:", p_pred p1); preface ("Need:", p_pred p2)) | UnifyTyp (t1, t2) => if eqTy (t, t1) then () else (print "Reason: Incompatible types.\n"; preface ("Have:", p_typ t1); preface ("Need:", p_typ t2)) | UnifyOccurs (name, t') => if eqTy (t, t') then () else (print "Reason: Occurs check failed for "; print name; print " in:\n"; printd (p_typ t)) fun describe_type_error loc te = case te of WrongType (place, e, t1, t2, ueo) => (ErrorMsg.error (SOME loc) (place ^ " has wrong type."); preface (" Expression:", p_exp e); preface ("Actual type:", p_typ t1); preface ("Needed type:", p_typ t2); Option.app (describe_unification_error t1) ueo) | WrongForm (place, form, e, t, ueo) => (ErrorMsg.error (SOME loc) (place ^ " has a non-" ^ form ^ " type."); preface ("Expression:", p_exp e); preface (" Type:", p_typ t); Option.app (describe_unification_error t) ueo) | UnboundVariable name => ErrorMsg.error (SOME loc) ("Unbound variable " ^ name ^ ".\n") fun unifyPred (p1All as (p1, _), p2All as (p2, _)) = case (p1, p2) of (CRoot, CRoot) => () | (CConst s1, CConst s2) => if s1 = s2 then () else raise (Unify (UnifyPred (p1All, p2All))) | (CPrefix p1, CPrefix p2) => unifyPred (p1, p2) | (CNot p1, CNot p2) => unifyPred (p1, p2) | (CAnd (p1, q1), CAnd (p2, q2)) => (unifyPred (p1, p2); unifyPred (q1, q2)) | _ => raise (Unify (UnifyPred (p1All, p2All))) fun unifyRecord f (r1, r2) = (SM.appi (fn (k, v1) => case SM.find (r2, k) of NONE => raise UnequalDomains | SOME v2 => f (v1, v2)) r1; SM.appi (fn (k, v2) => case SM.find (r1, k) of NONE => raise UnequalDomains | SOME v1 => f (v1, v2)) r2) fun occurs u (t, _) = case t of TBase _ => false | TList t => occurs u t | TArrow (d, r) => occurs u d orelse occurs u r | TAction (_, d, r) => List.exists (occurs u) (SM.listItems d) orelse List.exists (occurs u) (SM.listItems r) | TError => false | TUnif (_, ref (SOME t)) => occurs u t | TUnif (_, u') => u = u' fun unify (t1All as (t1, _), t2All as (t2, _)) = case (t1, t2) of (TBase s1, TBase s2) => if s1 = s2 then () else raise Unify (UnifyTyp (t1All, t2All)) | (TList t1, TList t2) => unify (t1, t2) | (TArrow (d1, r1), TArrow (d2, r2)) => (unify (d1, d2); unify (r1, r2)) | (TAction (p1, d1, r1), TAction (p2, d2, r2)) => ((unifyPred (p1, p2); unifyRecord unify (d1, d2); unifyRecord unify (r1, r2)) handle UnequalDomains => raise Unify (UnifyTyp (t1All, t2All))) | (TUnif (_, ref (SOME t1)), _) => unify (t1, t2All) | (_, TUnif (_, ref (SOME t2))) => unify (t1All, t2) | (TUnif (_, r1), TUnif (_, r2)) => if r1 = r2 then () else r1 := SOME t2All | (TUnif (name, r), _) => if occurs r t2All then raise (Unify (UnifyOccurs (name, t2All))) else r := SOME t2All | (_, TUnif (name, r)) => if occurs r t1All then raise (Unify (UnifyOccurs (name, t1All))) else r := SOME t1All | (TError, _) => () | (_, TError) => () | _ => raise Unify (UnifyTyp (t1All, t2All)) fun isError t = case t of (TError, _) => true | _ => false fun checkExp G (eAll as (e, loc)) = let val dte = describe_type_error loc in case e of EInt _ => (TBase "int", loc) | EString _ => (TBase "string", loc) | EList es => let val t = (newUnif (), loc) in foldl (fn (e', ret) => let val t' = checkExp G e' in (unify (t', t); if isError t' then (TList (TError, loc), loc) else ret) handle Unify ue => (dte (WrongType ("List element", e', t', t, SOME ue)); (TError, loc)) end) (TList t, loc) es end | ELam (x, to, e) => let val t = case to of NONE => (newUnif (), loc) | SOME t => t val G' = SM.insert (G, x, t) val t' = checkExp G' e in (TArrow (t, t'), loc) end | EVar x => (case SM.find (G, x) of NONE => (dte (UnboundVariable x); (TError, loc)) | SOME t => t) | EApp (func, arg) => let val dom = (newUnif (), loc) val ran = (newUnif (), loc) val tf = checkExp G func val ta = checkExp G arg in (unify (tf, (TArrow (dom, ran), loc)); unify (ta, dom) handle Unify ue => dte (WrongType ("Function argument", arg, ta, dom, SOME ue)); ran) handle Unify ue => (dte (WrongForm ("Function to be applied", "function", func, tf, SOME ue)); (TError, loc)) end | _ => raise Fail "Not ready for that expression yet!" end exception Ununif fun ununif (tAll as (t, loc)) = case t of TBase _ => tAll | TList t => (TList (ununif t), loc) | TArrow (d, r) => (TArrow (ununif d, ununif r), loc) | TAction (p, d, r) => (TAction (p, SM.map ununif d, SM.map ununif r), loc) | TUnif (_, ref (SOME t)) => ununif t | TError => tAll | TUnif (_, ref NONE) => raise Ununif fun hasError (t, _) = case t of TBase _ => false | TList t => hasError t | TArrow (d, r) => hasError d orelse hasError r | TAction (p, d, r) => List.exists hasError (SM.listItems d) orelse List.exists hasError (SM.listItems r) | TError => false | TUnif (_, ref (SOME t)) => hasError t | TUnif (_, ref NONE) => false fun checkUnit G (eAll as (_, loc)) = let val _ = resetUnif () val t = checkExp G eAll in if hasError t then t else ununif t handle Ununif => (ErrorMsg.error (SOME loc) "Unification variables remain in type:"; printd (p_typ t); t) end end