X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Ftypecheck%2FTcRnTypes.lhs;h=2bb80bcad1063cb586427991bd457c948c9926be;hp=b14cab5eb7489fd93cd42635631481ca4de4f8c0;hb=311b1cdfc9b1c311cc53482c461c18cba8885b2a;hpb=b00b5bc04ff36a551552470060064f0b7d84ca30 diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index b14cab5..2bb80bc 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1,4 +1,5 @@ % +% (c) The University of Glasgow 2006 % (c) The GRASP Project, Glasgow University, 1992-2002 % \begin{code} @@ -41,40 +42,34 @@ module TcRnTypes( #include "HsVersions.h" -import HsSyn ( PendingSplice, HsOverLit, LRuleDecl, LForeignDecl, - ArithSeqInfo, DictBinds, LHsBinds, LImportDecl, HsGroup, - HsWrapper, IE, HsDoc, HaddockModInfo ) -import HscTypes ( FixityEnv, - HscEnv, TypeEnv, TyThing, - GenAvailInfo(..), AvailInfo, HscSource(..), - availName, IsBootInterface, Deprecations ) -import Packages ( PackageId ) -import Type ( Type, pprTyThingCategory ) -import TcType ( TcTyVarSet, TcType, TcThetaType, SkolemInfo, - TcPredType, TcKind, tcCmpPred, tcCmpType, - tcCmpTypes, pprSkolInfo ) -import InstEnv ( Instance, InstEnv ) -import FamInstEnv ( FamInst, FamInstEnv ) +import HsSyn hiding (LIE) +import HscTypes +import Packages +import Type +import TcType +import InstEnv +import FamInstEnv import IOEnv -import RdrName ( GlobalRdrEnv, LocalRdrEnv ) -import Name ( Name ) +import RdrName +import Name import NameEnv -import NameSet ( NameSet, unionNameSets, DefUses ) -import Var ( Id, TyVar ) -import VarEnv ( TidyEnv ) +import NameSet +import Var +import VarEnv import Module import UniqFM -import SrcLoc ( SrcSpan, SrcLoc, Located, srcSpanStart ) -import VarSet ( IdSet ) -import ErrUtils ( Messages, Message ) -import UniqSupply ( UniqSupply ) -import BasicTypes ( IPName ) -import Util ( thenCmp ) +import SrcLoc +import VarSet +import ErrUtils +import UniqSupply +import BasicTypes +import Util import Bag import Outputable -import Maybe ( mapMaybe ) -import ListSetOps ( unionLists ) -import Data.List ( nub ) +import ListSetOps + +import Data.Maybe +import Data.List \end{code} @@ -534,7 +529,12 @@ data ImportAvails -- modules imported from other packages. imp_orphs :: [Module], - -- Orphan modules below us in the import tree + -- Orphan modules below us in the import tree (and maybe + -- including us for imported modules) + + imp_finsts :: [Module], + -- Family instance modules below us in the import tree (and + -- maybe including us for imported modules) imp_parent :: NameEnv AvailInfo -- for the names in scope in this module, tells us @@ -555,21 +555,25 @@ emptyImportAvails = ImportAvails { imp_env = emptyUFM, imp_dep_mods = emptyUFM, imp_dep_pkgs = [], imp_orphs = [], + imp_finsts = [], imp_parent = emptyNameEnv } plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails plusImportAvails (ImportAvails { imp_env = env1, imp_mods = mods1, imp_dep_mods = dmods1, imp_dep_pkgs = dpkgs1, - imp_orphs = orphs1, imp_parent = parent1 }) + imp_orphs = orphs1, imp_finsts = finsts1, + imp_parent = parent1 }) (ImportAvails { imp_env = env2, imp_mods = mods2, imp_dep_mods = dmods2, imp_dep_pkgs = dpkgs2, - imp_orphs = orphs2, imp_parent = parent2 }) + imp_orphs = orphs2, imp_finsts = finsts2, + imp_parent = parent2 }) = ImportAvails { imp_env = plusUFM_C (++) env1 env2, imp_mods = mods1 `plusModuleEnv` mods2, imp_dep_mods = plusUFM_C plus_mod_dep dmods1 dmods2, imp_dep_pkgs = dpkgs1 `unionLists` dpkgs2, imp_orphs = orphs1 `unionLists` orphs2, + imp_finsts = finsts1 `unionLists` finsts2, imp_parent = plusNameEnv_C plus_avails parent1 parent2 } where plus_avails (AvailTC tc subs1) (AvailTC _ subs2) @@ -685,48 +689,52 @@ type Int, represented by \begin{code} data Inst - = Dict - Name - TcPredType - InstLoc - - | Method - Id - - TcId -- The overloaded function - -- This function will be a global, local, or ClassOpId; - -- inside instance decls (only) it can also be an InstId! - -- The id needn't be completely polymorphic. - -- You'll probably find its name (for documentation purposes) - -- inside the InstOrigin - - [TcType] -- The types to which its polymorphic tyvars - -- should be instantiated. - -- These types must saturate the Id's foralls. - - TcThetaType -- The (types of the) dictionaries to which the function - -- must be applied to get the method + = Dict { + tci_name :: Name, + tci_pred :: TcPredType, + tci_loc :: InstLoc + } + + | Method { + tci_id :: TcId, -- The Id for the Inst - InstLoc + tci_oid :: TcId, -- The overloaded function + -- This function will be a global, local, or ClassOpId; + -- inside instance decls (only) it can also be an InstId! + -- The id needn't be completely polymorphic. + -- You'll probably find its name (for documentation purposes) + -- inside the InstOrigin - -- INVARIANT 1: in (Method u f tys theta tau loc) - -- type of (f tys dicts(from theta)) = tau + tci_tys :: [TcType], -- The types to which its polymorphic tyvars + -- should be instantiated. + -- These types must saturate the Id's foralls. - -- INVARIANT 2: tau must not be of form (Pred -> Tau) + tci_theta :: TcThetaType, + -- The (types of the) dictionaries to which the function + -- must be applied to get the method + + tci_loc :: InstLoc + } + -- INVARIANT 1: in (Method m f tys theta tau loc) + -- type of m = type of (f tys dicts(from theta)) + + -- INVARIANT 2: type of m must not be of form (Pred -> Tau) -- Reason: two methods are considered equal if the -- base Id matches, and the instantiating types -- match. The TcThetaType should then match too. -- This only bites in the call to tcInstClassOp in TcClassDcl.mkMethodBind - | LitInst - Name - (HsOverLit Name) -- The literal from the occurrence site - -- INVARIANT: never a rebindable-syntax literal - -- Reason: tcSyntaxName does unification, and we - -- don't want to deal with that during tcSimplify, - -- when resolving LitInsts - TcType -- The type at which the literal is used - InstLoc + | LitInst { + tci_name :: Name, + tci_lit :: HsOverLit Name, -- The literal from the occurrence site + -- INVARIANT: never a rebindable-syntax literal + -- Reason: tcSyntaxName does unification, and we + -- don't want to deal with that during tcSimplify, + -- when resolving LitInsts + + tci_ty :: TcType, -- The type at which the literal is used + tci_loc :: InstLoc + } \end{code} @Insts@ are ordered by their class/type info, rather than by their @@ -742,16 +750,18 @@ instance Eq Inst where EQ -> True other -> False -cmpInst (Dict _ pred1 _) (Dict _ pred2 _) = pred1 `tcCmpPred` pred2 -cmpInst (Dict _ _ _) other = LT +cmpInst d1@(Dict {}) d2@(Dict {}) = tci_pred d1 `tcCmpPred` tci_pred d2 +cmpInst (Dict {}) other = LT -cmpInst (Method _ _ _ _ _) (Dict _ _ _) = GT -cmpInst (Method _ id1 tys1 _ _) (Method _ id2 tys2 _ _) = (id1 `compare` id2) `thenCmp` (tys1 `tcCmpTypes` tys2) -cmpInst (Method _ _ _ _ _) other = LT +cmpInst (Method {}) (Dict {}) = GT +cmpInst m1@(Method {}) m2@(Method {}) = (tci_oid m1 `compare` tci_oid m2) `thenCmp` + (tci_tys m1 `tcCmpTypes` tci_tys m2) +cmpInst (Method {}) other = LT -cmpInst (LitInst _ _ _ _) (Dict _ _ _) = GT -cmpInst (LitInst _ _ _ _) (Method _ _ _ _ _) = GT -cmpInst (LitInst _ lit1 ty1 _) (LitInst _ lit2 ty2 _) = (lit1 `compare` lit2) `thenCmp` (ty1 `tcCmpType` ty2) +cmpInst (LitInst {}) (Dict {}) = GT +cmpInst (LitInst {}) (Method {}) = GT +cmpInst l1@(LitInst {}) l2@(LitInst {}) = (tci_lit l1 `compare` tci_lit l2) `thenCmp` + (tci_ty l1 `tcCmpType` tci_ty l2) \end{code}