[project @ 2003-12-30 16:29:17 by simonpj]
[ghc-hetmet.git] / ghc / compiler / types / TyCon.lhs
index 9b40a44..681d6e3 100644 (file)
@@ -5,12 +5,12 @@
 
 \begin{code}
 module TyCon(
-       TyCon, KindCon, SuperKindCon, ArgVrcs, 
+       TyCon, ArgVrcs, 
 
        AlgTyConFlavour(..), 
        DataConDetails(..), visibleDataCons,
 
-       isFunTyCon, isUnLiftedTyCon, isBoxedTyCon, isProductTyCon,
+       isFunTyCon, isUnLiftedTyCon, isProductTyCon,
        isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
        isEnumerationTyCon, 
        isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity,
@@ -25,16 +25,12 @@ module TyCon(
        mkLiftedPrimTyCon,
        mkTupleTyCon,
        mkSynTyCon,
-       mkKindCon,
-       mkSuperKindCon,
-
-       setTyConName,
 
        tyConName,
        tyConKind,
        tyConUnique,
        tyConTyVars,
-       tyConArgVrcs_maybe, tyConArgVrcs,
+       tyConArgVrcs,
        tyConDataConDetails, tyConDataCons, tyConDataCons_maybe, tyConFamilySize,
        tyConSelIds,
        tyConTheta,
@@ -46,15 +42,13 @@ module TyCon(
 
         maybeTyConSingleCon,
 
-       matchesTyCon,
-
        -- Generics
         tyConHasGenerics
 ) where
 
 #include "HsVersions.h"
 
-import {-# SOURCE #-} TypeRep ( Type, PredType, Kind, SuperKind )
+import {-# SOURCE #-} TypeRep ( Type, PredType )
  -- Should just be Type(Type), but this fails due to bug present up to
  -- and including 4.02 involving slurping of hi-boot files.  Bug is now fixed.
 
@@ -63,11 +57,12 @@ import {-# SOURCE #-} DataCon ( DataCon, isExistentialDataCon )
 
 import Var             ( TyVar, Id )
 import Class           ( Class )
+import Kind            ( Kind )
 import BasicTypes      ( Arity, RecFlag(..), Boxity(..), isBoxed )
 import Name            ( Name, nameUnique, NamedThing(getName) )
-import PrelNames       ( Unique, Uniquable(..), anyBoxConKey )
-import PrimRep         ( PrimRep(..), isFollowableRep )
-import Maybes          ( orElse, expectJust )
+import PrelNames       ( Unique, Uniquable(..) )
+import PrimRep         ( PrimRep(..) )
+import Maybes          ( orElse )
 import Outputable
 import FastString
 \end{code}
@@ -79,9 +74,6 @@ import FastString
 %************************************************************************
 
 \begin{code}
-type KindCon      = TyCon
-type SuperKindCon = TyCon
-
 data TyCon
   = FunTyCon {
        tyConUnique :: Unique,
@@ -157,18 +149,6 @@ data TyCon
        argVrcs :: ArgVrcs
     }
 
-  | KindCon {          -- Type constructor at the kind level
-       tyConUnique :: Unique,
-       tyConName   :: Name,
-       tyConKind   :: SuperKind,
-       tyConArity  :: Arity
-    }
-
-  | SuperKindCon       {               -- The type of kind variables or boxity variables,
-       tyConUnique :: Unique,
-       tyConName   :: Name
-    }
-
 type ArgVrcs = [(Bool,Bool)]  -- Tyvar variance info: [(occPos,occNeg)]
        -- [] means "no information, assume the worst"
 
@@ -195,8 +175,8 @@ data DataConDetails datacon
   = DataCons [datacon] -- Its data constructors, with fully polymorphic types
                        -- A type can have zero constructors
 
-  | Unknown            -- We're importing this data type from an hi-boot file
-                       -- and we don't know what its constructors are
+  | Unknown            -- Used only when We're importing this data type from an 
+                       -- hi-boot file, so we don't know what its constructors are
 
 visibleDataCons (DataCons cs) = cs
 visibleDataCons other        = []
@@ -216,21 +196,6 @@ module mutual-recursion.  And they aren't called from many places.
 So we compromise, and move their Kind calculation to the call site.
 
 \begin{code}
-mkSuperKindCon :: Name -> SuperKindCon
-mkSuperKindCon name = SuperKindCon {
-                       tyConUnique = nameUnique name,
-                       tyConName = name
-                     }
-
-mkKindCon :: Name -> SuperKind -> KindCon
-mkKindCon name kind
-  = KindCon { 
-       tyConUnique = nameUnique name,
-       tyConName = name,
-       tyConArity = 0,
-       tyConKind = kind
-     }
-
 mkFunTyCon :: Name -> Kind -> TyCon
 mkFunTyCon name kind 
   = FunTyCon { 
@@ -338,9 +303,6 @@ mkSynTyCon name kind tyvars rhs argvrcs
        synTyConDefn = rhs,
        argVrcs      = argvrcs
     }
-
-setTyConName tc name = tc {tyConName = name, tyConUnique = nameUnique name}
-
 \end{code}
 
 \begin{code}
@@ -357,12 +319,14 @@ isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
 isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity})      = not (isBoxed boxity)
 isUnLiftedTyCon _                                      = False
 
+#ifdef UNUSED
 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
 isBoxedTyCon :: TyCon -> Bool
 isBoxedTyCon (AlgTyCon {}) = True
 isBoxedTyCon (FunTyCon {}) = True
 isBoxedTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
+#endif
 
 -- isAlgTyCon returns True for both @data@ and @newtype@
 isAlgTyCon :: TyCon -> Bool
@@ -452,7 +416,7 @@ tyConHasGenerics other                               = False        -- Synonyms
 tyConDataConDetails :: TyCon -> DataConDetails DataCon
 tyConDataConDetails (AlgTyCon {dataCons = cons}) = cons
 tyConDataConDetails (TupleTyCon {dataCon = con}) = DataCons [con]
-tyConDataConDetails other                       = Unknown
+tyConDataConDetails other                       = pprPanic "tyConDataConDetails" (ppr other)
 
 tyConDataCons :: TyCon -> [DataCon]
 -- It's convenient for tyConDataCons to return the
@@ -501,15 +465,11 @@ actually computed (in another file).
 
 \begin{code}
 tyConArgVrcs :: TyCon -> ArgVrcs
-tyConArgVrcs tc = expectJust "tyConArgVrcs" (tyConArgVrcs_maybe tc)
-
-tyConArgVrcs_maybe :: TyCon -> Maybe ArgVrcs
-tyConArgVrcs_maybe (FunTyCon   {})                  = Just [(False,True),(True,False)]
-tyConArgVrcs_maybe (AlgTyCon   {argVrcs = oi})       = Just oi
-tyConArgVrcs_maybe (PrimTyCon  {argVrcs = oi})       = Just oi
-tyConArgVrcs_maybe (TupleTyCon {tyConArity = arity}) = Just (replicate arity (True,False))
-tyConArgVrcs_maybe (SynTyCon   {argVrcs = oi})       = Just oi
-tyConArgVrcs_maybe _                                 = Nothing
+tyConArgVrcs (FunTyCon   {})                  = [(False,True),(True,False)]
+tyConArgVrcs (AlgTyCon   {argVrcs = oi})       = oi
+tyConArgVrcs (PrimTyCon  {argVrcs = oi})       = oi
+tyConArgVrcs (TupleTyCon {tyConArity = arity}) = (replicate arity (True,False))
+tyConArgVrcs (SynTyCon   {argVrcs = oi})       = oi
 \end{code}
 
 \begin{code}
@@ -570,28 +530,3 @@ instance Outputable TyCon where
 instance NamedThing TyCon where
     getName = tyConName
 \end{code}
-
-
-%************************************************************************
-%*                                                                     *
-\subsection{Kind constructors}
-%*                                                                     *
-%************************************************************************
-
-@matchesTyCon tc1 tc2@ checks whether an appliation
-(tc1 t1..tn) matches (tc2 t1..tn).  By "matches" we basically mean "equals",
-except that at the kind level tc2 might have more boxity info than tc1.
-
-\begin{code}
-matchesTyCon :: TyCon  -- Expected (e.g. arg type of function)
-            -> TyCon   -- Inferred (e.g. type of actual arg to function)
-            -> Bool
-
-matchesTyCon tc1 tc2 =  uniq1 == uniq2 || uniq1 == anyBoxConKey
-                    where
-                       uniq1 = tyConUnique tc1
-                       uniq2 = tyConUnique tc2
-\end{code}
-
-
-