X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FbasicTypes%2FId.lhs;h=d8ae31dc3efdda762d13591dc52908f3455cb867;hb=b4d00dc0af1f633aa4a4fd519142cc2d466ede79;hp=8f955d31fd646d506f85541ad64bcfaae9eef2a8;hpb=b7d8dffaf1fefdf2f6b52fcf039a06843a28d586;p=ghc-hetmet.git diff --git a/compiler/basicTypes/Id.lhs b/compiler/basicTypes/Id.lhs index 8f955d3..d8ae31d 100644 --- a/compiler/basicTypes/Id.lhs +++ b/compiler/basicTypes/Id.lhs @@ -1,4 +1,5 @@ % +% (c) The University of Glasgow 2006 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[Id]{@Ids@: Value and constructor identifiers} @@ -21,10 +22,10 @@ module Id ( -- Modifying an Id setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo, - zapLamIdInfo, zapDemandIdInfo, + zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, -- Predicates - isImplicitId, isDeadBinder, isDictId, + isImplicitId, isDeadBinder, isDictId, isStrictId, isExportedId, isLocalId, isGlobalId, isRecordSelector, isNaughtyRecordSelector, isClassOpId_maybe, @@ -32,6 +33,7 @@ module Id ( isFCallId, isFCallId_maybe, isDataConWorkId, isDataConWorkId_maybe, isDataConId_maybe, idDataCon, isBottomingId, idIsFrom, + isTickBoxOp, isTickBoxOp_maybe, hasNoBinding, -- Inline pragma stuff @@ -79,42 +81,32 @@ module Id ( #include "HsVersions.h" - -import CoreSyn ( Unfolding, CoreRule ) -import BasicTypes ( Arity ) -import Var ( Id, DictId, - isId, isExportedId, isLocalId, - idName, idType, idUnique, idInfo, isGlobalId, - setIdName, setIdType, setIdUnique, - setIdExported, setIdNotExported, - setIdInfo, lazySetIdInfo, modifyIdInfo, - maybeModifyIdInfo, - globalIdDetails - ) -import qualified Var ( mkLocalId, mkGlobalId, mkExportedLocalId ) -import TyCon ( FieldLabel, TyCon ) -import Type ( Type, typePrimRep, addFreeTyVars, seqType, - splitTyConApp_maybe, PrimRep ) -import TcType ( isDictTy ) -import TysPrim ( statePrimTyCon ) +import CoreSyn +import BasicTypes +import qualified Var +import Var hiding (mkLocalId, mkGlobalId, mkExportedLocalId) +import TyCon +import Type +import TcType +import TysPrim import IdInfo - #ifdef OLD_STRICTNESS -import qualified Demand ( Demand ) +import qualified Demand #endif -import DataCon ( DataCon, isUnboxedTupleCon ) -import NewDemand ( Demand, StrictSig, topDmd, topSig, isBottomingSig ) -import Name ( Name, OccName, nameIsLocalOrFrom, - mkSystemVarName, mkInternalName, getOccName, - getSrcLoc ) -import Module ( Module ) -import OccName ( mkWorkerOcc ) -import Maybes ( orElse ) -import SrcLoc ( SrcLoc ) +import DataCon +import NewDemand +import Name +import Module +import Class +import PrimOp +import ForeignCall +import OccName +import Maybes +import SrcLoc import Outputable -import Unique ( Unique, mkBuiltinUnique ) -import FastString ( FastString ) -import StaticFlags ( opt_NoStateHack ) +import Unique +import FastString +import StaticFlags -- infixl so you can say (id `set` a `set` b) infixl 1 `setIdUnfolding`, @@ -160,13 +152,14 @@ mkLocalId :: Name -> Type -> Id mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo -- SysLocal: for an Id being created by the compiler out of thin air... +mkSysLocal :: FastString -> Unique -> Type -> Id +mkSysLocal fs uniq ty = mkLocalId (mkSystemVarName uniq fs) ty + + -- UserLocal: an Id with a name the user might recognize... -mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id -mkSysLocal :: FastString -> Unique -> Type -> Id +mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id mkVanillaGlobal :: Name -> Type -> IdInfo -> Id -mkSysLocal fs uniq ty = mkLocalId (mkSystemVarName uniq fs) ty - mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty mkVanillaGlobal = mkGlobalId VanillaGlobal \end{code} @@ -185,7 +178,7 @@ mkWorkerId :: Unique -> Id -> Type -> Id 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) -- "Template locals" typically used in unfoldings mkTemplateLocals :: [Type] -> [Id] @@ -224,51 +217,64 @@ 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 :: Var -> Bool +isNaughtyRecordSelector :: Var -> Bool +isPrimOpId :: Var -> Bool +isFCallId :: Var -> Bool +isDataConWorkId :: Var -> Bool +hasNoBinding :: Var -> Bool + +isClassOpId_maybe :: Var -> Maybe Class +isPrimOpId_maybe :: Var -> Maybe PrimOp +isFCallId_maybe :: Var -> Maybe ForeignCall +isDataConWorkId_maybe :: Var -> 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 @@ -276,9 +282,9 @@ idDataCon :: Id -> DataCon -- 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) + DataConWorkId con -> con + DataConWrapId con -> con + _ -> pprPanic "idDataCon" (ppr id) isDictId :: Id -> Bool @@ -291,10 +297,10 @@ isDictId id = isDictTy (idType id) -- 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 @@ -312,18 +318,46 @@ 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) | otherwise = False -- TyVars count as not dead \end{code} +\begin{code} +isTickBoxOp :: Id -> Bool +isTickBoxOp id = + case globalIdDetails id of + TickBoxOpId _ -> True + _ -> False + +isTickBoxOp_maybe :: Id -> Maybe TickBoxOp +isTickBoxOp_maybe id = + case globalIdDetails id of + TickBoxOpId tick -> Just tick + _ -> Nothing +\end{code} %************************************************************************ %* * @@ -365,6 +399,20 @@ 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} +isStrictId :: Id -> Bool +isStrictId id + = ASSERT2( isId id, text "isStrictId: not an id: " <+> ppr id ) + (isStrictDmd (idNewDemandInfo id)) || + (isStrictType (idType id)) --------------------------------- -- WORKER ID @@ -475,7 +523,7 @@ idLBVarInfo id = lbvarInfo (idInfo id) 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)) +isOneShotBndr id = isOneShotLambda id || isStateHackType (idType id) isStateHackType :: Type -> Bool isStateHackType ty @@ -484,7 +532,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 @@ -524,9 +572,16 @@ clearOneShotLambda id \end{code} \begin{code} +zapInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id +zapInfo zapper id = maybeModifyIdInfo (zapper (idInfo id)) id + zapLamIdInfo :: Id -> Id -zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id +zapLamIdInfo = zapInfo zapLamInfo + +zapDemandIdInfo :: Id -> Id +zapDemandIdInfo = zapInfo zapDemandInfo -zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id +zapFragileIdInfo :: Id -> Id +zapFragileIdInfo = zapInfo zapFragileInfo \end{code}