Super-monster patch implementing the new typechecker -- at last
[ghc-hetmet.git] / compiler / basicTypes / Var.lhs
index c1a9370..a0fa921 100644 (file)
@@ -25,8 +25,8 @@
 -- Global 'Id's and 'Var's are those that are imported or correspond to a data constructor, primitive operation, or record selectors.
 -- Local 'Id's and 'Var's are those bound within an expression (e.g. by a lambda) or at the top level of the module being compiled.
 module Var (
-        -- * The main data type
-       Var,
+        -- * The main data type and synonyms
+       Var, TyVar, CoVar, Id, DictId, DFunId, EvVar, EvId, IpId,
 
        -- ** Taking 'Var's apart
        varName, varUnique, varType, 
@@ -41,14 +41,11 @@ module Var (
        setIdExported, setIdNotExported,
 
         -- ** Predicates
-        isCoVar, isId, isTyVar, isTcTyVar,
+        isCoVar, isId, isTyCoVar, isTyVar, isTcTyVar,
         isLocalVar, isLocalId,
        isGlobalId, isExportedId,
        mustHaveLocalBinding,
 
-       -- * Type variable data type
-       TyVar,
-
        -- ** Constructing 'TyVar's
        mkTyVar, mkTcTyVar, mkWildCoVar,
 
@@ -58,9 +55,6 @@ module Var (
        -- ** Modifying 'TyVar's
        setTyVarName, setTyVarUnique, setTyVarKind,
 
-        -- * Coercion variable data type
-        CoVar,
-
         -- ** Constructing 'CoVar's
         mkCoVar,
 
@@ -68,13 +62,12 @@ module Var (
         coVarName,
 
         -- ** Modifying 'CoVar's
-        setCoVarUnique, setCoVarName,
+        setCoVarUnique, setCoVarName
 
-       -- * 'Var' type synonyms
-       Id, DictId
     ) where
 
 #include "HsVersions.h"
+#include "Typeable.h"
 
 import {-# SOURCE #-}  TypeRep( Type, Kind )
 import {-# SOURCE #-}  TcType( TcTyVarDetails, pprTcTyVarDetails )
@@ -83,14 +76,41 @@ import {-# SOURCE #-}       TypeRep( isCoercionKind )
 
 import Name hiding (varName)
 import Unique
+import Util
 import FastTypes
 import FastString
 import Outputable
+
+import Data.Data
 \end{code}
 
 
 %************************************************************************
 %*                                                                     *
+                     Synonyms                                                                  
+%*                                                                     *
+%************************************************************************
+-- These synonyms are here and not in Id because otherwise we need a very
+-- large number of SOURCE imports of Id.hs :-(
+
+\begin{code}
+type EvVar = Var       -- An evidence variable: dictionary or equality constraint
+                       -- Could be an DictId or a CoVar
+
+type Id     = Var       -- A term-level identifier
+type DFunId = Id       -- A dictionary function
+type EvId   = Id        -- Term-level evidence: DictId or IpId
+type DictId = EvId     -- A dictionary variable
+type IpId   = EvId      -- A term-level implicit parameter
+
+type TyVar = Var
+type CoVar = TyVar     -- A coercion variable is simply a type 
+                       -- variable of kind @ty1 ~ ty2@. Hence its
+                       -- 'varType' is always @PredTy (EqPred t1 t2)@
+\end{code}
+
+%************************************************************************
+%*                                                                     *
 \subsection{The main data type declarations}
 %*                                                                     *
 %************************************************************************
@@ -120,15 +140,15 @@ data Var
        varName        :: !Name,
        realUnique     :: FastInt,
        varType        :: Kind,
-       tcTyVarDetails :: TcTyVarDetails }
+       tc_tv_details  :: TcTyVarDetails }
 
   | Id {
        varName    :: !Name,
        realUnique :: FastInt,
        varType    :: Type,
        idScope    :: IdScope,
-       idDetails  :: IdDetails,        -- Stable, doesn't change
-       idInfo     :: IdInfo }          -- Unstable, updated by simplifier
+       id_details :: IdDetails,        -- Stable, doesn't change
+       id_info    :: IdInfo }          -- Unstable, updated by simplifier
 
 data IdScope   -- See Note [GlobalId/LocalId]
   = GlobalId 
@@ -137,7 +157,6 @@ data IdScope        -- See Note [GlobalId/LocalId]
 data ExportFlag 
   = NotExported        -- ^ Not exported: may be discarded as dead code.
   | Exported   -- ^ Exported: kept alive
-
 \end{code}
 
 Note [GlobalId/LocalId]
@@ -163,8 +182,8 @@ instance Outputable Var where
 
 ppr_debug :: Var -> SDoc
 ppr_debug (TyVar {})                          = ptext (sLit "tv")
-ppr_debug (TcTyVar {tcTyVarDetails = d})      = pprTcTyVarDetails d
-ppr_debug (Id { idScope = s, idDetails = d }) = ppr_id_scope s <> pprIdDetails d
+ppr_debug (TcTyVar {tc_tv_details = d})       = pprTcTyVarDetails d
+ppr_debug (Id { idScope = s, id_details = d }) = ppr_id_scope s <> pprIdDetails d
 
 ppr_id_scope :: IdScope -> SDoc
 ppr_id_scope GlobalId              = ptext (sLit "gid")
@@ -189,6 +208,14 @@ instance Ord Var where
     a >= b = realUnique a >=# realUnique b
     a >         b = realUnique a >#  realUnique b
     a `compare` b = varUnique a `compare` varUnique b
+
+INSTANCE_TYPEABLE0(Var,varTc,"Var")
+
+instance Data Var where
+  -- don't traverse?
+  toConstr _   = abstractConstr "Var"
+  gunfold _ _  = error "gunfold"
+  dataTypeOf _ = mkNoRepType "Var"
 \end{code}
 
 
@@ -218,8 +245,6 @@ setVarType id ty = id { varType = ty }
 %************************************************************************
 
 \begin{code}
-type TyVar = Var
-
 tyVarName :: TyVar -> Name
 tyVarName = varName
 
@@ -251,8 +276,12 @@ mkTcTyVar name kind details
     TcTyVar {  varName    = name,
                realUnique = getKeyFastInt (nameUnique name),
                varType  = kind,
-               tcTyVarDetails = details
+               tc_tv_details = details
        }
+
+tcTyVarDetails :: TyVar -> TcTyVarDetails
+tcTyVarDetails (TcTyVar { tc_tv_details = details }) = details
+tcTyVarDetails var = pprPanic "tcTyVarDetails" (ppr var)
 \end{code}
 
 %************************************************************************
@@ -262,10 +291,6 @@ mkTcTyVar name kind details
 %************************************************************************
 
 \begin{code}
-type CoVar = TyVar -- A coercion variable is simply a type 
-                       -- variable of kind @ty1 ~ ty2@. Hence its
-                       -- 'varType' is always @PredTy (EqPred t1 t2)@
-
 coVarName :: CoVar -> Name
 coVarName = varName
 
@@ -296,10 +321,13 @@ mkWildCoVar = mkCoVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "co_wild"))
 %************************************************************************
 
 \begin{code}
--- These synonyms are here and not in Id because otherwise we need a very
--- large number of SOURCE imports of Id.hs :-(
-type Id = Var
-type DictId = Var
+idInfo :: Id -> IdInfo
+idInfo (Id { id_info = info }) = info
+idInfo other                  = pprPanic "idInfo" (ppr other)
+
+idDetails :: Id -> IdDetails
+idDetails (Id { id_details = details }) = details
+idDetails other                        = pprPanic "idDetails" (ppr other)
 
 -- The next three have a 'Var' suffix even though they always build
 -- Ids, becuase Id.lhs uses 'mkGlobalId' etc with different types
@@ -322,15 +350,15 @@ mk_id name ty scope details info
         realUnique = getKeyFastInt (nameUnique name),
         varType    = ty,       
         idScope    = scope,
-        idDetails  = details,
-        idInfo     = info }
+        id_details = details,
+        id_info    = info }
 
 -------------------
 lazySetIdInfo :: Id -> IdInfo -> Var
-lazySetIdInfo id info = id { idInfo = info }
+lazySetIdInfo id info = id { id_info = info }
 
 setIdDetails :: Id -> IdDetails -> Id
-setIdDetails id details = id { idDetails = details }
+setIdDetails id details = id { id_details = details }
 
 globaliseId :: Id -> Id
 -- ^ If it's a local, make it global
@@ -356,11 +384,20 @@ setIdNotExported id = ASSERT( isLocalId id )
 %************************************************************************
 
 \begin{code}
-isTyVar :: Var -> Bool
-isTyVar (TyVar {})   = True
+isTyCoVar :: Var -> Bool       -- True of both type and coercion variables
+isTyCoVar (TyVar {})   = True
+isTyCoVar (TcTyVar {}) = True
+isTyCoVar _            = False
+
+isTyVar :: Var -> Bool         -- True of both type variables only
+isTyVar v@(TyVar {}) = not (isCoercionVar v)
 isTyVar (TcTyVar {}) = True
 isTyVar _            = False
 
+isCoVar :: Var -> Bool         -- Only works after type checking (sigh)
+isCoVar v@(TyVar {}) = isCoercionVar v
+isCoVar _            = False
+
 isTcTyVar :: Var -> Bool
 isTcTyVar (TcTyVar {}) = True
 isTcTyVar _            = False
@@ -373,11 +410,6 @@ isLocalId :: Var -> Bool
 isLocalId (Id { idScope = LocalId _ }) = True
 isLocalId _                            = False
 
-isCoVar :: Var -> Bool
-isCoVar (v@(TyVar {}))             = isCoercionVar v
-isCoVar (TcTyVar {varType = kind}) = isCoercionKind kind  -- used during solving
-isCoVar _                          = False
-
 -- | 'isLocalVar' returns @True@ for type variables as well as local 'Id's
 -- These are the variables that we need to pay attention to when finding free
 -- variables, or doing dependency analysis.