X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FbasicTypes%2FId.lhs;h=5ac261255cb787d280a1bd86395b24d2622b6076;hp=e0ccb3e76dce451b03706d571c69a313c22aa3b3;hb=914e415702a25a6e52ab1eaaf2aea233d6c6097e;hpb=8f567db9b9b8d48c3efef7f3c229e5b7cbf3bfe6 diff --git a/compiler/basicTypes/Id.lhs b/compiler/basicTypes/Id.lhs index e0ccb3e..5ac2612 100644 --- a/compiler/basicTypes/Id.lhs +++ b/compiler/basicTypes/Id.lhs @@ -23,19 +23,18 @@ -- * 'Var.Var': see "Var#name_types" module Id ( -- * The main types - Id, DictId, + Var, Id, isId, -- ** Simple construction mkGlobalId, mkVanillaGlobal, mkVanillaGlobalWithInfo, mkLocalId, mkLocalIdWithInfo, mkExportedLocalId, mkSysLocal, mkSysLocalM, mkUserLocal, mkUserLocalM, mkTemplateLocals, mkTemplateLocalsNum, mkTemplateLocal, - mkWorkerId, + mkWorkerId, mkWiredInIdName, -- ** Taking an Id apart idName, idType, idUnique, idInfo, idDetails, - isId, idPrimRep, - recordSelectorFieldLabel, + idPrimRep, recordSelectorFieldLabel, -- ** Modifying an Id setIdName, setIdUnique, Id.setIdType, @@ -46,10 +45,11 @@ module Id ( -- ** Predicates on Ids - isImplicitId, isDeadBinder, isDictId, isStrictId, + isImplicitId, isDeadBinder, + isStrictId, isExportedId, isLocalId, isGlobalId, isRecordSelector, isNaughtyRecordSelector, - isClassOpId_maybe, isDFunId, + isClassOpId_maybe, isDFunId, dfunNSilent, isPrimOpId, isPrimOpId_maybe, isFCallId, isFCallId_maybe, isDataConWorkId, isDataConWorkId_maybe, isDataConId_maybe, idDataCon, @@ -57,6 +57,9 @@ module Id ( isTickBoxOp, isTickBoxOp_maybe, hasNoBinding, + -- ** Evidence variables + DictId, isDictId, isEvVar, evVarPred, + -- ** Inline pragma stuff idInlinePragma, setInlinePragma, modifyInlinePragma, idInlineActivation, setInlineActivation, idRuleMatchInfo, @@ -76,6 +79,7 @@ module Id ( idOccInfo, -- ** Writing 'IdInfo' fields + setIdUnfoldingLazily, setIdUnfolding, setIdArity, setIdDemandInfo, @@ -94,14 +98,13 @@ import IdInfo import BasicTypes -- Imported and re-exported -import Var( Var, Id, DictId, - idInfo, idDetails, globaliseId, +import Var( Var, Id, DictId, EvVar, + idInfo, idDetails, globaliseId, varType, isId, isLocalId, isGlobalId, isExportedId ) import qualified Var import TyCon import Type -import TcType import TysPrim import DataCon import Demand @@ -120,7 +123,8 @@ import Util( count ) import StaticFlags -- infixl so you can say (id `set` a `set` b) -infixl 1 `setIdUnfolding`, +infixl 1 `setIdUnfoldingLazily`, + `setIdUnfolding`, `setIdArity`, `setIdOccInfo`, `setIdDemandInfo`, @@ -171,7 +175,7 @@ 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 + | ASSERT( isId id ) isLocalId id && isInternalName name = id | otherwise = mkLocalIdWithInfo (localiseName name) (idType id) (idInfo id) @@ -259,6 +263,9 @@ 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)) +mkWiredInIdName :: Module -> FastString -> Unique -> Id -> Name +mkWiredInIdName mod fs uniq id + = mkWiredInName mod (mkOccNameFS varName fs) uniq (AnId id) UserSyntax \end{code} Make some local @Ids@ for a template @CoreExpr@. These have bogus @@ -328,8 +335,13 @@ isPrimOpId id = case Var.idDetails id of _ -> False isDFunId id = case Var.idDetails id of - DFunId _ -> True - _ -> False + DFunId {} -> True + _ -> False + +dfunNSilent :: Id -> Int +dfunNSilent id = case Var.idDetails id of + DFunId ns _ -> ns + _ -> pprTrace "dfunSilent: not a dfun:" (ppr id) 0 isPrimOpId_maybe id = case Var.idDetails id of PrimOpId op -> Just op @@ -363,10 +375,6 @@ idDataCon :: Id -> DataCon -- 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 :: Id -> Bool -- ^ Returns @True@ of an 'Id' which may not have a -- binding, even though it is defined in this module. @@ -439,6 +447,26 @@ isTickBoxOp_maybe id = %************************************************************************ %* * + Evidence variables +%* * +%************************************************************************ + +\begin{code} +isEvVar :: Var -> Bool +isEvVar var = isPredTy (varType var) + +isDictId :: Id -> Bool +isDictId id = isDictTy (idType id) + +evVarPred :: EvVar -> PredType +evVarPred var + = case splitPredTy_maybe (varType var) of + Just pred -> pred + Nothing -> pprPanic "evVarPred" (ppr var <+> ppr (varType var)) +\end{code} + +%************************************************************************ +%* * \subsection{IdInfo stuff} %* * %************************************************************************ @@ -494,6 +522,9 @@ realIdUnfolding :: Id -> Unfolding -- Expose the unfolding if there is one, including for loop breakers realIdUnfolding id = unfoldingInfo (idInfo id) +setIdUnfoldingLazily :: Id -> Unfolding -> Id +setIdUnfoldingLazily id unfolding = modifyIdInfo (`setUnfoldingInfoLazily` unfolding) id + setIdUnfolding :: Id -> Unfolding -> Id setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id @@ -652,29 +683,44 @@ zapFragileIdInfo = zapInfo zapFragileInfo Note [transferPolyIdInfo] ~~~~~~~~~~~~~~~~~~~~~~~~~ -Suppose we have +This transfer is used in two places: + FloatOut (long-distance let-floating) + SimplUtils.abstractFloats (short-distance let-floating) + +Consider the short-distance let-floating: f = /\a. let g = rhs in ... -where g has interesting strictness information. Then if we float thus +Then if we float thus g' = /\a. rhs - f = /\a. ...[g' a/g] + f = /\a. ...[g' a/g].... we *do not* want to lose g's * strictness information * arity * inline pragma (though that is bit more debatable) + * occurrence info -It's simple to retain strictness and arity, but not so simple to retain +Mostly this is just an optimisation, but it's *vital* to +transfer the occurrence info. Consider + + NonRec { f = /\a. let Rec { g* = ..g.. } in ... } + +where the '*' means 'LoopBreaker'. Then if we float we must get + + Rec { g'* = /\a. ...(g' a)... } + NonRec { f = /\a. ...[g' a/g]....} + +where g' is also marked as LoopBreaker. If not, terrible things +can happen if we re-simplify the binding (and the Simplifier does +sometimes simplify a term twice); see Trac #4345. + +It's 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) - If we abstract wrt one or more *value* binders, we must modify the arity and strictness info before transferring it. E.g. f = \x. e @@ -697,6 +743,7 @@ transferPolyIdInfo old_id abstract_wrt new_id old_info = idInfo old_id old_arity = arityInfo old_info old_inline_prag = inlinePragInfo old_info + old_occ_info = occInfo old_info new_arity = old_arity + arity_increase old_strictness = strictnessInfo old_info new_strictness = fmap (increaseStrictSigArity arity_increase) old_strictness @@ -704,4 +751,5 @@ transferPolyIdInfo old_id abstract_wrt new_id transfer new_info = new_info `setStrictnessInfo` new_strictness `setArityInfo` new_arity `setInlinePragInfo` old_inline_prag + `setOccInfo` old_occ_info \end{code}