From e0eaaf09894f74939166568573b36cb5bdafcfc7 Mon Sep 17 00:00:00 2001
From: sof <unknown>
Date: Mon, 4 May 1998 21:00:08 +0000
Subject: [PATCH] [project @ 1998-05-04 20:56:54 by sof] Import lists updated

---
 ghc/compiler/rename/ParseIface.y        | 2 +-
 ghc/compiler/rename/Rename.lhs          | 7 ++++---
 ghc/compiler/rename/RnBinds.lhs         | 2 +-
 ghc/compiler/rename/RnIfaces.lhs        | 4 ++--
 ghc/compiler/rename/RnNames.lhs         | 2 +-
 ghc/compiler/simplStg/SimplStg.lhs      | 2 +-
 ghc/compiler/typecheck/TcClassDcl.lhs   | 6 +++---
 ghc/compiler/typecheck/TcDefaults.lhs   | 2 +-
 ghc/compiler/typecheck/TcDeriv.lhs      | 2 +-
 ghc/compiler/typecheck/TcIfaceSig.lhs   | 2 +-
 ghc/compiler/typecheck/TcInstUtil.lhs   | 2 +-
 ghc/compiler/typecheck/TcModule.lhs     | 2 +-
 ghc/compiler/typecheck/TcMonoType.lhs   | 2 +-
 ghc/compiler/typecheck/TcSimplify.lhs   | 2 +-
 ghc/compiler/typecheck/TcTyClsDecls.lhs | 2 +-
 ghc/compiler/typecheck/TcTyDecls.lhs    | 2 +-
 ghc/compiler/typecheck/Unify.lhs        | 2 +-
 17 files changed, 23 insertions(+), 22 deletions(-)

diff --git a/ghc/compiler/rename/ParseIface.y b/ghc/compiler/rename/ParseIface.y
index 35043d8f5a29..96fac18cedb2 100644
--- a/ghc/compiler/rename/ParseIface.y
+++ b/ghc/compiler/rename/ParseIface.y
@@ -9,7 +9,7 @@ import HsDecls		( HsIdInfo(..), HsStrictnessInfo(..) )
 import HsTypes		( mkHsForAllTy )
 import HsCore
 import Literal
-import BasicTypes	( IfaceFlavour(..), Fixity(..), FixityDirection(..), NewOrData(..), Version(..) )
+import BasicTypes	( IfaceFlavour(..), Fixity(..), FixityDirection(..), NewOrData(..), Version )
 import HsPragmas	( noDataPragmas, noClassPragmas )
 import Kind		( Kind, mkArrowKind, mkBoxedTypeKind, mkTypeKind )
 import IdInfo           ( ArgUsageInfo, FBTypeInfo, ArityInfo, exactArity )
diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs
index 5a98a5b89a18..2fab42ef494c 100644
--- a/ghc/compiler/rename/Rename.lhs
+++ b/ghc/compiler/rename/Rename.lhs
@@ -25,9 +25,10 @@ import RnIfaces		( getImportedInstDecls, importDecl, getImportVersions, getSpeci
 			)
 import RnEnv		( addImplicitOccsRn, availNames )
 import Name		( Name, PrintUnqualified, Provenance, isLocallyDefined,
-			  NameSet(..),
-			  nameSetToList, minusNameSet, NamedThing(..),
-			  nameModule, pprModule, pprOccName, nameOccName
+			  NameSet,
+			    nameSetToList, minusNameSet,
+			  NamedThing(..),
+			   nameModule, pprModule, pprOccName, nameOccName
 			)
 import TysWiredIn	( unitTyCon, intTyCon, doubleTyCon )
 import TyCon		( TyCon )
diff --git a/ghc/compiler/rename/RnBinds.lhs b/ghc/compiler/rename/RnBinds.lhs
index a92ac88960d5..4f302044b81d 100644
--- a/ghc/compiler/rename/RnBinds.lhs
+++ b/ghc/compiler/rename/RnBinds.lhs
@@ -32,7 +32,7 @@ import CmdLineOpts	( opt_SigsRequired )
 import Digraph		( stronglyConnComp, SCC(..) )
 import Name		( OccName(..), Provenance, 
 			  Name, isExportedName,
-			  NameSet(..), emptyNameSet, mkNameSet, unionNameSets, 
+			  NameSet, emptyNameSet, mkNameSet, unionNameSets, 
 		 	  minusNameSet, unionManyNameSets, elemNameSet, unitNameSet, nameSetToList
 			)
 import BasicTypes	( RecFlag(..), TopLevelFlag(..) )
