Use OPTIONS rather than OPTIONS_GHC for pragmas
[ghc-hetmet.git] / compiler / basicTypes / Var.lhs
index 60fdf38..f2bef26 100644 (file)
@@ -1,25 +1,36 @@
 %
+% (c) The University of Glasgow 2006
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
 \section{@Vars@: Variables}
 
 \begin{code}
+{-# OPTIONS -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings
+-- for details
+
 module Var (
        Var, 
-       varName, varUnique, 
+       varName, varUnique, varType,
        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 +43,19 @@ 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 )
+#ifdef DEBUG
+import {-# SOURCE #-}  TypeRep( isCoercionKind )
+#endif
+
+import Name hiding (varName)
+import Unique
 import FastTypes
-import Outputable
+import FastString
+import Outputable       
 \end{code}
 
 
@@ -65,26 +78,32 @@ data Var
        realUnique :: FastInt,          -- Key for fast comparison
                                        -- Identical to the Unique in the name,
                                        -- cached here for speed
-       tyVarKind :: Kind }
+       varType       :: Kind,
+        isCoercionVar :: Bool
+ }
 
   | TcTyVar {                          -- Used only during type inference
+                                       -- Used for kind variables during 
+                                       -- inference, as well
        varName        :: !Name,
        realUnique     :: FastInt,
-       tyVarKind      :: Kind,
+       varType        :: Kind,
        tcTyVarDetails :: TcTyVarDetails }
 
   | GlobalId {                         -- Used for imported Ids, dict selectors etc
-       varName    :: !Name,
+                               -- See Note [GlobalId/LocalId] below
+       varName    :: !Name,    -- Always an External or WiredIn Name
        realUnique :: FastInt,
-       idType     :: Type,
-       idInfo     :: IdInfo,
+       varType    :: 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,
-       idInfo     :: IdInfo,
+       varType    :: Type,
+       idInfo_    :: IdInfo,
        lclDetails :: LocalIdDetails }
 
 data LocalIdDetails 
@@ -94,17 +113,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
  
@@ -166,27 +188,69 @@ setVarName var new_name
 type TyVar = Var
 
 tyVarName = varName
+tyVarKind = varType
 
 setTyVarUnique = setVarUnique
 setTyVarName   = setVarName
+
+setTyVarKind :: TyVar -> Kind -> TyVar
+setTyVarKind tv k = tv {varType = k}
 \end{code}
 
 \begin{code}
 mkTyVar :: Name -> Kind -> TyVar
-mkTyVar name kind = TyVar { varName    = name
+mkTyVar name kind = ASSERT( not (isCoercionKind kind ) )
+                   TyVar { varName    = name
                          , realUnique = getKey# (nameUnique name)
-                         , tyVarKind  = kind
+                         , varType  = kind
+                          , isCoercionVar    = False
                        }
 
 mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
 mkTcTyVar name kind details
-  = TcTyVar {  varName    = name,
+  = -- TOM: no longer valid assertion? 
+    -- ASSERT( not (isCoercionKind kind) )
+    TcTyVar {  varName    = name,
                realUnique = getKey# (nameUnique name),
-               tyVarKind  = kind,
+               varType  = kind,
                tcTyVarDetails = details
        }
 \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 = ASSERT( isCoercionKind kind )
+                   TyVar { varName    = name
+                         , realUnique = getKey# (nameUnique name)
+                         , varType  = kind
+                          , isCoercionVar    = True
+                       }
+
+mkWildCoVar :: Kind -> TyVar
+-- A type variable that is never referred to,
+-- so its unique doesn't matter
+mkWildCoVar kind 
+  = ASSERT( isCoercionKind kind )
+    TyVar { varName = mkSysTvName wild_uniq FSLIT("co_wild"),
+            realUnique = _ILIT(1),
+            varType = kind,
+            isCoercionVar = True }
+  where
+    wild_uniq = mkBuiltinUnique 1
+\end{code}
 
 %************************************************************************
 %*                                                                     *
@@ -204,6 +268,7 @@ type DictId = Id
 \begin{code}
 idName    = varName
 idUnique  = varUnique
+idType    = varType
 
 setIdUnique :: Id -> Unique -> Id
 setIdUnique = setVarUnique
@@ -212,7 +277,7 @@ setIdName :: Id -> Name -> Id
 setIdName = setVarName
 
 setIdType :: Id -> Type -> Id
-setIdType id ty = id {idType = ty}
+setIdType id ty = id {varType = ty}
 
 setIdExported :: Id -> Id
 -- Can be called on GlobalIds, such as data cons and class ops,
@@ -228,29 +293,32 @@ globaliseId :: GlobalIdDetails -> Id -> Id
 -- If it's a local, make it global
 globaliseId details id = GlobalId { varName    = varName id,
                                    realUnique = realUnique id,
-                                   idType     = idType id,
-                                   idInfo     = idInfo id,
+                                   varType    = varType id,
+                                   idInfo_    = idInfo id,
                                    gblDetails = details }
 
+idInfo :: Id -> IdInfo
+idInfo (GlobalId {idInfo_ = info}) = info
+idInfo (LocalId  {idInfo_ = info}) = info
+idInfo other_var                  = pprPanic "idInfo" (ppr other_var)
+
 lazySetIdInfo :: Id -> IdInfo -> Id
-lazySetIdInfo id info = id {idInfo = info}
+lazySetIdInfo id info = id {idInfo_ = info}
 
 setIdInfo :: Id -> IdInfo -> Id
-setIdInfo id info = seqIdInfo info `seq` id {idInfo = info}
+setIdInfo id info = seqIdInfo info `seq` id {idInfo_ = info}
        -- Try to avoid spack leaks by seq'ing
 
 modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
 modifyIdInfo fn id
-  = seqIdInfo new_info `seq` id {idInfo = new_info}
+  = seqIdInfo new_info `seq` id {idInfo_ = new_info}
   where
     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}
 
 %************************************************************************
@@ -264,17 +332,17 @@ mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
 mkGlobalId details name ty info 
   = GlobalId { varName    = name, 
                realUnique = getKey# (nameUnique name),         -- Cache the unique
-               idType     = ty,        
+               varType     = ty,       
                gblDetails = details,
-               idInfo     = info }
+               idInfo_    = info }
 
 mk_local_id :: Name -> Type -> LocalIdDetails -> IdInfo -> Id
 mk_local_id name ty details info
   = LocalId {  varName    = name, 
                realUnique = getKey# (nameUnique name),         -- Cache the unique
-               idType     = ty,        
+               varType     = ty,       
                lclDetails = details,
-               idInfo     = info }
+               idInfo_    = info }
 
 mkLocalId :: Name -> Type -> IdInfo -> Id
 mkLocalId name ty info = mk_local_id name ty NotExported info
@@ -303,6 +371,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.