X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FVar.lhs;h=b9d7cf7e757221ee8de660a6ff70396b3925b80a;hb=54922479beb371d9662983ffb4036171f2f9f28e;hp=cacde2b61e1cc4ef804f8f4252ed567b191af470;hpb=d133b73a4d4717892ced072d05e039a54ede0ceb;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Var.lhs b/ghc/compiler/basicTypes/Var.lhs index cacde2b..b9d7cf7 100644 --- a/ghc/compiler/basicTypes/Var.lhs +++ b/ghc/compiler/basicTypes/Var.lhs @@ -5,52 +5,52 @@ \begin{code} module Var ( - Var, IdOrTyVar, -- Abstract - VarDetails(..), -- Concrete - varName, varUnique, varDetails, varInfo, varType, - setVarName, setVarUnique, setVarType, setVarOcc, - + Var, VarDetails, -- Abstract + varName, varUnique, varInfo, varType, + setVarName, setVarUnique, setVarType, setVarOcc, -- TyVars TyVar, tyVarName, tyVarKind, setTyVarName, setTyVarUnique, - mkTyVar, mkSysTyVar, isTyVar, isSigTyVar, + mkTyVar, mkSysTyVar, newMutTyVar, newSigTyVar, - readMutTyVar, writeMutTyVar, isMutTyVar, makeTyVarImmutable, - - -- UVars - UVar, - isUVar, - mkUVar, + readMutTyVar, writeMutTyVar, makeTyVarImmutable, -- Ids Id, DictId, - idDetails, idName, idType, idUnique, idInfo, modifyIdInfo, - setIdName, setIdUnique, setIdInfo, - mkId, isId, externallyVisibleId + idName, idType, idUnique, idInfo, modifyIdInfo, maybeModifyIdInfo, + setIdName, setIdUnique, setIdInfo, lazySetIdInfo, + setIdNoDiscard, zapSpecPragmaId, + + globalIdDetails, setGlobalIdDetails, + + mkLocalId, mkGlobalId, mkSpecPragmaId, + + isTyVar, isMutTyVar, isSigTyVar, + isId, isLocalVar, isLocalId, + isGlobalId, isExportedId, isSpecPragmaId, + mustHaveLocalBinding ) where #include "HsVersions.h" -import {-# SOURCE #-} Type( Type, Kind ) -import {-# SOURCE #-} IdInfo( IdInfo ) -import {-# SOURCE #-} Const( Con ) +import {-# SOURCE #-} TypeRep( Type, Kind ) +import {-# SOURCE #-} IdInfo( GlobalIdDetails, notGlobalId, + IdInfo, seqIdInfo ) -import FieldLabel ( FieldLabel ) -import Unique ( Unique, Uniquable(..), mkUniqueGrimily, getKey ) import Name ( Name, OccName, NamedThing(..), setNameUnique, setNameOcc, nameUnique, mkSysLocalName, isExternallyVisibleName ) -import BasicTypes ( Unused ) +import Unique ( Unique, Uniquable(..), mkUniqueGrimily, getKey ) +import FastTypes import Outputable import IOExts ( IORef, newIORef, readIORef, writeIORef ) \end{code} - %************************************************************************ %* * \subsection{The main data type declarations} @@ -64,12 +64,10 @@ strictness). The essential info about different kinds of @Vars@ is in its @VarDetails@. \begin{code} -type IdOrTyVar = Var - data Var = Var { varName :: Name, - realUnique :: Int#, -- Key for fast comparison + realUnique :: FastInt, -- Key for fast comparison -- Identical to the Unique in the name, -- cached here for speed varType :: Type, @@ -78,21 +76,42 @@ data Var } data VarDetails - = VanillaId -- Most Ids are like this - | ConstantId Con -- The Id for a constant (data constructor or primop) - | RecordSelId FieldLabel -- The Id for a record selector + = LocalId -- Used for locally-defined Ids (see NOTE below) + LocalIdDetails -- True <=> exported; don't discard even if dead + + | GlobalId -- Used for imported Ids, dict selectors etc + GlobalIdDetails + | TyVar | MutTyVar (IORef (Maybe Type)) -- Used during unification; Bool -- True <=> this is a type signature variable, which -- should not be unified with a non-tyvar type - | UVar -- Usage variable --- For a long time I tried to keep mutable Vars statically type-distinct --- from immutable Vars, but I've finally given up. It's just too painful. --- After type checking there are no MutTyVars left, but there's no static check --- of that fact. + -- For a long time I tried to keep mutable Vars statically type-distinct + -- from immutable Vars, but I've finally given up. It's just too painful. + -- After type checking there are no MutTyVars left, but there's no static check + -- of that fact. + +data LocalIdDetails + = NotExported -- Not exported + | Exported -- Exported + | SpecPragma -- Not exported, but not to be discarded either + -- It's unclean that this is so deeply built in \end{code} +LocalId and GlobalId +~~~~~~~~~~~~~~~~~~~~ +A GlobalId is + * always a constant (top-level) + * imported, or data constructor, or primop, or record selector + +A LocalId is + * bound within an expression (lambda, case, local let(rec)) + * or defined at top level in the module being compiled + +After CoreTidy, top-level LocalIds are turned into GlobalIds + + \begin{code} instance Outputable Var where ppr var = ppr (varName var) @@ -123,8 +142,9 @@ varUnique :: Var -> Unique varUnique (Var {realUnique = uniq}) = mkUniqueGrimily uniq setVarUnique :: Var -> Unique -> Var -setVarUnique var uniq = var {realUnique = getKey uniq, - varName = setNameUnique (varName var) uniq} +setVarUnique var@(Var {varName = name}) uniq + = var {realUnique = getKey uniq, + varName = setNameUnique name uniq} setVarName :: Var -> Name -> Var setVarName var new_name @@ -163,9 +183,7 @@ mkTyVar name kind = Var { varName = name , realUnique = getKey (nameUnique name) , varType = kind , varDetails = TyVar -#ifdef DEBUG - , varInfo = pprPanic "mkTyVar" (ppr name) -#endif + , varInfo = pprPanic "mkTyVar" (ppr name) } mkSysTyVar :: Unique -> Kind -> TyVar @@ -173,28 +191,29 @@ mkSysTyVar uniq kind = Var { varName = name , realUnique = getKey uniq , varType = kind , varDetails = TyVar -#ifdef DEBUG - , varInfo = pprPanic "mkSysTyVar" (ppr name) -#endif + , varInfo = pprPanic "mkSysTyVar" (ppr name) } where name = mkSysLocalName uniq SLIT("t") newMutTyVar :: Name -> Kind -> IO TyVar -newMutTyVar name kind = - do loc <- newIORef Nothing - return (Var { varName = name, - realUnique = getKey (nameUnique name), - varType = kind, - varDetails = MutTyVar loc False}) +newMutTyVar name kind = newTyVar name kind False newSigTyVar :: Name -> Kind -> IO TyVar -newSigTyVar name kind = - do loc <- newIORef Nothing - return (Var { varName = name, - realUnique = getKey (nameUnique name), - varType = kind, - varDetails = MutTyVar loc True}) +-- Type variables from type signatures are still mutable, because +-- they may get unified with type variables from other signatures +-- But they do contain a flag to distinguish them, so we can tell if +-- we unify them with a non-type-variable. +newSigTyVar name kind = newTyVar name kind True + +newTyVar name kind is_sig + = do loc <- newIORef Nothing + return (Var { varName = name + , realUnique = getKey (nameUnique name) + , varType = kind + , varDetails = MutTyVar loc is_sig + , varInfo = pprPanic "newMutTyVar" (ppr name) + }) readMutTyVar :: TyVar -> IO (Maybe Type) readMutTyVar (Var {varDetails = MutTyVar loc _}) = readIORef loc @@ -204,45 +223,6 @@ writeMutTyVar (Var {varDetails = MutTyVar loc _}) val = writeIORef loc val makeTyVarImmutable :: TyVar -> TyVar makeTyVarImmutable tyvar = tyvar { varDetails = TyVar} - -isTyVar :: Var -> Bool -isTyVar (Var {varDetails = details}) = case details of - TyVar -> True - MutTyVar _ _ -> True - other -> False - -isMutTyVar :: Var -> Bool -isMutTyVar (Var {varDetails = MutTyVar _ _}) = True -isMutTyVar other = False - -isSigTyVar :: Var -> Bool -isSigTyVar (Var {varDetails = MutTyVar _ is_sig}) = is_sig -isSigTyVar other = False -\end{code} - - -%************************************************************************ -%* * -\subsection{Usage variables} -%* * -%************************************************************************ - -\begin{code} -type UVar = Var -\end{code} - -\begin{code} -mkUVar :: Unique -> UVar -mkUVar unique = Var { varName = mkSysLocalName unique SLIT("u"), - realUnique = getKey unique, - varDetails = UVar } -\end{code} - -\begin{code} -isUVar :: Var -> Bool -isUVar (Var {varDetails = details}) = case details of - UVar -> True - other -> False \end{code} @@ -264,7 +244,6 @@ idName = varName idType = varType idUnique = varUnique idInfo = varInfo -idDetails = varDetails setIdUnique :: Id -> Unique -> Id setIdUnique = setVarUnique @@ -272,41 +251,127 @@ setIdUnique = setVarUnique setIdName :: Id -> Name -> Id setIdName = setVarName -setIdInfo :: Id -> IdInfo -> Id -setIdInfo var info = var {varInfo = info} +setIdNoDiscard :: Id -> Id +setIdNoDiscard id + = WARN( not (isLocalId id), ppr id ) + id { varDetails = LocalId Exported } + +zapSpecPragmaId :: Id -> Id +zapSpecPragmaId id + = case varDetails id of + LocalId SpecPragma -> id { varDetails = LocalId NotExported } + other -> id -modifyIdInfo :: Id -> (IdInfo -> IdInfo) -> Id -modifyIdInfo var@(Var {varInfo = info}) fn = var {varInfo = fn info} +lazySetIdInfo :: Id -> IdInfo -> Id +lazySetIdInfo var info = var {varInfo = info} + +setIdInfo :: Id -> IdInfo -> Id +setIdInfo var info = seqIdInfo info `seq` var {varInfo = info} + -- Try to avoid spack leaks by seq'ing + +modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id +modifyIdInfo fn var@(Var {varInfo = info}) + = seqIdInfo new_info `seq` var {varInfo = new_info} + where + new_info = fn info + +-- maybeModifyIdInfo tries to avoid unnecesary thrashing +maybeModifyIdInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id +maybeModifyIdInfo fn var@(Var {varInfo = info}) = case fn info of + Nothing -> var + Just new_info -> var {varInfo = new_info} \end{code} +%************************************************************************ +%* * +\subsection{Predicates over variables +%* * +%************************************************************************ + \begin{code} mkId :: Name -> Type -> VarDetails -> IdInfo -> Id mkId name ty details info - = Var {varName = name, realUnique = getKey (nameUnique name), varType = ty, - varDetails = details, varInfo = info} + = Var { varName = name, + realUnique = getKey (nameUnique name), -- Cache the unique + varType = ty, + varDetails = details, + varInfo = info } + +mkLocalId :: Name -> Type -> IdInfo -> Id +mkLocalId name ty info = mkId name ty (LocalId NotExported) info + +mkSpecPragmaId :: Name -> Type -> IdInfo -> Id +mkSpecPragmaId name ty info = mkId name ty (LocalId SpecPragma) info + +mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id +mkGlobalId details name ty info = mkId name ty (GlobalId details) info \end{code} \begin{code} -isId :: Var -> Bool -isId (Var {varDetails = details}) = case details of - VanillaId -> True - ConstantId _ -> True - RecordSelId _ -> True - other -> False -\end{code} +isTyVar, isMutTyVar, isSigTyVar :: Var -> Bool +isId, isLocalVar, isLocalId :: Var -> Bool +isGlobalId, isExportedId, isSpecPragmaId :: Var -> Bool +mustHaveLocalBinding :: Var -> Bool -@externallyVisibleId@: is it true that another module might be -able to ``see'' this Id in a code generation sense. That -is, another .o file might refer to this Id. +isTyVar var = case varDetails var of + TyVar -> True + MutTyVar _ _ -> True + other -> False -In tidyCorePgm (SimplCore.lhs) we carefully set each top level thing's -local-ness precisely so that the test here would be easy +isMutTyVar (Var {varDetails = MutTyVar _ _}) = True +isMutTyVar other = False -This defn appears here (rather than, say, in Id.lhs) because -CostCentre.lhs uses it (CostCentre feeds PprType feeds Id.lhs) +isSigTyVar (Var {varDetails = MutTyVar _ is_sig}) = is_sig +isSigTyVar other = False +isId var = case varDetails var of + LocalId _ -> True + GlobalId _ -> True + other -> False + +isLocalId var = case varDetails var of + LocalId _ -> True + other -> False + +-- isLocalVar returns True for type variables as well as local Ids +-- These are the variables that we need to pay attention to when finding free +-- variables, or doing dependency analysis. +isLocalVar var = case varDetails var of + LocalId _ -> True + TyVar -> True + MutTyVar _ _ -> True + other -> False + +-- mustHaveLocalBinding returns True of Ids and TyVars +-- that must have a binding in this module. The converse +-- is not quite right: there are some GlobalIds that must have +-- bindings, such as record selectors. But that doesn't matter, +-- because it's only used for assertions +mustHaveLocalBinding var = isLocalVar var + +isGlobalId var = case varDetails var of + GlobalId _ -> True + other -> False + +-- isExportedId means "don't throw this away" +isExportedId var = case varDetails var of + LocalId Exported -> True + LocalId SpecPragma -> True + GlobalId _ -> True + other -> False + +isSpecPragmaId var = case varDetails var of + LocalId SpecPragma -> True + other -> False \end{code} + \begin{code} -externallyVisibleId :: Id -> Bool -externallyVisibleId var = isExternallyVisibleName (varName var) +globalIdDetails :: Var -> GlobalIdDetails +-- Works OK on local Ids too, returning notGlobalId +globalIdDetails var = case varDetails var of + GlobalId details -> details + other -> notGlobalId +setGlobalIdDetails :: Id -> GlobalIdDetails -> Id +setGlobalIdDetails id details = id { varDetails = GlobalId details } \end{code} +