diff --git a/ghc/compiler/rename/RnIfaces.lhs b/ghc/compiler/rename/RnIfaces.lhs
index 55ad5f97aeae..8092a6d5cd7f 100644
--- a/ghc/compiler/rename/RnIfaces.lhs
+++ b/ghc/compiler/rename/RnIfaces.lhs
@@ -44,12 +44,12 @@ import FiniteMap	( FiniteMap, sizeFM, emptyFM, delFromFM,
 			)
 import Name		( Name {-instance NamedThing-}, Provenance, OccName(..),
 			  nameModule, moduleString, pprModule, isLocallyDefined,
-			  NameSet(..), emptyNameSet, unionNameSets, nameSetToList,
+			  NameSet, emptyNameSet, unionNameSets, nameSetToList,
 			  minusNameSet, mkNameSet, elemNameSet, nameUnique, addOneToNameSet,
 			  isWiredInName, maybeWiredInTyConName, maybeWiredInIdName,
 			  NamedThing(..)
 			 )
-import Id		( GenId, Id(..), idType, dataConTyCon, isAlgCon )
+import Id		( GenId, Id, idType, dataConTyCon, isAlgCon )
 import TyCon		( TyCon, tyConDataCons, isSynTyCon, getSynTyConDefn )
 import Type		( namesOfType )
 import TyVar		( GenTyVar )
diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs
index a45926dfc443..549137ac7719 100644
--- a/ghc/compiler/rename/RnNames.lhs
+++ b/ghc/compiler/rename/RnNames.lhs
@@ -19,7 +19,7 @@ import HsSyn	( HsModule(..), ImportDecl(..), HsDecl(..),
 		  FixityDecl(..),
 		  collectTopBinders
 		)
