X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FId.lhs;h=b810376efa156d251492a7a7ee58ec5dcee43bea;hb=ed5abcc97716009f048ca04084226aee2b99b474;hp=9047cd798ce223ff52575004d581c512b6ccf023;hpb=5e3f005d3012472e422d4ffd7dca5c21a80fca80;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Id.lhs b/ghc/compiler/basicTypes/Id.lhs index 9047cd7..b810376 100644 --- a/ghc/compiler/basicTypes/Id.lhs +++ b/ghc/compiler/basicTypes/Id.lhs @@ -9,7 +9,7 @@ module Id ( -- Simple construction mkGlobalId, mkLocalId, mkSpecPragmaId, mkLocalIdWithInfo, - mkSysLocal, mkUserLocal, mkVanillaGlobal, + mkSysLocal, mkSysLocalUnencoded, mkUserLocal, mkVanillaGlobal, mkTemplateLocals, mkTemplateLocalsNum, mkWildId, mkTemplateLocal, mkWorkerId, @@ -29,7 +29,7 @@ module Id ( isRecordSelector, isPrimOpId, isPrimOpId_maybe, isFCallId, isFCallId_maybe, - isDataConId, isDataConId_maybe, + isDataConWorkId, isDataConWorkId_maybe, isDataConWrapId, isDataConWrapId_maybe, isBottomingId, hasNoBinding, @@ -44,36 +44,42 @@ module Id ( -- IdInfo stuff setIdUnfolding, setIdArity, - setIdDemandInfo, setIdNewDemandInfo, - setIdStrictness, setIdNewStrictness, zapIdNewStrictness, - setIdTyGenInfo, + setIdNewDemandInfo, + setIdNewStrictness, zapIdNewStrictness, setIdWorkerInfo, setIdSpecialisation, - setIdCgInfo, - setIdCprInfo, + setIdCafInfo, setIdOccInfo, +#ifdef OLD_STRICTNESS + idDemandInfo, + idStrictness, + idCprInfo, + setIdStrictness, + setIdDemandInfo, + setIdCprInfo, +#endif + idArity, - idDemandInfo, idNewDemandInfo, - idStrictness, idNewStrictness, idNewStrictness_maybe, - idTyGenInfo, + idNewDemandInfo, idNewDemandInfo_maybe, + idNewStrictness, idNewStrictness_maybe, idWorkerInfo, idUnfolding, - idSpecialisation, - idCgInfo, + idSpecialisation, idCoreRules, idCafInfo, - idCprInfo, idLBVarInfo, idOccInfo, +#ifdef OLD_STRICTNESS newStrictnessFromOld -- Temporary +#endif ) where #include "HsVersions.h" -import CoreSyn ( Unfolding, CoreRules ) +import CoreSyn ( Unfolding, CoreRules, IdCoreRule, rulesRules ) import BasicTypes ( Arity ) import Var ( Id, DictId, isId, isExportedId, isSpecPragmaId, isLocalId, @@ -85,39 +91,41 @@ import Var ( Id, DictId, ) import qualified Var ( mkLocalId, mkGlobalId, mkSpecPragmaId ) import Type ( Type, typePrimRep, addFreeTyVars, - usOnce, eqUsage, seqType, splitTyConApp_maybe ) + seqType, splitTyConApp_maybe ) import IdInfo +#ifdef OLD_STRICTNESS import qualified Demand ( Demand ) -import NewDemand ( Demand, StrictSig, topSig, isBottomingSig ) +#endif +import DataCon ( isUnboxedTupleCon ) +import NewDemand ( Demand, StrictSig, topDmd, topSig, isBottomingSig ) import Name ( Name, OccName, - mkSysLocalName, mkLocalName, + mkSystemName, mkSystemNameEncoded, mkInternalName, getOccName, getSrcLoc ) -import OccName ( UserFS, mkWorkerOcc ) +import OccName ( EncodedFS, mkWorkerOcc ) import PrimRep ( PrimRep ) -import TysPrim ( statePrimTyCon ) import FieldLabel ( FieldLabel ) import Maybes ( orElse ) import SrcLoc ( SrcLoc ) import Outputable import Unique ( Unique, mkBuiltinUnique ) +-- infixl so you can say (id `set` a `set` b) infixl 1 `setIdUnfolding`, `setIdArity`, - `setIdDemandInfo`, - `setIdStrictness`, `setIdNewDemandInfo`, `setIdNewStrictness`, - `setIdTyGenInfo`, `setIdWorkerInfo`, `setIdSpecialisation`, `setInlinePragma`, - `idCafInfo`, - `idCprInfo` - - -- infixl so you can say (id `set` a `set` b) + `idCafInfo` +#ifdef OLD_STRICTNESS + ,`idCprInfo` + ,`setIdStrictness` + ,`setIdDemandInfo` +#endif \end{code} @@ -150,11 +158,17 @@ mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo -- SysLocal: for an Id being created by the compiler out of thin air... -- UserLocal: an Id with a name the user might recognize... mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id -mkSysLocal :: UserFS -> Unique -> Type -> Id +mkSysLocal :: EncodedFS -> Unique -> Type -> Id mkVanillaGlobal :: Name -> Type -> IdInfo -> Id -mkSysLocal fs uniq ty = mkLocalId (mkSysLocalName uniq fs) ty -mkUserLocal occ uniq ty loc = mkLocalId (mkLocalName uniq occ loc) ty +-- for SysLocal, we assume the base name is already encoded, to avoid +-- re-encoding the same string over and over again. +mkSysLocal fs uniq ty = mkLocalId (mkSystemNameEncoded uniq fs) ty + +-- version to use when the faststring needs to be encoded +mkSysLocalUnencoded fs uniq ty = mkLocalId (mkSystemName uniq fs) ty + +mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty mkVanillaGlobal = mkGlobalId VanillaGlobal \end{code} @@ -165,14 +179,14 @@ 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 SLIT("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 globalise it if necessary. +-- A worker gets a local name. CoreTidy will externalise it if necessary. mkWorkerId uniq unwrkr ty = mkLocalId wkr_name ty where - wkr_name = mkLocalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr) + wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr) -- "Template locals" typically used in unfoldings mkTemplateLocals :: [Type] -> [Id] @@ -183,7 +197,7 @@ mkTemplateLocalsNum :: Int -> [Type] -> [Id] mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys mkTemplateLocal :: Int -> Type -> Id -mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty +mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty \end{code} @@ -245,13 +259,13 @@ isFCallId_maybe id = case globalIdDetails id of FCallId call -> Just call other -> Nothing -isDataConId id = case globalIdDetails id of - DataConId _ -> True - other -> False +isDataConWorkId id = case globalIdDetails id of + DataConWorkId _ -> True + other -> False -isDataConId_maybe id = case globalIdDetails id of - DataConId con -> Just con - other -> Nothing +isDataConWorkId_maybe id = case globalIdDetails id of + DataConWorkId con -> Just con + other -> Nothing isDataConWrapId_maybe id = case globalIdDetails id of DataConWrapId con -> Just con @@ -265,11 +279,13 @@ isDataConWrapId id = case globalIdDetails id of -- 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. +-- them at the CorePrep stage. +-- EXCEPT: unboxed tuples, which definitely have no binding hasNoBinding id = case globalIdDetails id of - PrimOpId _ -> True - FCallId _ -> True - other -> False + PrimOpId _ -> True + FCallId _ -> True + DataConWorkId dc -> isUnboxedTupleCon dc + other -> False isImplicitId :: Id -> Bool -- isImplicitId tells whether an Id's info is implied by other @@ -277,15 +293,17 @@ isImplicitId :: Id -> Bool -- file, even if it's mentioned in some other interface unfolding. isImplicitId id = case globalIdDetails id of - RecordSelId _ -> True -- Includes dictionary selectors + RecordSelId _ -> True FCallId _ -> True PrimOpId _ -> True - DataConId _ -> True + ClassOpId _ -> True + GenericOpId _ -> True + DataConWorkId _ -> True DataConWrapId _ -> True -- These are are implied by their type or class decl; -- remember that all type and class decls appear in the interface file. - -- The dfun id must *not* be omitted, because it carries version info for - -- the instance decl + -- The dfun id is not an implicit Id; it must *not* be omitted, because + -- it carries version info for the instance decl other -> False \end{code} @@ -311,13 +329,15 @@ idArity id = arityInfo (idInfo id) setIdArity :: Id -> Arity -> Id setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id +#ifdef OLD_STRICTNESS --------------------------------- - -- STRICTNESS + -- (OLD) STRICTNESS idStrictness :: Id -> StrictnessInfo idStrictness id = strictnessInfo (idInfo id) 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 isBottomingId :: Id -> Bool @@ -336,14 +356,6 @@ zapIdNewStrictness :: Id -> Id zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id --------------------------------- - -- TYPE GENERALISATION -idTyGenInfo :: Id -> TyGenInfo -idTyGenInfo id = tyGenInfo (idInfo id) - -setIdTyGenInfo :: Id -> TyGenInfo -> Id -setIdTyGenInfo id tygen_info = modifyIdInfo (`setTyGenInfo` tygen_info) id - - --------------------------------- -- WORKER ID idWorkerInfo :: Id -> WorkerInfo idWorkerInfo id = workerInfo (idInfo id) @@ -359,60 +371,59 @@ idUnfolding id = unfoldingInfo (idInfo id) setIdUnfolding :: Id -> Unfolding -> Id setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id +#ifdef OLD_STRICTNESS --------------------------------- - -- DEMAND + -- (OLD) DEMAND idDemandInfo :: Id -> Demand.Demand idDemandInfo id = demandInfo (idInfo id) setIdDemandInfo :: Id -> Demand.Demand -> Id setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id +#endif + +idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand +idNewDemandInfo :: Id -> NewDemand.Demand -idNewDemandInfo :: Id -> NewDemand.Demand -idNewDemandInfo id = newDemandInfo (idInfo id) +idNewDemandInfo_maybe id = newDemandInfo (idInfo id) +idNewDemandInfo id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id -setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` dmd) id +setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id --------------------------------- -- SPECIALISATION idSpecialisation :: Id -> CoreRules idSpecialisation id = specInfo (idInfo id) +idCoreRules :: Id -> [IdCoreRule] +idCoreRules id = [(id,rule) | rule <- rulesRules (idSpecialisation id)] + setIdSpecialisation :: Id -> CoreRules -> Id setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id --------------------------------- - -- CG INFO -idCgInfo :: Id -> CgInfo -#ifdef DEBUG -idCgInfo id = case cgInfo (idInfo id) of - NoCgInfo -> pprPanic "idCgInfo" (ppr id) - info -> info -#else -idCgInfo id = cgInfo (idInfo id) -#endif - -setIdCgInfo :: Id -> CgInfo -> Id -setIdCgInfo id cg_info = modifyIdInfo (`setCgInfo` cg_info) id - - --------------------------------- -- CAF INFO idCafInfo :: Id -> CafInfo -#ifdef DEBUG +#ifdef OLD_STRICTNESS idCafInfo id = case cgInfo (idInfo id) of NoCgInfo -> pprPanic "idCafInfo" (ppr id) info -> cgCafInfo info #else -idCafInfo id = cgCafInfo (idCgInfo id) +idCafInfo id = cafInfo (idInfo id) #endif +setIdCafInfo :: Id -> CafInfo -> Id +setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id + --------------------------------- -- CPR INFO +#ifdef OLD_STRICTNESS idCprInfo :: Id -> CprInfo idCprInfo id = cprInfo (idInfo id) setIdCprInfo :: Id -> CprInfo -> Id setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id +#endif --------------------------------- -- Occcurrence INFO @@ -448,34 +459,12 @@ idLBVarInfo :: Id -> LBVarInfo idLBVarInfo id = lbvarInfo (idInfo id) isOneShotLambda :: Id -> Bool -isOneShotLambda id = analysis || hack - where analysis = case idLBVarInfo id of - LBVarInfo u | u `eqUsage` usOnce -> True - other -> False - hack = case splitTyConApp_maybe (idType id) of - Just (tycon,_) | tycon == statePrimTyCon -> True - other -> False - - -- The last clause 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 - -- difference. For example, consider - -- a `thenST` \ r -> ...E... - -- The early full laziness pass, if it doesn't know that r is one-shot - -- will pull out E (let's say it doesn't mention r) to give - -- let lvl = E in a `thenST` \ r -> ...lvl... - -- When `thenST` gets inlined, we end up with - -- let lvl = E in \s -> case a s of (r, s') -> ...lvl... - -- and we don't re-inline E. - -- - -- It would be better to spot that r was one-shot to start with, but - -- I don't want to rely on that. - -- - -- Another good example is in fill_in in PrelPack.lhs. We should be able to - -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet. +isOneShotLambda id = case idLBVarInfo id of + IsOneShotLambda -> True + NoLBVarInfo -> False setOneShotLambda :: Id -> Id -setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id +setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id clearOneShotLambda :: Id -> Id clearOneShotLambda id