[project @ 2001-02-20 15:36:55 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Id.lhs
index 28bc5da..13443a9 100644 (file)
@@ -22,17 +22,14 @@ module Id (
        zapFragileIdInfo, zapLamIdInfo,
 
        -- Predicates
-       omitIfaceSigForId, isDeadBinder,
-       exportWithOrigOccName,
+       isImplicitId, isDeadBinder,
        externallyVisibleId,
-       idFreeTyVars,
-       isIP,
        isSpecPragmaId, isRecordSelector,
-       isPrimOpId, isPrimOpId_maybe, 
-       isDataConId, isDataConId_maybe, isDataConWrapId, 
-               isDataConWrapId_maybe,
+       isPrimOpId, isPrimOpId_maybe, isDictFunId,
+       isDataConId, isDataConId_maybe, 
+       isDataConWrapId, isDataConWrapId_maybe,
        isBottomingId,
-       isExportedId, isUserExportedId,
+       isExportedId, isLocalId, 
        hasNoBinding,
 
        -- Inline pragma stuff
@@ -47,6 +44,7 @@ module Id (
        setIdArityInfo,
        setIdDemandInfo,
        setIdStrictness,
+        setIdTyGenInfo,
        setIdWorkerInfo,
        setIdSpecialisation,
        setIdCafInfo,
@@ -57,6 +55,7 @@ module Id (
        idFlavour,
        idDemandInfo,
        idStrictness,
+        idTyGenInfo,
        idWorkerInfo,
        idUnfolding,
        idSpecialisation,
@@ -80,16 +79,15 @@ import Var          ( Id, DictId,
                          maybeModifyIdInfo,
                          externallyVisibleId
                        )
-import VarSet
-import Type            ( Type, tyVarsOfType, typePrimRep, addFreeTyVars, 
-                         seqType, splitTyConApp_maybe )
+import Type            ( Type, typePrimRep, addFreeTyVars, 
+                          usOnce, seqType, splitTyConApp_maybe )
 
 import IdInfo 
 
 import Demand          ( Demand )
 import Name            ( Name, OccName,
                          mkSysLocalName, mkLocalName,
-                         isUserExportedName, getOccName, isIPOcc
+                         getOccName
                        ) 
 import OccName         ( UserFS )
 import PrimRep         ( PrimRep )
@@ -98,11 +96,13 @@ import FieldLabel   ( FieldLabel )
 import SrcLoc          ( SrcLoc )
 import Unique          ( Unique, mkBuiltinUnique, getBuiltinUniques, 
                          getNumBuiltinUniques )
+import Outputable
 
 infixl         1 `setIdUnfolding`,
          `setIdArityInfo`,
          `setIdDemandInfo`,
          `setIdStrictness`,
+         `setIdTyGenInfo`,
          `setIdWorkerInfo`,
          `setIdSpecialisation`,
          `setInlinePragma`,
@@ -127,10 +127,7 @@ Absolutely all Ids are made by mkId.  It
 
 \begin{code}
 mkId :: Name -> Type -> IdInfo -> Id
-mkId name ty info = mkIdVar name (addFreeTyVars ty) info'
-                 where
-                   info' | isUserExportedName name = setNoDiscardInfo info
-                         | otherwise               = info
+mkId name ty info = mkIdVar name (addFreeTyVars ty) info
 \end{code}
 
 \begin{code}
@@ -162,6 +159,7 @@ mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
                               tys
 
 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
+-- The Int gives the starting point for unique allocation
 mkTemplateLocalsNum n tys = zipWith (mkSysLocal SLIT("tpl"))
                               (getNumBuiltinUniques n (length tys))
                               tys
@@ -178,9 +176,6 @@ mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
 %************************************************************************
 
 \begin{code}
-idFreeTyVars :: Id -> TyVarSet
-idFreeTyVars id = tyVarsOfType (idType id)
-
 setIdType :: Id -> Type -> Id
        -- Add free tyvar info to the type
 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
@@ -248,31 +243,42 @@ hasNoBinding id = case idFlavour id of
        -- binding, even though it is defined in this module.  Notably,
        -- the constructors of a dictionary are in this situation.
 
+isDictFunId id = case idFlavour id of
+                  DictFunId -> True
+                  other     -> False
+
 -- Don't drop a binding for an exported Id,
 -- if it otherwise looks dead.  
+-- Perhaps a better name would be isDiscardableId
 isExportedId :: Id -> Bool
-isExportedId id = isUserExportedId id  -- Try this
-{-
-  case idFlavour id of
-                       VanillaId -> False
-                       other     -> True       -- All the others are no-discard
--}
-
--- Say if an Id was exported by the user
--- Implies isExportedId (see mkId above)
-isUserExportedId :: Id -> Bool
-isUserExportedId id = isUserExportedName (idName id)
+isExportedId id = case idFlavour id of
+                       VanillaId  -> False
+                       other      -> True
+
+isLocalId :: Id -> Bool
+-- True of Ids that are locally defined, but are not constants
+-- like data constructors, record selectors, and the like. 
+-- See comments with CoreFVs.isLocalVar
+isLocalId id 
+#ifdef DEBUG
+  | not (isId id) = pprTrace "isLocalid" (ppr id) False
+  | otherwise
+#endif
+  = case idFlavour id of
+        VanillaId    -> True
+        ExportedId   -> True
+        SpecPragmaId -> True
+        other        -> False
 \end{code}
 
 
-omitIfaceSigForId 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.
 
 \begin{code}
-omitIfaceSigForId :: Id -> Bool
-omitIfaceSigForId id
-  | otherwise
+isImplicitId :: Id -> Bool
+isImplicitId id
   = case idFlavour id of
        RecordSelId _   -> True -- Includes dictionary selectors
         PrimOpId _      -> True
@@ -282,22 +288,13 @@ omitIfaceSigForId id
                -- 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
-
-       other          -> False -- Don't omit!
-
--- Certain names must be exported with their original occ names, because
--- these names are bound by either a class declaration or a data declaration
--- or an explicit user export.
-exportWithOrigOccName :: Id -> Bool
-exportWithOrigOccName id = omitIfaceSigForId id || isUserExportedId id
+       other           -> False
 \end{code}
 
 \begin{code}
 isDeadBinder :: Id -> Bool
 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
                  | otherwise = False   -- TyVars count as not dead
-
-isIP id = isIPOcc (getOccName id)
 \end{code}
 
 
@@ -332,6 +329,14 @@ isBottomingId :: Id -> Bool
 isBottomingId id = isBottomingStrictness (idStrictness 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)
@@ -413,11 +418,14 @@ idLBVarInfo :: Id -> LBVarInfo
 idLBVarInfo id = lbvarInfo (idInfo id)
 
 isOneShotLambda :: Id -> Bool
-isOneShotLambda id = case idLBVarInfo id of
-                       IsOneShotLambda -> True
-                       NoLBVarInfo     -> case splitTyConApp_maybe (idType id) of
-                                               Just (tycon,_) -> tycon == statePrimTyCon
-                                               other          -> False
+isOneShotLambda id = analysis || hack
+  where analysis = case idLBVarInfo id of
+                     LBVarInfo u    | u == 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
@@ -437,7 +445,7 @@ isOneShotLambda id = case idLBVarInfo id of
        -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
 
 setOneShotLambda :: Id -> Id
-setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
+setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id
 
 clearOneShotLambda :: Id -> Id
 clearOneShotLambda id 
@@ -457,13 +465,3 @@ zapLamIdInfo :: Id -> Id
 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
 \end{code}
 
-
-
-
-
-
-
-
-
-
-