diff --git a/ghc/compiler/hsSyn/HsBinds.lhs b/ghc/compiler/hsSyn/HsBinds.lhs
index 51f98c83a00fa5524ba08fea94697c4c39e1abd4..0c167d6e5a9f6874522a579e607925a168b9a1ae 100644
--- a/ghc/compiler/hsSyn/HsBinds.lhs
+++ b/ghc/compiler/hsSyn/HsBinds.lhs
@@ -13,16 +13,22 @@ module HsBinds where
 IMP_Ubiq()
 
 -- friends:
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
 IMPORT_DELOOPER(HsLoop)	( pprMatches, pprGRHSsAndBinds,
 			  Match, GRHSsAndBinds,
-			  HsExpr, pprExpr )
+			  pprExpr, HsExpr )
+#else
+import {-# SOURCE #-} HsMatches ( pprMatches, Match, pprGRHSsAndBinds, GRHSsAndBinds )
+import {-# SOURCE #-} HsExpr    ( pprExpr, HsExpr )
+#endif
+
 import HsPragmas	( GenPragmas, ClassOpPragmas )
 import HsTypes		( HsType )
 import CoreSyn		( SYN_IE(CoreExpr) )
 
 --others:
 import Id		( SYN_IE(DictVar), SYN_IE(Id), GenId )
-import Name		( getOccName, OccName, NamedThing(..) )
+import Name		( OccName, NamedThing(..) )
 import Outputable	( interpp'SP, ifnotPprForUser, pprQuote,
 			  Outputable(..){-instance * (,)-}
 			)
diff --git a/ghc/compiler/hsSyn/HsExpr.lhs b/ghc/compiler/hsSyn/HsExpr.lhs
index e72c1fdb9ff88a4f3a6dd95550ea58378c1dd28b..1acfd7102d5ee0390f734a7911cc473ee3f9f2be 100644
--- a/ghc/compiler/hsSyn/HsExpr.lhs
+++ b/ghc/compiler/hsSyn/HsExpr.lhs
@@ -11,7 +11,12 @@ module HsExpr where
 IMP_Ubiq(){-uitous-}
 
 -- friends:
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
 IMPORT_DELOOPER(HsLoop) ( pprMatches, pprMatch, Match )
+#else
+import {-# SOURCE #-} HsMatches ( pprMatches, pprMatch, Match )
+#endif
+
 import HsBinds		( HsBinds )
 import HsBasic		( HsLit )
 import BasicTypes	( Fixity(..), FixityDirection(..) )
@@ -25,7 +30,6 @@ import PprType		( pprGenType, pprParendGenType, GenType{-instance-} )
 import Pretty
 import SrcLoc		( SrcLoc )
 import Usage		( GenUsage{-instance-} )
---import Util		( panic{-ToDo:rm eventually-} )
 #if __GLASGOW_HASKELL__ >= 202
 import Name
 #endif