-import RdrHsSyn	( RdrNameHsDecl(..), RdrName(..), RdrNameIE(..), RdrNameImportDecl,
+import RdrHsSyn	( RdrNameHsDecl, RdrName(..), RdrNameIE, RdrNameImportDecl,
 		  RdrNameHsModule, RdrNameFixityDecl,
 		  rdrNameOcc, ieOcc
 		)
diff --git a/ghc/compiler/simplStg/SimplStg.lhs b/ghc/compiler/simplStg/SimplStg.lhs
index e843a6fd69b5..fb626f32adc7 100644
--- a/ghc/compiler/simplStg/SimplStg.lhs
+++ b/ghc/compiler/simplStg/SimplStg.lhs
@@ -12,7 +12,7 @@ import StgSyn
 
 import LambdaLift	( liftProgram )
 import Name		( isLocallyDefined )
-import UniqSet          ( UniqSet(..), mapUniqSet )
+import UniqSet          ( UniqSet, mapUniqSet )
 import CostCentre       ( CostCentre )
 import SCCfinal		( stgMassageForProfiling )
 import StgLint		( lintStgBindings )
diff --git a/ghc/compiler/typecheck/TcClassDcl.lhs b/ghc/compiler/typecheck/TcClassDcl.lhs
index 2482fe174add..82c9212321a6 100644
--- a/ghc/compiler/typecheck/TcClassDcl.lhs
+++ b/ghc/compiler/typecheck/TcClassDcl.lhs
@@ -15,9 +15,9 @@ import HsSyn		( HsDecl(..), ClassDecl(..), Sig(..), MonoBinds(..),
 			)
 import HsPragmas	( ClassPragmas(..) )
 import BasicTypes	( NewOrData(..), TopLevelFlag(..), RecFlag(..) )
-import RnHsSyn		( RenamedClassDecl(..), RenamedClassPragmas(..),
-			  RenamedClassOpSig(..), RenamedMonoBinds,
-			  RenamedContext(..), RenamedHsDecl, RenamedSig
+import RnHsSyn		( RenamedClassDecl, RenamedClassPragmas,
+			  RenamedClassOpSig, RenamedMonoBinds,
+			  RenamedContext, RenamedHsDecl, RenamedSig
 			)
 import TcHsSyn		( TcMonoBinds )
 
diff --git a/ghc/compiler/typecheck/TcDefaults.lhs b/ghc/compiler/typecheck/TcDefaults.lhs
index f6e337e5b340..28046a12fe7f 100644
--- a/ghc/compiler/typecheck/TcDefaults.lhs
+++ b/ghc/compiler/typecheck/TcDefaults.lhs
@@ -9,7 +9,7 @@ module TcDefaults ( tcDefaults ) where
 #include "HsVersions.h"
 
 import HsSyn		( HsDecl(..), DefaultDecl(..) )
-import RnHsSyn		( RenamedHsDecl(..) )
+import RnHsSyn		( RenamedHsDecl )
 
 import TcMonad
 import TcEnv		( tcLookupClassByKey )
diff --git a/ghc/compiler/typecheck/TcDeriv.lhs b/ghc/compiler/typecheck/TcDeriv.lhs
index f83767c8f080..6c45ca937795 100644
--- a/ghc/compiler/typecheck/TcDeriv.lhs
+++ b/ghc/compiler/typecheck/TcDeriv.lhs
@@ -24,7 +24,7 @@ import TcSimplify	( tcSimplifyThetas )
 
 import RnBinds		( rnMethodBinds, rnTopMonoBinds )
 import RnEnv		( newDfunName, bindLocatedLocalsRn )
-import RnMonad		( RnM, RnDown, SDown, RnNameSupply(..), 
+import RnMonad		( RnM, RnDown, SDown, RnNameSupply, 
 			  renameSourceCode, thenRn, mapRn, returnRn )
 
 import Bag		( Bag, emptyBag, unionBags, listToBag )
diff --git a/ghc/compiler/typecheck/TcIfaceSig.lhs b/ghc/compiler/typecheck/TcIfaceSig.lhs
index 14e4c9f49998..1646bfb3a0a4 100644
--- a/ghc/compiler/typecheck/TcIfaceSig.lhs
+++ b/ghc/compiler/typecheck/TcIfaceSig.lhs
@@ -18,7 +18,7 @@ import TcEnv		( tcExtendTyVarEnv, tcExtendGlobalValEnv, tcSetGlobalValEnv,
 			)
 import TcKind		( TcKind, kindToTcKind )
 
-import RnHsSyn		( RenamedHsDecl(..) )
+import RnHsSyn		( RenamedHsDecl )
 import HsCore
 import HsDecls		( HsIdInfo(..), HsStrictnessInfo(..) )
 import Literal		( Literal(..) )
diff --git a/ghc/compiler/typecheck/TcInstUtil.lhs b/ghc/compiler/typecheck/TcInstUtil.lhs
index 51ce9677fd22..d84bf5418b7d 100644
--- a/ghc/compiler/typecheck/TcInstUtil.lhs
+++ b/ghc/compiler/typecheck/TcInstUtil.lhs
@@ -15,7 +15,7 @@ module TcInstUtil (
 
 #include "HsVersions.h"
 
-import RnHsSyn		( RenamedMonoBinds, RenamedSig(..) )
+import RnHsSyn		( RenamedMonoBinds, RenamedSig )
 
 import CmdLineOpts	( opt_AllowOverlappingInstances )
 import TcMonad
diff --git a/ghc/compiler/typecheck/TcModule.lhs b/ghc/compiler/typecheck/TcModule.lhs
index 7ed38a5964e4..c3767e1c95fa 100644
--- a/ghc/compiler/typecheck/TcModule.lhs
+++ b/ghc/compiler/typecheck/TcModule.lhs
@@ -35,7 +35,7 @@ import TcTyDecls	( mkDataBinds )
 import TcType		( TcType, tcInstType )
 import TcKind		( TcKind, kindToTcKind )
 
-import RnMonad		( RnNameSupply(..) )
+import RnMonad		( RnNameSupply )
 import Bag		( isEmptyBag )
 import ErrUtils		( WarnMsg, ErrMsg, 
 			  pprBagOfErrors, dumpIfSet
diff --git a/ghc/compiler/typecheck/TcMonoType.lhs b/ghc/compiler/typecheck/TcMonoType.lhs
index ed35d0863400..d20bb9149177 100644
--- a/ghc/compiler/typecheck/TcMonoType.lhs
+++ b/ghc/compiler/typecheck/TcMonoType.lhs
@@ -9,7 +9,7 @@ module TcMonoType ( tcHsType, tcHsTypeKind, tcContext, tcTyVarScope ) where
 #include "HsVersions.h"
 
 import HsSyn		( HsType(..), HsTyVar(..), pprContext )
-import RnHsSyn		( RenamedHsType(..), RenamedContext(..) )
+import RnHsSyn		( RenamedHsType, RenamedContext )
 
 import TcMonad
 import TcEnv		( tcLookupTyVar, tcLookupClass, tcLookupTyCon, tcExtendTyVarEnv	)
diff --git a/ghc/compiler/typecheck/TcSimplify.lhs b/ghc/compiler/typecheck/TcSimplify.lhs
index 7c6e6e5e9e6a..3f9a9de19e92 100644
--- a/ghc/compiler/typecheck/TcSimplify.lhs
+++ b/ghc/compiler/typecheck/TcSimplify.lhs
@@ -136,7 +136,7 @@ import Inst		( lookupInst, lookupSimpleInst, LookupInstResult(..),
 			  newDictFromOld,
 			  instLoc, getDictClassTys,
 			  pprInst, zonkInst,
-			  Inst(..), LIE, pprInsts, pprInstsInFull, mkLIE, 
+			  Inst, LIE, pprInsts, pprInstsInFull, mkLIE, 
 			  InstOrigin, pprOrigin
 			)
 import TcEnv		( TcIdOcc(..) )
diff --git a/ghc/compiler/typecheck/TcTyClsDecls.lhs b/ghc/compiler/typecheck/TcTyClsDecls.lhs
index 7de928a77b6b..32c571ea20a0 100644
--- a/ghc/compiler/typecheck/TcTyClsDecls.lhs
+++ b/ghc/compiler/typecheck/TcTyClsDecls.lhs
@@ -16,7 +16,7 @@ import HsSyn		( HsDecl(..), TyDecl(..), ClassDecl(..),
 			  Sig(..),
 			  hsDeclName
 			)
-import RnHsSyn		( RenamedTyDecl(..), RenamedClassDecl(..), RenamedHsDecl )
+import RnHsSyn		( RenamedTyDecl, RenamedClassDecl, RenamedHsDecl )
 import TcHsSyn		( TcHsBinds )
 import BasicTypes	( RecFlag(..) )
 
diff --git a/ghc/compiler/typecheck/TcTyDecls.lhs b/ghc/compiler/typecheck/TcTyDecls.lhs
index 0e83986ca8bf..64ccfbb72310 100644
--- a/ghc/compiler/typecheck/TcTyDecls.lhs
+++ b/ghc/compiler/typecheck/TcTyDecls.lhs
@@ -17,7 +17,7 @@ import HsSyn		( MonoBinds(..),
 			  andMonoBinds
 			)
 import HsTypes		( getTyVarName )
-import RnHsSyn		( RenamedTyDecl(..), RenamedConDecl(..)	)
+import RnHsSyn		( RenamedTyDecl, RenamedConDecl )
 import TcHsSyn		( mkHsTyLam, mkHsDictLam, tcIdType,
 			  TcHsBinds, TcMonoBinds
 			)
diff --git a/ghc/compiler/typecheck/Unify.lhs b/ghc/compiler/typecheck/Unify.lhs
index 4e200006de22..276a110d2593 100644
--- a/ghc/compiler/typecheck/Unify.lhs
+++ b/ghc/compiler/typecheck/Unify.lhs
@@ -19,7 +19,7 @@ import TcMonad
 import Type	( GenType(..), Type, tyVarsOfType,
 		  typeKind, mkFunTy, splitFunTy_maybe, splitTyConApp_maybe )
 import TyCon	( TyCon, mkFunTyCon, isTupleTyCon, tyConArity, Arity )
-import TyVar	( TyVar(..), GenTyVar(..), tyVarKind, tyVarFlexi,
+import TyVar	( TyVar, GenTyVar(..), tyVarKind, tyVarFlexi,
 		  TyVarEnv, lookupTyVarEnv, emptyTyVarEnv, addToTyVarEnv,
 		  tyVarSetToList
 		)
-- 
GitLab