diff --git a/ghc/compiler/hsSyn/HsTypes.lhs b/ghc/compiler/hsSyn/HsTypes.lhs
index 06ba30d5f99253f87147dcdfd7818707324d3f15..14157d7cf1134419591503a5eebb2ea1da2fa9b2 100644
--- a/ghc/compiler/hsSyn/HsTypes.lhs
+++ b/ghc/compiler/hsSyn/HsTypes.lhs
@@ -30,7 +30,7 @@ import Type		( Type, Kind, PredType(..), UsageAnn(..), ClassContext,
 			  getTyVar_maybe, splitSigmaTy, unUsgTy, boxedTypeKind
 			)
 import TypeRep		( Type(..), TyNote(..) )	-- toHsType sees the representation
-import TyCon		( isTupleTyCon, tupleTyConBoxity, tyConArity, tyConClass_maybe )
+import TyCon		( isTupleTyCon, tupleTyConBoxity, tyConArity )
 import RdrName		( RdrName )
 import Name		( toRdrName )
 import OccName		( NameSpace )
diff --git a/ghc/compiler/parser/ParseUtil.lhs b/ghc/compiler/parser/ParseUtil.lhs
index 006456cff249d894dbfee596e6911579843b5c94..49c0376a7f2bb34311d17dcc955e424a8bb55081 100644
--- a/ghc/compiler/parser/ParseUtil.lhs
+++ b/ghc/compiler/parser/ParseUtil.lhs
@@ -199,9 +199,8 @@ checkPat e [] = case e of
 	ExplicitList es	   -> mapP (\e -> checkPat e []) es `thenP` \ps ->
 			      returnP (ListPatIn ps)
 
-	ExplicitTuple es Boxed -> mapP (\e -> checkPat e []) es `thenP` \ps ->
-			          returnP (TuplePatIn ps Boxed)
-		-- Unboxed tuples are illegal in patterns
+	ExplicitTuple es b -> mapP (\e -> checkPat e []) es `thenP` \ps ->
+			      returnP (TuplePatIn ps b)
 
 	RecordCon c fs     -> mapP checkPatField fs `thenP` \fs ->
 			      returnP (RecPatIn c fs)
diff --git a/ghc/compiler/typecheck/TcModule.lhs b/ghc/compiler/typecheck/TcModule.lhs
index 03f4fce6eb4f0f3cc66e120563fc53c4fc3d5834..1478dc9f4f29793fb0cb6054be0393e5287d1e11 100644
--- a/ghc/compiler/typecheck/TcModule.lhs
+++ b/ghc/compiler/typecheck/TcModule.lhs
@@ -48,7 +48,7 @@ import Name		( nameOccName, isLocallyDefined, isGlobalName,
 			  toRdrName, nameEnvElts, 
 			)
 import OccName		( isSysOcc )
-import TyCon		( TyCon, tyConClass_maybe )
+import TyCon		( TyCon, isClassTyCon )
 import Class		( Class )
 import PrelNames	( mAIN_Name, mainKey )
 import UniqSupply       ( UniqSupply )
@@ -162,7 +162,7 @@ tcModule rn_name_supply fixities
 	    local_classes = filter isLocallyDefined classes
 	    local_tycons  = [ tc | tc <- tycons,
 				   isLocallyDefined tc,
-				   Nothing <- [tyConClass_maybe tc]
+				   not (isClassTyCon tc)
 			    ]
 				-- For local_tycons, filter out the ones derived from classes
 				-- Otherwise the latter show up in interface files
diff --git a/ghc/compiler/types/TyCon.lhs b/ghc/compiler/types/TyCon.lhs
index 9692a9a7560bfe3f09c7ab03957fe4399590018d..b8786940fd7df337e8c9494af4d8c4124a4c11f3 100644
--- a/ghc/compiler/types/TyCon.lhs
+++ b/ghc/compiler/types/TyCon.lhs
@@ -34,7 +34,7 @@ module TyCon(
 	tyConTheta,
 	tyConPrimRep,
 	tyConArity,
-	tyConClass_maybe,
+	isClassTyCon,
 	getSynTyConDefn,
 
         maybeTyConSingleCon,
@@ -110,10 +110,7 @@ data TyCon
 	algTyConRec     :: RecFlag,		-- Tells whether the data type is part of 
 						-- a mutually-recursive group or not
 
-	algTyConClass_maybe :: Maybe Class	-- Nothing for ordinary types; 
-						-- Just c for the type constructor
-						-- for dictionaries of class c.
-
+	algTyConClass :: Bool		-- True if this tycon comes from a class declaration
     }
 
   | PrimTyCon {		-- Primitive types; cannot be defined in Haskell
@@ -232,7 +229,7 @@ mkAlgTyCon name kind tyvars theta argvrcs cons ncons derivs flavour rec
 	dataCons		= cons, 
 	noOfDataCons		= ncons,
 	algTyConDerivings	= derivs,
-	algTyConClass_maybe	= Nothing,
+	algTyConClass		= False,
 	algTyConFlavour 	= flavour,
 	algTyConRec		= rec
     }
@@ -249,7 +246,7 @@ mkClassTyCon name kind tyvars argvrcs con clas flavour
 	dataCons		= [con],
 	noOfDataCons		= 1,
 	algTyConDerivings	= [],
-	algTyConClass_maybe	= Just clas,
+	algTyConClass		= True,
 	algTyConFlavour		= flavour,
 	algTyConRec		= NonRecursive
     }
@@ -429,9 +426,9 @@ maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $
 \end{code}
 
 \begin{code}
-tyConClass_maybe :: TyCon -> Maybe Class
-tyConClass_maybe (AlgTyCon {algTyConClass_maybe = maybe_cls}) = maybe_cls
-tyConClass_maybe other_tycon			              = Nothing
+isClassTyCon :: TyCon -> Bool
+isClassTyCon (AlgTyCon {algTyConClass = is_class_tycon}) = is_class_tycon
+isClassTyCon other_tycon			         = False
 \end{code}
 
 
diff --git a/ghc/compiler/types/Type.lhs b/ghc/compiler/types/Type.lhs
index 1b8d996e0eafae5bba1b4dd822598d27f4e08635..aad32281be6e324a7f8cdd156ae79e0dd49803a2 100644
--- a/ghc/compiler/types/Type.lhs
+++ b/ghc/compiler/types/Type.lhs
@@ -98,7 +98,7 @@ import TyCon	( TyCon,
 		  isFunTyCon, isDataTyCon, isNewTyCon, newTyConRep,
 		  isAlgTyCon, isSynTyCon, tyConArity,
 	          tyConKind, tyConDataCons, getSynTyConDefn,
-		  tyConPrimRep, tyConClass_maybe
+		  tyConPrimRep
 		)
 
 -- others