X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FbasicTypes%2FId.lhs;h=012e42bf1c90d9c3bb09c1947cd94d468461fd57;hp=acd4d5e9f04e156263fa735ebdbdd1c0392d4af3;hb=d95ce839533391e7118257537044f01cbb1d6694;hpb=9526ada5b1e4a3463833bd74a15473d2ff7b53c1 diff --git a/compiler/basicTypes/Id.lhs b/compiler/basicTypes/Id.lhs index acd4d5e..012e42b 100644 --- a/compiler/basicTypes/Id.lhs +++ b/compiler/basicTypes/Id.lhs @@ -5,26 +5,47 @@ \section[Id]{@Ids@: Value and constructor identifiers} \begin{code} +-- | +-- #name_types# +-- GHC uses several kinds of name internally: +-- +-- * 'OccName.OccName': see "OccName#name_types" +-- +-- * 'RdrName.RdrName': see "RdrName#name_types" +-- +-- * 'Name.Name': see "Name#name_types" +-- +-- * 'Id.Id' represents names that not only have a 'Name.Name' but also a 'TypeRep.Type' and some additional +-- details (a 'IdInfo.IdInfo' and one of 'Var.LocalIdDetails' or 'IdInfo.GlobalIdDetails') that +-- are added, modified and inspected by various compiler passes. These 'Var.Var' names may either +-- be global or local, see "Var#globalvslocal" +-- +-- * 'Var.Var': see "Var#name_types" module Id ( + -- * The main types Id, DictId, - -- Simple construction - mkGlobalId, mkLocalId, mkLocalIdWithInfo, - mkSysLocal, mkUserLocal, mkVanillaGlobal, - mkTemplateLocals, mkTemplateLocalsNum, mkWildId, mkTemplateLocal, + -- ** Simple construction + mkGlobalId, mkVanillaGlobal, mkVanillaGlobalWithInfo, + mkLocalId, mkLocalIdWithInfo, + mkSysLocal, mkSysLocalM, mkUserLocal, mkUserLocalM, + mkTemplateLocals, mkTemplateLocalsNum, mkTemplateLocal, mkWorkerId, mkExportedLocalId, - -- Taking an Id apart + -- ** Taking an Id apart idName, idType, idUnique, idInfo, isId, globalIdDetails, idPrimRep, recordSelectorFieldLabel, - -- Modifying an Id - setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, + -- ** Modifying an Id + setIdName, setIdUnique, Id.setIdType, + setIdExported, setIdNotExported, + globaliseId, localiseId, setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo, zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, transferPolyIdInfo, + - -- Predicates + -- ** Predicates on Ids isImplicitId, isDeadBinder, isDictId, isStrictId, isExportedId, isLocalId, isGlobalId, isRecordSelector, isNaughtyRecordSelector, @@ -36,37 +57,17 @@ module Id ( isTickBoxOp, isTickBoxOp_maybe, hasNoBinding, - -- Inline pragma stuff + -- ** Inline pragma stuff idInlinePragma, setInlinePragma, modifyInlinePragma, - - -- One shot lambda stuff + -- ** One-shot lambdas isOneShotBndr, isOneShotLambda, isStateHackType, setOneShotLambda, clearOneShotLambda, - -- IdInfo stuff - setIdUnfolding, - setIdArity, - setIdNewDemandInfo, - setIdNewStrictness, zapIdNewStrictness, - setIdWorkerInfo, - setIdSpecialisation, - setIdCafInfo, - setIdOccInfo, - -#ifdef OLD_STRICTNESS - idDemandInfo, - idStrictness, - idCprInfo, - setIdStrictness, - setIdDemandInfo, - setIdCprInfo, -#endif - + -- ** Reading 'IdInfo' fields idArity, idNewDemandInfo, idNewDemandInfo_maybe, idNewStrictness, idNewStrictness_maybe, - idWorkerInfo, idUnfolding, idSpecialisation, idCoreRules, idHasRules, idCafInfo, @@ -74,22 +75,39 @@ module Id ( idOccInfo, #ifdef OLD_STRICTNESS - newStrictnessFromOld -- Temporary + idDemandInfo, + idStrictness, + idCprInfo, #endif + -- ** Writing 'IdInfo' fields + setIdUnfolding, + setIdArity, + setIdNewDemandInfo, + setIdNewStrictness, zapIdNewStrictness, + setIdSpecialisation, + setIdCafInfo, + setIdOccInfo, zapIdOccInfo, + +#ifdef OLD_STRICTNESS + setIdStrictness, + setIdDemandInfo, + setIdCprInfo, +#endif ) where #include "HsVersions.h" -import CoreSyn +import CoreSyn ( CoreRule, Unfolding ) + +import IdInfo import BasicTypes import qualified Var -import Var hiding (mkLocalId, mkGlobalId, mkExportedLocalId) +import Var import TyCon import Type import TcType import TysPrim -import IdInfo #ifdef OLD_STRICTNESS import qualified Demand #endif @@ -105,6 +123,7 @@ import Maybes import SrcLoc import Outputable import Unique +import UniqSupply import FastString import StaticFlags @@ -113,7 +132,6 @@ infixl 1 `setIdUnfolding`, `setIdArity`, `setIdNewDemandInfo`, `setIdNewStrictness`, - `setIdWorkerInfo`, `setIdSpecialisation`, `setInlinePragma`, `idCafInfo` @@ -124,7 +142,78 @@ infixl 1 `setIdUnfolding`, #endif \end{code} +%************************************************************************ +%* * +\subsection{Basic Id manipulation} +%* * +%************************************************************************ + +\begin{code} +idName :: Id -> Name +idName = Var.varName + +idUnique :: Id -> Unique +idUnique = varUnique + +idType :: Id -> Kind +idType = varType + +idInfo :: Id -> IdInfo +idInfo = varIdInfo + +idPrimRep :: Id -> PrimRep +idPrimRep id = typePrimRep (idType id) + +globalIdDetails :: Id -> GlobalIdDetails +globalIdDetails = globalIdVarDetails + + +setIdName :: Id -> Name -> Id +setIdName = setVarName + +setIdUnique :: Id -> Unique -> Id +setIdUnique = setVarUnique +-- | Not only does this set the 'Id' 'Type', it also evaluates the type to try and +-- reduce space usage +setIdType :: Id -> Type -> Id +setIdType id ty = seqType ty `seq` Var.setVarType id ty + +setIdExported :: Id -> Id +setIdExported = setIdVarExported + +setIdNotExported :: Id -> Id +setIdNotExported = setIdVarNotExported + +localiseId :: Id -> Id +-- Make an with the same unique and type as the +-- incoming Id, but with an *Internal* Name and *LocalId* flavour +localiseId id + | isLocalId id && isInternalName name + = id + | otherwise + = mkLocalIdWithInfo (localiseName name) (idType id) (idInfo id) + where + name = idName id + +globaliseId :: GlobalIdDetails -> Id -> Id +globaliseId = globaliseIdVar + +lazySetIdInfo :: Id -> IdInfo -> Id +lazySetIdInfo = lazySetVarIdInfo + +setIdInfo :: Id -> IdInfo -> Id +setIdInfo id info = seqIdInfo info `seq` (lazySetIdInfo id info) + -- Try to avoid spack leaks by seq'ing + +modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id +modifyIdInfo fn id = setIdInfo id (fn (idInfo id)) + +-- maybeModifyIdInfo tries to avoid unnecesary thrashing +maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id +maybeModifyIdInfo (Just new_info) id = lazySetIdInfo id new_info +maybeModifyIdInfo Nothing id = id +\end{code} %************************************************************************ %* * @@ -147,33 +236,48 @@ substitution (which changes the free type variables) is more common. Anyway, we removed it in March 2008. \begin{code} +-- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal" +mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id +mkGlobalId = mkGlobalIdVar + +-- | Make a global 'Id' without any extra information at all +mkVanillaGlobal :: Name -> Type -> Id +mkVanillaGlobal name ty = mkVanillaGlobalWithInfo name ty vanillaIdInfo + +-- | Make a global 'Id' with no global information but some generic 'IdInfo' +mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id +mkVanillaGlobalWithInfo = mkGlobalId VanillaGlobal + + +-- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal" +mkLocalId :: Name -> Type -> Id +mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo + mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id -mkLocalIdWithInfo name ty info = Var.mkLocalId name ty info +mkLocalIdWithInfo = mkLocalIdVar -- Note [Free type variables] +-- | Create a local 'Id' that is marked as exported. This prevents things attached to it from being removed as dead code. mkExportedLocalId :: Name -> Type -> Id -mkExportedLocalId name ty = Var.mkExportedLocalId name ty vanillaIdInfo +mkExportedLocalId name ty = mkExportedLocalIdVar name ty vanillaIdInfo -- Note [Free type variables] -mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id -mkGlobalId details name ty info = Var.mkGlobalId details name ty info -\end{code} -\begin{code} -mkLocalId :: Name -> Type -> Id -mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo - --- SysLocal: for an Id being created by the compiler out of thin air... +-- | Create a system local 'Id'. These are local 'Id's (see "Var#globalvslocal") that are created by the compiler out of thin air mkSysLocal :: FastString -> Unique -> Type -> Id mkSysLocal fs uniq ty = mkLocalId (mkSystemVarName uniq fs) ty +mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id +mkSysLocalM fs ty = getUniqueM >>= (\uniq -> return (mkSysLocal fs uniq ty)) + --- UserLocal: an Id with a name the user might recognize... +-- | Create a user local 'Id'. These are local 'Id's (see "Var#globalvslocal") with a name and location that the user might recognize mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id -mkVanillaGlobal :: Name -> Type -> IdInfo -> Id +mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty + +mkUserLocalM :: MonadUnique m => OccName -> Type -> SrcSpan -> m Id +mkUserLocalM occ ty loc = getUniqueM >>= (\uniq -> return (mkUserLocal occ uniq ty loc)) -mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty -mkVanillaGlobal = mkGlobalId VanillaGlobal \end{code} Make some local @Ids@ for a template @CoreExpr@. These have bogus @@ -181,45 +285,49 @@ Make some local @Ids@ for a template @CoreExpr@. These have bogus instantiated before use. \begin{code} --- "Wild Id" typically used when you need a binder that you don't expect to use -mkWildId :: Type -> Id -mkWildId ty = mkSysLocal FSLIT("wild") (mkBuiltinUnique 1) ty - +-- | Workers get local names. "CoreTidy" will externalise these if necessary mkWorkerId :: Unique -> Id -> Type -> Id --- A worker gets a local name. CoreTidy will externalise it if necessary. mkWorkerId uniq unwrkr ty = mkLocalId wkr_name ty where wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcSpan unwrkr) --- "Template locals" typically used in unfoldings +-- | Create a /template local/: a family of system local 'Id's in bijection with @Int@s, typically used in unfoldings +mkTemplateLocal :: Int -> Type -> Id +mkTemplateLocal i ty = mkSysLocal (fsLit "tpl") (mkBuiltinUnique i) ty + +-- | Create a template local for a series of types mkTemplateLocals :: [Type] -> [Id] -mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys +mkTemplateLocals = mkTemplateLocalsNum 1 +-- | Create a template local for a series of type, but start from a specified template local mkTemplateLocalsNum :: Int -> [Type] -> [Id] --- The Int gives the starting point for unique allocation mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys - -mkTemplateLocal :: Int -> Type -> Id -mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty \end{code} %************************************************************************ %* * -\subsection[Id-general-funs]{General @Id@-related functions} +\subsection{Basic predicates on @Id@s} %* * %************************************************************************ \begin{code} -setIdType :: Id -> Type -> Id - -- Add free tyvar info to the type -setIdType id ty = seqType ty `seq` Var.setIdType id ty +isId :: Id -> Bool +isId = isIdVar -idPrimRep :: Id -> PrimRep -idPrimRep id = typePrimRep (idType id) -\end{code} +-- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal" +isLocalId :: Id -> Bool +isLocalId = isLocalIdVar +-- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal" +isGlobalId :: Id -> Bool +isGlobalId = isGlobalIdVar + +-- | Determines whether an 'Id' is marked as exported and hence will not be considered dead code +isExportedId :: Id -> Bool +isExportedId = isExportedIdVar +\end{code} %************************************************************************ %* * @@ -228,23 +336,23 @@ idPrimRep id = typePrimRep (idType id) %************************************************************************ \begin{code} +-- | If the 'Id' is that for a record selector, extract the 'sel_tycon' and label. Panic otherwise recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) recordSelectorFieldLabel id = case globalIdDetails id of RecordSelId { sel_tycon = tycon, sel_label = lbl } -> (tycon,lbl) _ -> panic "recordSelectorFieldLabel" -isRecordSelector :: Var -> Bool -isNaughtyRecordSelector :: Var -> Bool -isPrimOpId :: Var -> Bool -isFCallId :: Var -> Bool -isDataConWorkId :: Var -> Bool -hasNoBinding :: Var -> Bool +isRecordSelector :: Id -> Bool +isNaughtyRecordSelector :: Id -> Bool +isPrimOpId :: Id -> Bool +isFCallId :: Id -> Bool +isDataConWorkId :: Id -> Bool -isClassOpId_maybe :: Var -> Maybe Class -isPrimOpId_maybe :: Var -> Maybe PrimOp -isFCallId_maybe :: Var -> Maybe ForeignCall -isDataConWorkId_maybe :: Var -> Maybe DataCon +isClassOpId_maybe :: Id -> Maybe Class +isPrimOpId_maybe :: Id -> Maybe PrimOp +isFCallId_maybe :: Id -> Maybe ForeignCall +isDataConWorkId_maybe :: Id -> Maybe DataCon isRecordSelector id = case globalIdDetails id of RecordSelId {} -> True @@ -289,21 +397,19 @@ isDataConId_maybe id = case globalIdDetails id of _ -> Nothing idDataCon :: Id -> DataCon --- Get from either the worker or the wrapper to the DataCon --- Currently used only in the desugarer --- INVARIANT: idDataCon (dataConWrapId d) = d --- (Remember, dataConWrapId can return either the wrapper or the worker.) -idDataCon id = case globalIdDetails id of - DataConWorkId con -> con - DataConWrapId con -> con - _ -> pprPanic "idDataCon" (ppr id) +-- ^ Get from either the worker or the wrapper 'Id' to the 'DataCon'. Currently used only in the desugarer. +-- +-- INVARIANT: @idDataCon (dataConWrapId d) = d@: remember, 'dataConWrapId' can return either the wrapper or the worker +idDataCon id = isDataConId_maybe id `orElse` pprPanic "idDataCon" (ppr id) isDictId :: Id -> Bool isDictId id = isDictTy (idType id) --- hasNoBinding returns True of an Id which may not have a --- binding, even though it is defined in this module. +hasNoBinding :: Id -> Bool +-- ^ Returns @True@ of an 'Id' which may not have a +-- binding, even though it is defined in this module. + -- Data constructor workers used to be things of this kind, but -- they aren't any more. Instead, we inject a binding for -- them at the CorePrep stage. @@ -315,9 +421,9 @@ hasNoBinding id = case globalIdDetails id of _ -> False isImplicitId :: Id -> Bool - -- isImplicitId tells whether an Id's info is implied by other - -- declarations, so we don't need to put its signature in an interface - -- file, even if it's mentioned in some other interface unfolding. +-- ^ 'isImplicitId' tells whether an 'Id's info is implied by other +-- declarations, so we don't need to put its signature in an interface +-- file, even if it's mentioned in some other interface unfolding. isImplicitId id = case globalIdDetails id of RecordSelId {} -> True @@ -396,7 +502,7 @@ setIdStrictness :: Id -> StrictnessInfo -> Id setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id #endif --- isBottomingId returns true if an application to n args would diverge +-- | Returns true if an application to n args would diverge isBottomingId :: Id -> Bool isBottomingId id = isBottomingSig (idNewStrictness id) @@ -411,15 +517,13 @@ setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id zapIdNewStrictness :: Id -> Id zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id -\end{code} -This predicate says whether the id has a strict demand placed on it or -has a type such that it can always be evaluated strictly (e.g., an -unlifted type, but see the comment for isStrictType). We need to -check separately whether has a so-called "strict type" because if -the demand for hasn't been computed yet but has a strict -type, we still want (isStrictId ) to be True. -\begin{code} +-- | This predicate says whether the 'Id' has a strict demand placed on it or +-- has a type such that it can always be evaluated strictly (e.g., an +-- unlifted type, but see the comment for 'isStrictType'). We need to +-- check separately whether the 'Id' has a so-called \"strict type\" because if +-- the demand for the given @id@ hasn't been computed yet but @id@ has a strict +-- type, we still want @isStrictId id@ to be @True@. isStrictId :: Id -> Bool isStrictId id = ASSERT2( isId id, text "isStrictId: not an id: " <+> ppr id ) @@ -427,14 +531,6 @@ isStrictId id (isStrictType (idType id)) --------------------------------- - -- WORKER ID -idWorkerInfo :: Id -> WorkerInfo -idWorkerInfo id = workerInfo (idInfo id) - -setIdWorkerInfo :: Id -> WorkerInfo -> Id -setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id - - --------------------------------- -- UNFOLDING idUnfolding :: Id -> Unfolding idUnfolding id = unfoldingInfo (idInfo id) @@ -506,6 +602,9 @@ idOccInfo id = occInfo (idInfo id) setIdOccInfo :: Id -> OccInfo -> Id setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id + +zapIdOccInfo :: Id -> Id +zapIdOccInfo b = b `setIdOccInfo` NoOccInfo \end{code} @@ -532,11 +631,15 @@ modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn ( idLBVarInfo :: Id -> LBVarInfo idLBVarInfo id = lbvarInfo (idInfo id) +-- | Returns whether the lambda associated with the 'Id' is certainly applied at most once +-- OR we are applying the \"state hack\" which makes it appear as if theis is the case for +-- lambdas used in @IO@. You should prefer using this over 'isOneShotLambda' isOneShotBndr :: Id -> Bool -- This one is the "business end", called externally. -- Its main purpose is to encapsulate the Horrible State Hack isOneShotBndr id = isOneShotLambda id || isStateHackType (idType id) +-- | Should we apply the state hack to values of this 'Type'? isStateHackType :: Type -> Bool isStateHackType ty | opt_NoStateHack @@ -564,7 +667,8 @@ isStateHackType ty -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet. --- The OneShotLambda functions simply fiddle with the IdInfo flag +-- | Returns whether the lambda associated with the 'Id' is certainly applied at most once. +-- You probably want to use 'isOneShotBndr' instead isOneShotLambda :: Id -> Bool isOneShotLambda id = case idLBVarInfo id of IsOneShotLambda -> True @@ -578,6 +682,7 @@ clearOneShotLambda id | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id | otherwise = id +-- The OneShotLambda functions simply fiddle with the IdInfo flag -- But watch out: this may change the type of something else -- f = \x -> e -- If we change the one-shot-ness of x, f's type changes @@ -628,4 +733,3 @@ transferPolyIdInfo old_id new_id transfer new_info = new_info `setNewStrictnessInfo` (newStrictnessInfo old_info) `setArityInfo` (arityInfo old_info) \end{code} -