Module header tidyup, phase 1
[ghc-hetmet.git] / compiler / basicTypes / Var.lhs
index 4ba7d89..3510828 100644 (file)
@@ -1,4 +1,5 @@
 %
+% (c) The University of Glasgow 2006
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
 \section{@Vars@: Variables}
@@ -10,16 +11,19 @@ module Var (
        setVarName, setVarUnique, 
 
        -- TyVars
-       TyVar, mkTyVar, mkTcTyVar,
+       TyVar, mkTyVar, mkTcTyVar, mkWildCoVar,
        tyVarName, tyVarKind,
-       setTyVarName, setTyVarUnique,
+       setTyVarName, setTyVarUnique, setTyVarKind,
        tcTyVarDetails,
 
+        -- CoVars
+        CoVar, coVarName, setCoVarUnique, setCoVarName, mkCoVar, isCoVar,
+
        -- Ids
        Id, DictId,
        idName, idType, idUnique, idInfo, modifyIdInfo, maybeModifyIdInfo,
        setIdName, setIdUnique, setIdType, setIdInfo, lazySetIdInfo, 
-       setIdExported, setIdNotExported, 
+       setIdExported, setIdNotExported,
 
        globalIdDetails, globaliseId, 
 
@@ -32,17 +36,15 @@ module Var (
 
 #include "HsVersions.h"
 
-import {-# SOURCE #-}  TypeRep( Type )
+import {-# SOURCE #-}  TypeRep( Type, Kind )
 import {-# SOURCE #-}  TcType( TcTyVarDetails, pprTcTyVarDetails )
-import {-# SOURCE #-}  IdInfo( GlobalIdDetails, notGlobalId, IdInfo, seqIdInfo )
-
-import Name            ( Name, NamedThing(..),
-                         setNameUnique, nameUnique
-                       )
-import Kind            ( Kind )
-import Unique          ( Unique, Uniquable(..), mkUniqueGrimily, getKey# )
+import {-# SOURCE #-}  IdInfo( GlobalIdDetails, notGlobalId, 
+                                IdInfo, seqIdInfo )
+import Name hiding (varName)
+import Unique
 import FastTypes
-import Outputable
+import FastString
+import Outputable       
 \end{code}
 
 
@@ -65,22 +67,28 @@ data Var
        realUnique :: FastInt,          -- Key for fast comparison
                                        -- Identical to the Unique in the name,
                                        -- cached here for speed
-       tyVarKind :: Kind }
+       tyVarKind :: Kind,
+        isCoercionVar :: Bool
+ }
 
   | TcTyVar {                          -- Used only during type inference
+                                       -- Used for kind variables during 
+                                       -- inference, as well
        varName        :: !Name,
        realUnique     :: FastInt,
        tyVarKind      :: Kind,
        tcTyVarDetails :: TcTyVarDetails }
 
   | GlobalId {                         -- Used for imported Ids, dict selectors etc
+                               -- See Note [GlobalId/LocalId] below
        varName    :: !Name,    -- Always an External or WiredIn Name
        realUnique :: FastInt,
        idType     :: Type,
        idInfo     :: IdInfo,
        gblDetails :: GlobalIdDetails }
 
-  | LocalId {                  -- Used for locally-defined Ids (see NOTE below)
+  | LocalId {                  -- Used for locally-defined Ids 
+                               -- See Note [GlobalId/LocalId] below
        varName    :: !Name,
        realUnique :: FastInt,
        idType     :: Type,
@@ -94,17 +102,20 @@ data LocalIdDetails
   -- NotExported things may be discarded as dead code.
 \end{code}
 
-LocalId and GlobalId
-~~~~~~~~~~~~~~~~~~~~
+Note [GlobalId/LocalId]
+~~~~~~~~~~~~~~~~~~~~~~~
 A GlobalId is
   * always a constant (top-level)
   * imported, or data constructor, or primop, or record selector
   * has a Unique that is globally unique across the whole
     GHC invocation (a single invocation may compile multiple modules)
+  * never treated as a candidate by the free-variable finder;
+       it's a constant!
 
 A LocalId is 
   * bound within an expression (lambda, case, local let(rec))
   * or defined at top level in the module being compiled
+  * always treated as a candidate by the free-variable finder
 
 After CoreTidy, top-level LocalIds are turned into GlobalIds
  
@@ -169,6 +180,9 @@ tyVarName = varName
 
 setTyVarUnique = setVarUnique
 setTyVarName   = setVarName
+
+setTyVarKind :: TyVar -> Kind -> TyVar
+setTyVarKind tv k = tv {tyVarKind = k}
 \end{code}
 
 \begin{code}
@@ -176,6 +190,7 @@ mkTyVar :: Name -> Kind -> TyVar
 mkTyVar name kind = TyVar { varName    = name
                          , realUnique = getKey# (nameUnique name)
                          , tyVarKind  = kind
+                          , isCoercionVar    = False
                        }
 
 mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
@@ -185,8 +200,41 @@ mkTcTyVar name kind details
                tyVarKind  = kind,
                tcTyVarDetails = details
        }
+
+mkWildCoVar :: Kind -> TyVar
+-- A type variable that is never referred to,
+-- so its unique doesn't matter
+mkWildCoVar kind 
+  = TyVar { varName = mkSysTvName wild_uniq FSLIT("co_wild"),
+            realUnique = _ILIT(1),
+            tyVarKind = kind,
+            isCoercionVar = True }
+  where
+    wild_uniq = mkBuiltinUnique 1
 \end{code}
 
+%************************************************************************
+%*                                                                     *
+\subsection{Coercion variables}
+%*                                                                     *
+%************************************************************************
+
+\begin{code}
+type CoVar = Var       -- A coercion variable is simply a type 
+                       -- variable of kind (ty1 :=: ty2)
+coVarName = varName
+
+setCoVarUnique = setVarUnique
+setCoVarName   = setVarName
+
+mkCoVar :: Name -> Kind -> CoVar
+mkCoVar name kind = TyVar { varName    = name
+                         , realUnique = getKey# (nameUnique name)
+                         , tyVarKind  = kind
+                          , isCoercionVar    = True
+                       }
+
+\end{code}
 
 %************************************************************************
 %*                                                                     *
@@ -246,11 +294,9 @@ modifyIdInfo fn id
     new_info = fn (idInfo id)
 
 -- maybeModifyIdInfo tries to avoid unnecesary thrashing
-maybeModifyIdInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id
-maybeModifyIdInfo fn id
-  = case fn (idInfo id) of
-       Nothing       -> id
-       Just new_info -> id {idInfo = new_info}
+maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
+maybeModifyIdInfo (Just new_info) id = id {idInfo = new_info}
+maybeModifyIdInfo Nothing        id = id
 \end{code}
 
 %************************************************************************
@@ -303,6 +349,9 @@ isId other     = False
 isLocalId (LocalId {}) = True
 isLocalId other               = False
 
+isCoVar (v@(TyVar {})) = isCoercionVar v
+isCoVar other          = False
+
 -- isLocalVar returns True for type variables as well as local Ids
 -- These are the variables that we need to pay attention to when finding free
 -- variables, or doing dependency analysis.