X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Ftypecheck%2FInst.lhs;h=1032f91c60acd8f85bd7623b3f3abc9243fdcffe;hp=e175951d9517375c49fa56cd60115f7e8ea319e9;hb=6a05ec5ef5373f61b7f9f5bdc344483417fa801b;hpb=66c58d1c46338135abdb76a86c7342fab005a988 diff --git a/compiler/typecheck/Inst.lhs b/compiler/typecheck/Inst.lhs index e175951..1032f91 100644 --- a/compiler/typecheck/Inst.lhs +++ b/compiler/typecheck/Inst.lhs @@ -42,7 +42,8 @@ module Inst ( isTyVarDict, isMethodFor, zonkInst, zonkInsts, - instToId, instToVar, instType, instName, + instToId, instToVar, instType, instName, instToDictBind, + addInstToDictBind, InstOrigin(..), InstLoc, pprInstLoc, @@ -91,6 +92,7 @@ import PrelNames import BasicTypes import SrcLoc import DynFlags +import Bag import Maybes import Util import Outputable @@ -205,6 +207,15 @@ tyVarsOfInst (EqInst {tci_left = ty1, tci_right = ty2}) = tyVarsOfType ty1 `unio tyVarsOfInsts insts = foldr (unionVarSet . tyVarsOfInst) emptyVarSet insts tyVarsOfLIE lie = tyVarsOfInsts (lieToList lie) + + +-------------------------- +instToDictBind :: Inst -> LHsExpr TcId -> TcDictBinds +instToDictBind inst rhs + = unitBag (L (instSpan inst) (VarBind (instToId inst) rhs)) + +addInstToDictBind :: TcDictBinds -> Inst -> LHsExpr TcId -> TcDictBinds +addInstToDictBind binds inst rhs = binds `unionBags` instToDictBind inst rhs \end{code} Predicates @@ -765,7 +776,7 @@ lookupSimpleInst (Method {tci_oid = id, tci_tys = tys, tci_theta = theta, tci_lo -- [Same shortcut as in newOverloadedLit, but we -- may have done some unification by now] -lookupSimpleInst (LitInst {tci_lit = HsIntegral i from_integer_name, tci_ty = ty, tci_loc = loc}) +lookupSimpleInst (LitInst {tci_lit = HsIntegral i from_integer_name _, tci_ty = ty, tci_loc = loc}) | Just expr <- shortCutIntLit i ty = returnM (GenInst [] (noLoc expr)) | otherwise @@ -777,7 +788,7 @@ lookupSimpleInst (LitInst {tci_lit = HsIntegral i from_integer_name, tci_ty = ty (mkHsApp (L (instLocSpan loc) (HsVar (instToId method_inst))) integer_lit)) -lookupSimpleInst (LitInst {tci_lit = HsFractional f from_rat_name, tci_ty = ty, tci_loc = loc}) +lookupSimpleInst (LitInst {tci_lit = HsFractional f from_rat_name _, tci_ty = ty, tci_loc = loc}) | Just expr <- shortCutFracLit f ty = returnM (GenInst [] (noLoc expr)) @@ -789,7 +800,7 @@ lookupSimpleInst (LitInst {tci_lit = HsFractional f from_rat_name, tci_ty = ty, returnM (GenInst [method_inst] (mkHsApp (L (instLocSpan loc) (HsVar (instToId method_inst))) rat_lit)) -lookupSimpleInst (LitInst {tci_lit = HsIsString s from_string_name, tci_ty = ty, tci_loc = loc}) +lookupSimpleInst (LitInst {tci_lit = HsIsString s from_string_name _, tci_ty = ty, tci_loc = loc}) | Just expr <- shortCutStringLit s ty = returnM (GenInst [] (noLoc expr)) | otherwise @@ -979,11 +990,10 @@ fromWantedCo :: String -> Either TcTyVar Coercion -> TcTyVar fromWantedCo _ (Left covar) = covar fromWantedCo msg _ = panic ("fromWantedCo: not a wanted coercion: " ++ msg) -eitherEqInst - :: Inst -- given or wanted EqInst - -> (TcTyVar -> a) -- result if wanted - -> (Coercion -> a) -- result if given - -> a +eitherEqInst :: Inst -- given or wanted EqInst + -> (TcTyVar -> a) -- result if wanted + -> (Coercion -> a) -- result if given + -> a eitherEqInst (EqInst {tci_co = either_co}) withWanted withGiven = case either_co of Left covar -> withWanted covar @@ -1006,7 +1016,7 @@ mkEqInst (EqPred ty1 ty2) co mkWantedEqInst :: PredType -> TcM Inst mkWantedEqInst pred@(EqPred ty1 ty2) - = do { cotv <- newMetaTyVar TauTv (mkCoKind ty1 ty2) + = do { cotv <- newMetaCoVar ty1 ty2 ; mkEqInst pred (Left cotv) }