X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FbasicTypes%2FId.lhs;h=070526e2f75916d8c926644c98f9398f19f0cd2f;hb=08652e67c4d5d9a40687f93c286021a867c1bca0;hp=5f43a9dd04998eb8029551301d7d14996e826736;hpb=55710e16202e985f8e4f910a09dfc2d0298ca255;p=ghc-hetmet.git diff --git a/compiler/basicTypes/Id.lhs b/compiler/basicTypes/Id.lhs index 5f43a9d..070526e 100644 --- a/compiler/basicTypes/Id.lhs +++ b/compiler/basicTypes/Id.lhs @@ -22,7 +22,7 @@ module Id ( -- Modifying an Id setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo, - zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, + zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, transferPolyIdInfo, -- Predicates isImplicitId, isDeadBinder, isDictId, isStrictId, @@ -97,6 +97,9 @@ import DataCon import NewDemand import Name import Module +import Class +import PrimOp +import ForeignCall import OccName import Maybes import SrcLoc @@ -133,15 +136,27 @@ 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 +mkLocalIdWithInfo name ty info = Var.mkLocalId name ty info + -- Note [Free type variables] mkExportedLocalId :: Name -> Type -> Id -mkExportedLocalId name ty = Var.mkExportedLocalId name (addFreeTyVars ty) vanillaIdInfo +mkExportedLocalId name ty = Var.mkExportedLocalId name ty vanillaIdInfo + -- Note [Free type variables] mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id -mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info +mkGlobalId details name ty info = Var.mkGlobalId details name ty info \end{code} \begin{code} @@ -154,7 +169,7 @@ 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 +mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id mkVanillaGlobal :: Name -> Type -> IdInfo -> Id mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty @@ -168,14 +183,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 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. 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] @@ -186,7 +201,7 @@ mkTemplateLocalsNum :: Int -> [Type] -> [Id] mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys mkTemplateLocal :: Int -> Type -> Id -mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty +mkTemplateLocal i ty = mkSysLocal (fsLit "tpl") (mkBuiltinUnique i) ty \end{code} @@ -199,7 +214,7 @@ 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) +setIdType id ty = seqType ty `seq` Var.setIdType id ty idPrimRep :: Id -> PrimRep idPrimRep id = typePrimRep (idType id) @@ -216,50 +231,62 @@ idPrimRep id = typePrimRep (idType id) recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) recordSelectorFieldLabel id = case globalIdDetails id of - RecordSelId { sel_tycon = tycon, sel_label = lbl } -> (tycon,lbl) - other -> panic "recordSelectorFieldLabel" + 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 @@ -267,9 +294,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 @@ -282,10 +309,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 @@ -303,12 +330,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) @@ -319,7 +361,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 @@ -502,7 +544,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 @@ -548,9 +590,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} +