X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FbasicTypes%2FVar.lhs;h=3c3ff7f44055e84f020fac1ca3d93404760f3152;hp=c1a93707f1a7e6fa3f9240c65b72b7f30e976b05;hb=86add45dbfb6f962b65e371143dd467ae783f9e7;hpb=9ffadf219cbc4f8ec57264786df936a3cee88aec diff --git a/compiler/basicTypes/Var.lhs b/compiler/basicTypes/Var.lhs index c1a9370..3c3ff7f 100644 --- a/compiler/basicTypes/Var.lhs +++ b/compiler/basicTypes/Var.lhs @@ -17,16 +17,22 @@ -- -- * 'Id.Id': see "Id#name_types" -- --- * 'Var.Var' is a synonym for the 'Id.Id' type but it may additionally potentially contain type variables, --- which have a 'TypeRep.Kind' rather than a 'TypeRep.Type' and only contain some extra details during typechecking. +-- * 'Var.Var' is a synonym for the 'Id.Id' type but it may additionally +-- potentially contain type variables, which have a 'TypeRep.Kind' +-- rather than a 'TypeRep.Type' and only contain some extra +-- details during typechecking. +-- -- These 'Var.Var' names may either be global or local, see "Var#globalvslocal" -- -- #globalvslocal# --- Global 'Id's and 'Var's are those that are imported or correspond to a data constructor, primitive operation, or record selectors. --- Local 'Id's and 'Var's are those bound within an expression (e.g. by a lambda) or at the top level of the module being compiled. +-- Global 'Id's and 'Var's are those that are imported or correspond +-- to a data constructor, primitive operation, or record selectors. +-- Local 'Id's and 'Var's are those bound within an expression +-- (e.g. by a lambda) or at the top level of the module being compiled. + module Var ( - -- * The main data type - Var, + -- * The main data type and synonyms + Var, TyVar, CoVar, TyCoVar, Id, DictId, DFunId, EvVar, EvId, IpId, -- ** Taking 'Var's apart varName, varUnique, varType, @@ -35,62 +41,73 @@ module Var ( setVarName, setVarUnique, setVarType, -- ** Constructing, taking apart, modifying 'Id's - mkGlobalVar, mkLocalVar, mkExportedLocalVar, + mkGlobalVar, mkLocalVar, mkExportedLocalVar, mkCoVar, idInfo, idDetails, lazySetIdInfo, setIdDetails, globaliseId, setIdExported, setIdNotExported, -- ** Predicates - isCoVar, isId, isTyVar, isTcTyVar, + isId, isTyVar, isTcTyVar, isLocalVar, isLocalId, isGlobalId, isExportedId, mustHaveLocalBinding, - -- * Type variable data type - TyVar, - -- ** Constructing 'TyVar's - mkTyVar, mkTcTyVar, mkWildCoVar, + mkTyVar, mkTcTyVar, -- ** Taking 'TyVar's apart - tyVarName, tyVarKind, tcTyVarDetails, + tyVarName, tyVarKind, tcTyVarDetails, setTcTyVarDetails, -- ** Modifying 'TyVar's - setTyVarName, setTyVarUnique, setTyVarKind, - - -- * Coercion variable data type - CoVar, - - -- ** Constructing 'CoVar's - mkCoVar, - - -- ** Taking 'CoVar's apart - coVarName, - - -- ** Modifying 'CoVar's - setCoVarUnique, setCoVarName, + setTyVarName, setTyVarUnique, setTyVarKind - -- * 'Var' type synonyms - Id, DictId ) where #include "HsVersions.h" +#include "Typeable.h" import {-# SOURCE #-} TypeRep( Type, Kind ) import {-# SOURCE #-} TcType( TcTyVarDetails, pprTcTyVarDetails ) -import {-# SOURCE #-} IdInfo( IdDetails, IdInfo, pprIdDetails ) -import {-# SOURCE #-} TypeRep( isCoercionKind ) +import {-# SOURCE #-} IdInfo( IdDetails, IdInfo, coVarDetails, vanillaIdInfo, pprIdDetails ) import Name hiding (varName) import Unique +import Util import FastTypes import FastString import Outputable + +import Data.Data \end{code} %************************************************************************ %* * + Synonyms +%* * +%************************************************************************ +-- These synonyms are here and not in Id because otherwise we need a very +-- large number of SOURCE imports of Id.hs :-( + +\begin{code} +type EvVar = Var -- An evidence variable: dictionary or equality constraint + -- Could be an DictId or a CoVar + +type Id = Var -- A term-level identifier +type DFunId = Id -- A dictionary function +type EvId = Id -- Term-level evidence: DictId or IpId +type DictId = EvId -- A dictionary variable +type IpId = EvId -- A term-level implicit parameter + +type TyVar = Var +type CoVar = Id -- A coercion variable is simply an Id + -- variable of kind @ty1 ~ ty2@. Hence its + -- 'varType' is always @PredTy (EqPred t1 t2)@ +type TyCoVar = TyVar -- Something that is a type OR coercion variable. +\end{code} + +%************************************************************************ +%* * \subsection{The main data type declarations} %* * %************************************************************************ @@ -110,8 +127,7 @@ data Var realUnique :: FastInt, -- Key for fast comparison -- Identical to the Unique in the name, -- cached here for speed - varType :: Kind, -- ^ The type or kind of the 'Var' in question - isCoercionVar :: Bool + varType :: Kind -- ^ The type or kind of the 'Var' in question } | TcTyVar { -- Used only during type inference @@ -120,15 +136,16 @@ data Var varName :: !Name, realUnique :: FastInt, varType :: Kind, - tcTyVarDetails :: TcTyVarDetails } + tc_tv_details :: TcTyVarDetails } | Id { varName :: !Name, realUnique :: FastInt, varType :: Type, idScope :: IdScope, - idDetails :: IdDetails, -- Stable, doesn't change - idInfo :: IdInfo } -- Unstable, updated by simplifier + id_details :: IdDetails, -- Stable, doesn't change + id_info :: IdInfo } -- Unstable, updated by simplifier + deriving Typeable data IdScope -- See Note [GlobalId/LocalId] = GlobalId @@ -137,7 +154,6 @@ data IdScope -- See Note [GlobalId/LocalId] data ExportFlag = NotExported -- ^ Not exported: may be discarded as dead code. | Exported -- ^ Exported: kept alive - \end{code} Note [GlobalId/LocalId] @@ -162,9 +178,9 @@ instance Outputable Var where ppr var = ppr (varName var) <+> ifPprDebug (brackets (ppr_debug var)) ppr_debug :: Var -> SDoc -ppr_debug (TyVar {}) = ptext (sLit "tv") -ppr_debug (TcTyVar {tcTyVarDetails = d}) = pprTcTyVarDetails d -ppr_debug (Id { idScope = s, idDetails = d }) = ppr_id_scope s <> pprIdDetails d +ppr_debug (TyVar {}) = ptext (sLit "tv") +ppr_debug (TcTyVar {tc_tv_details = d}) = pprTcTyVarDetails d +ppr_debug (Id { idScope = s, id_details = d }) = ppr_id_scope s <> pprIdDetails d ppr_id_scope :: IdScope -> SDoc ppr_id_scope GlobalId = ptext (sLit "gid") @@ -189,6 +205,12 @@ instance Ord Var where a >= b = realUnique a >=# realUnique b a > b = realUnique a ># realUnique b a `compare` b = varUnique a `compare` varUnique b + +instance Data Var where + -- don't traverse? + toConstr _ = abstractConstr "Var" + gunfold _ _ = error "gunfold" + dataTypeOf _ = mkNoRepType "Var" \end{code} @@ -218,8 +240,6 @@ setVarType id ty = id { varType = ty } %************************************************************************ \begin{code} -type TyVar = Var - tyVarName :: TyVar -> Name tyVarName = varName @@ -238,11 +258,9 @@ setTyVarKind tv k = tv {varType = k} \begin{code} mkTyVar :: Name -> Kind -> TyVar -mkTyVar name kind = ASSERT( not (isCoercionKind kind ) ) - TyVar { varName = name +mkTyVar name kind = TyVar { varName = name , realUnique = getKeyFastInt (nameUnique name) , varType = kind - , isCoercionVar = False } mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar @@ -251,42 +269,15 @@ mkTcTyVar name kind details TcTyVar { varName = name, realUnique = getKeyFastInt (nameUnique name), varType = kind, - tcTyVarDetails = details + tc_tv_details = details } -\end{code} - -%************************************************************************ -%* * -\subsection{Coercion variables} -%* * -%************************************************************************ - -\begin{code} -type CoVar = TyVar -- A coercion variable is simply a type - -- variable of kind @ty1 ~ ty2@. Hence its - -- 'varType' is always @PredTy (EqPred t1 t2)@ - -coVarName :: CoVar -> Name -coVarName = varName -setCoVarUnique :: CoVar -> Unique -> CoVar -setCoVarUnique = setVarUnique - -setCoVarName :: CoVar -> Name -> CoVar -setCoVarName = setVarName - -mkCoVar :: Name -> Kind -> CoVar -mkCoVar name kind = ASSERT( isCoercionKind kind ) - TyVar { varName = name - , realUnique = getKeyFastInt (nameUnique name) - , varType = kind - , isCoercionVar = True - } +tcTyVarDetails :: TyVar -> TcTyVarDetails +tcTyVarDetails (TcTyVar { tc_tv_details = details }) = details +tcTyVarDetails var = pprPanic "tcTyVarDetails" (ppr var) -mkWildCoVar :: Kind -> TyVar --- ^ Create a type variable that is never referred to, so its unique doesn't --- matter -mkWildCoVar = mkCoVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "co_wild")) +setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar +setTcTyVarDetails tv details = tv { tc_tv_details = details } \end{code} %************************************************************************ @@ -296,10 +287,13 @@ mkWildCoVar = mkCoVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "co_wild")) %************************************************************************ \begin{code} --- These synonyms are here and not in Id because otherwise we need a very --- large number of SOURCE imports of Id.hs :-( -type Id = Var -type DictId = Var +idInfo :: Id -> IdInfo +idInfo (Id { id_info = info }) = info +idInfo other = pprPanic "idInfo" (ppr other) + +idDetails :: Id -> IdDetails +idDetails (Id { id_details = details }) = details +idDetails other = pprPanic "idDetails" (ppr other) -- The next three have a 'Var' suffix even though they always build -- Ids, becuase Id.lhs uses 'mkGlobalId' etc with different types @@ -311,6 +305,10 @@ mkLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id mkLocalVar details name ty info = mk_id name ty (LocalId NotExported) details info +mkCoVar :: Name -> Type -> CoVar +-- Coercion variables have no IdInfo +mkCoVar name ty = mk_id name ty (LocalId NotExported) coVarDetails vanillaIdInfo + -- | Exported 'Var's will not be removed as dead code mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id mkExportedLocalVar details name ty info @@ -322,15 +320,15 @@ mk_id name ty scope details info realUnique = getKeyFastInt (nameUnique name), varType = ty, idScope = scope, - idDetails = details, - idInfo = info } + id_details = details, + id_info = info } ------------------- lazySetIdInfo :: Id -> IdInfo -> Var -lazySetIdInfo id info = id { idInfo = info } +lazySetIdInfo id info = id { id_info = info } setIdDetails :: Id -> IdDetails -> Id -setIdDetails id details = id { idDetails = details } +setIdDetails id details = id { id_details = details } globaliseId :: Id -> Id -- ^ If it's a local, make it global @@ -356,7 +354,7 @@ setIdNotExported id = ASSERT( isLocalId id ) %************************************************************************ \begin{code} -isTyVar :: Var -> Bool +isTyVar :: Var -> Bool -- True of both type variables only isTyVar (TyVar {}) = True isTyVar (TcTyVar {}) = True isTyVar _ = False @@ -373,11 +371,6 @@ isLocalId :: Var -> Bool isLocalId (Id { idScope = LocalId _ }) = True isLocalId _ = False -isCoVar :: Var -> Bool -isCoVar (v@(TyVar {})) = isCoercionVar v -isCoVar (TcTyVar {varType = kind}) = isCoercionKind kind -- used during solving -isCoVar _ = False - -- | 'isLocalVar' returns @True@ for type variables as well as local 'Id's -- These are the variables that we need to pay attention to when finding free -- variables, or doing dependency analysis.