X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;ds=sidebyside;f=compiler%2FbasicTypes%2FId.lhs;h=95f90a45dbd326768b5aea3114fd28e65685b19b;hb=6084fb5517da34f65034370a3695e2af3b85ce2b;hp=61a39f1fa06ee1491c1153fa261154e1e3976900;hpb=49d454d8f8f0e1a83369ec12f8aafc1dcf80aea9;p=ghc-hetmet.git diff --git a/compiler/basicTypes/Id.lhs b/compiler/basicTypes/Id.lhs index 61a39f1..95f90a4 100644 --- a/compiler/basicTypes/Id.lhs +++ b/compiler/basicTypes/Id.lhs @@ -6,25 +6,25 @@ \begin{code} module Id ( + -- * The main types Id, DictId, - -- Simple construction - mkGlobalId, mkLocalId, mkLocalIdWithInfo, - mkSysLocal, mkUserLocal, mkVanillaGlobal, - mkTemplateLocals, mkTemplateLocalsNum, mkWildId, mkTemplateLocal, - mkWorkerId, mkExportedLocalId, + -- ** Simple construction + mkGlobalId, mkVanillaGlobal, mkVanillaGlobalWithInfo, + mkLocalId, mkLocalIdWithInfo, + mkSysLocal, mkSysLocalM, mkUserLocal, mkUserLocalM, - -- Taking an Id apart + -- ** Taking an Id apart idName, idType, idUnique, idInfo, isId, globalIdDetails, idPrimRep, recordSelectorFieldLabel, - -- Modifying an Id + -- ** Modifying an Id setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, - setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo, - zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, + globaliseId, setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo, + zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, transferPolyIdInfo, - -- Predicates + -- ** Predicates on Ids isImplicitId, isDeadBinder, isDictId, isStrictId, isExportedId, isLocalId, isGlobalId, isRecordSelector, isNaughtyRecordSelector, @@ -36,15 +36,15 @@ module Id ( isTickBoxOp, isTickBoxOp_maybe, hasNoBinding, - -- Inline pragma stuff + -- ** Inline pragma stuff idInlinePragma, setInlinePragma, modifyInlinePragma, - -- One shot lambda stuff + -- ** One shot lambda stuff isOneShotBndr, isOneShotLambda, isStateHackType, setOneShotLambda, clearOneShotLambda, - -- IdInfo stuff + -- ** IdInfo stuff setIdUnfolding, setIdArity, setIdNewDemandInfo, @@ -54,6 +54,7 @@ module Id ( setIdCafInfo, setIdOccInfo, + -- ** Id demand information #ifdef OLD_STRICTNESS idDemandInfo, idStrictness, @@ -81,15 +82,16 @@ module Id ( #include "HsVersions.h" -import CoreSyn +import {-# SOURCE #-} 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 +import TysPrim #ifdef OLD_STRICTNESS import qualified Demand #endif @@ -97,11 +99,15 @@ import DataCon import NewDemand import Name import Module +import Class +import PrimOp +import ForeignCall import OccName import Maybes import SrcLoc import Outputable import Unique +import UniqSupply import FastString import StaticFlags @@ -120,8 +126,58 @@ infixl 1 `setIdUnfolding`, ,`setIdDemandInfo` #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 + +setIdUnique :: Id -> Unique -> Id +setIdUnique = setVarUnique + +setIdName :: Id -> Name -> Id +setIdName = setVarName + +setIdType :: Id -> Type -> Id +setIdType id ty = seqType ty `seq` Var.setVarType id ty + +setIdExported :: Id -> Id +setIdExported = setIdVarExported + +setIdNotExported :: Id -> Id +setIdNotExported = setIdVarNotExported + +globaliseId :: GlobalIdDetails -> Id -> Id +globaliseId = globaliseIdVar + +idInfo :: Id -> IdInfo +idInfo = varIdInfo +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} %************************************************************************ %* * @@ -133,32 +189,55 @@ Absolutely all Ids are made by mkId. It is just like Var.mkId, but in addition it pins free-tyvar-info onto the Id's type, where it can easily be found. +Note [Free type variables] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +At one time we cached the free type variables of the type of an Id +at the root of the type in a TyNote. The idea was to avoid repeating +the free-type-variable calculation. But it turned out to slow down +the compiler overall. I don't quite know why; perhaps finding free +type variables of an Id isn't all that common whereas applying a +substitution (which changes the free type variables) is more common. +Anyway, we removed it in March 2008. + \begin{code} -mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id -mkLocalIdWithInfo name ty info = Var.mkLocalId name (addFreeTyVars ty) info +-- | Create a global Id. Global identifiers are those that are imported or are data constructors/destructors. +mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id +mkGlobalId = mkGlobalIdVar -mkExportedLocalId :: Name -> Type -> Id -mkExportedLocalId name ty = Var.mkExportedLocalId name (addFreeTyVars ty) vanillaIdInfo +mkVanillaGlobal :: Name -> Type -> Id +mkVanillaGlobal name ty = mkVanillaGlobalWithInfo name ty vanillaIdInfo -mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id -mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info -\end{code} +mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id +mkVanillaGlobalWithInfo = mkGlobalId VanillaGlobal -\begin{code} + +-- | Create a local Id. Local identifiers are those bound at the top level of the current module or in an expression. mkLocalId :: Name -> Type -> Id mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo --- SysLocal: for an Id being created by the compiler out of thin air... +mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id +mkLocalIdWithInfo = mkLocalIdVar + +-- | 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 = mkExportedLocalIdVar name ty vanillaIdInfo + -- Note [Free type variables] + + +-- | Create a system local Id. These are local Ids 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... -mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id -mkVanillaGlobal :: Name -> Type -> IdInfo -> Id -mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty -mkVanillaGlobal = mkGlobalId VanillaGlobal +-- | Create a user local Id. These are local Id with a name and location that the user might recognize +mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> 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)) \end{code} Make some local @Ids@ for a template @CoreExpr@. These have bogus @@ -166,27 +245,29 @@ 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 +-- | Make a "wild Id". This is 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 +mkWildId ty = mkSysLocal (fsLit "wild") (mkBuiltinUnique 1) ty mkWorkerId :: Unique -> Id -> Type -> Id --- A worker gets a local name. CoreTidy will externalise it if necessary. +-- | Workers get local names. CoreTidy will externalise these if necessary mkWorkerId uniq unwrkr ty = mkLocalId wkr_name ty where - wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr) + wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcSpan unwrkr) + +-- | Create a "template local": a family of system local Ids in bijection with Ints, typically used in unfoldings +mkTemplateLocal :: Int -> Type -> Id +mkTemplateLocal i ty = mkSysLocal (fsLit "tpl") (mkBuiltinUnique i) ty --- "Template locals" typically used in unfoldings +-- | 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} @@ -197,12 +278,23 @@ mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty %************************************************************************ \begin{code} -setIdType :: Id -> Type -> Id - -- Add free tyvar info to the type -setIdType id ty = seqType ty `seq` Var.setIdType id (addFreeTyVars ty) - idPrimRep :: Id -> PrimRep idPrimRep id = typePrimRep (idType id) + +globalIdDetails :: Id -> GlobalIdDetails +globalIdDetails = globalIdVarDetails + +isId :: Id -> Bool +isId = isIdVar + +isLocalId :: Id -> Bool +isLocalId = isLocalIdVar + +isGlobalId :: Id -> Bool +isGlobalId = isGlobalIdVar + +isExportedId :: Var -> Bool +isExportedId = isExportedIdVar \end{code} @@ -214,82 +306,94 @@ idPrimRep id = typePrimRep (idType id) \begin{code} recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) -recordSelectorFieldLabel id = case globalIdDetails id of - RecordSelId tycon lbl _ -> (tycon,lbl) - other -> panic "recordSelectorFieldLabel" +recordSelectorFieldLabel id + = case globalIdDetails id of + RecordSelId { sel_tycon = tycon, sel_label = lbl } -> (tycon,lbl) + _ -> panic "recordSelectorFieldLabel" + +isRecordSelector :: Id -> Bool +isNaughtyRecordSelector :: Id -> Bool +isPrimOpId :: Id -> Bool +isFCallId :: Id -> Bool +isDataConWorkId :: Id -> Bool + +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 - other -> False + RecordSelId {} -> True + _ -> False isNaughtyRecordSelector id = case globalIdDetails id of - RecordSelId { sel_naughty = n } -> n - other -> False + RecordSelId { sel_naughty = n } -> n + _ -> False isClassOpId_maybe id = case globalIdDetails id of ClassOpId cls -> Just cls _other -> Nothing isPrimOpId id = case globalIdDetails id of - PrimOpId op -> True - other -> False + PrimOpId _ -> True + _ -> False isPrimOpId_maybe id = case globalIdDetails id of - PrimOpId op -> Just op - other -> Nothing + PrimOpId op -> Just op + _ -> Nothing isFCallId id = case globalIdDetails id of - FCallId call -> True - other -> False + FCallId _ -> True + _ -> False isFCallId_maybe id = case globalIdDetails id of - FCallId call -> Just call - other -> Nothing + FCallId call -> Just call + _ -> Nothing isDataConWorkId id = case globalIdDetails id of - DataConWorkId _ -> True - other -> False + DataConWorkId _ -> True + _ -> False isDataConWorkId_maybe id = case globalIdDetails id of - DataConWorkId con -> Just con - other -> Nothing + DataConWorkId con -> Just con + _ -> Nothing isDataConId_maybe :: Id -> Maybe DataCon isDataConId_maybe id = case globalIdDetails id of - DataConWorkId con -> Just con - DataConWrapId con -> Just con - other -> Nothing + DataConWorkId con -> Just con + DataConWrapId con -> Just con + _ -> 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 +-- ^ 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 - other -> pprPanic "idDataCon" (ppr id) +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 +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. -- EXCEPT: unboxed tuples, which definitely have no binding hasNoBinding id = case globalIdDetails id of - PrimOpId _ -> True + PrimOpId _ -> True -- See Note [Primop wrappers] FCallId _ -> True DataConWorkId dc -> isUnboxedTupleCon dc - other -> False + _ -> 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 @@ -302,12 +406,27 @@ isImplicitId id -- remember that all type and class decls appear in the interface file. -- The dfun id is not an implicit Id; it must *not* be omitted, because -- it carries version info for the instance decl - other -> False + _ -> False idIsFrom :: Module -> Id -> Bool idIsFrom mod id = nameIsLocalOrFrom mod (idName id) \end{code} +Note [Primop wrappers] +~~~~~~~~~~~~~~~~~~~~~~ +Currently hasNoBinding claims that PrimOpIds don't have a curried +function definition. But actually they do, in GHC.PrimopWrappers, +which is auto-generated from prelude/primops.txt.pp. So actually, hasNoBinding +could return 'False' for PrimOpIds. + +But we'd need to add something in CoreToStg to swizzle any unsaturated +applications of GHC.Prim.plusInt# to GHC.PrimopWrappers.plusInt#. + +Nota Bene: GHC.PrimopWrappers is needed *regardless*, because it's +used by GHCi, which does not implement primops direct at all. + + + \begin{code} isDeadBinder :: Id -> Bool isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr) @@ -318,7 +437,7 @@ isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr) isTickBoxOp :: Id -> Bool isTickBoxOp id = case globalIdDetails id of - TickBoxOpId tick -> True + TickBoxOpId _ -> True _ -> False isTickBoxOp_maybe :: Id -> Maybe TickBoxOp @@ -353,7 +472,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) @@ -368,15 +487,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 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. isStrictId :: Id -> Bool isStrictId id = ASSERT2( isId id, text "isStrictId: not an id: " <+> ppr id ) @@ -501,7 +618,7 @@ isStateHackType ty | otherwise = case splitTyConApp_maybe ty of Just (tycon,_) -> tycon == statePrimTyCon - other -> False + _ -> False -- This is a gross hack. It claims that -- every function over realWorldStatePrimTy is a one-shot -- function. This is pretty true in practice, and makes a big @@ -547,9 +664,42 @@ zapInfo zapper id = maybeModifyIdInfo (zapper (idInfo id)) id zapLamIdInfo :: Id -> Id zapLamIdInfo = zapInfo zapLamInfo +zapDemandIdInfo :: Id -> Id zapDemandIdInfo = zapInfo zapDemandInfo zapFragileIdInfo :: Id -> Id zapFragileIdInfo = zapInfo zapFragileInfo \end{code} +Note [transferPolyIdInfo] +~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we have + + f = /\a. let g = rhs in ... + +where g has interesting strictness information. Then if we float thus + + g' = /\a. rhs + f = /\a. ...[g' a/g] + +we *do not* want to lose the strictness information on g. Nor arity. + +It's simple to retain strictness and arity, but not so simple to retain + worker info + rules +so we simply discard those. Sooner or later this may bite us. + +This transfer is used in two places: + FloatOut (long-distance let-floating) + SimplUtils.abstractFloats (short-distance let-floating) + +\begin{code} +transferPolyIdInfo :: Id -> Id -> Id +transferPolyIdInfo old_id new_id + = modifyIdInfo transfer new_id + where + old_info = idInfo old_id + transfer new_info = new_info `setNewStrictnessInfo` (newStrictnessInfo old_info) + `setArityInfo` (arityInfo old_info) +\end{code} +