diff --git a/ghc/compiler/prelude/PrelInfo.lhs b/ghc/compiler/prelude/PrelInfo.lhs
index 665aa92da1e4289009173f19cdc66f70a7c607f6..37de70cbd691d2319b0933723c94221517553cc7 100644
--- a/ghc/compiler/prelude/PrelInfo.lhs
+++ b/ghc/compiler/prelude/PrelInfo.lhs
@@ -34,12 +34,12 @@ module PrelInfo (
     ) where
 
 IMP_Ubiq()
+
 #if __GLASGOW_HASKELL__ >= 202
 import IdUtils ( primOpName )
 #else
 IMPORT_DELOOPER(PrelLoop) ( primOpName )
 #endif
--- IMPORT_DELOOPER(IdLoop)	  ( SpecEnv )
 
 -- friends:
 import PrelMods		-- Prelude module names
diff --git a/ghc/compiler/prelude/PrelVals.lhs b/ghc/compiler/prelude/PrelVals.lhs
index 5cea8884aa9b4ca56ca2b872ede5669191a4c462..f223311cf6ed99528546af47d715cc20cc77a34a 100644
--- a/ghc/compiler/prelude/PrelVals.lhs
+++ b/ghc/compiler/prelude/PrelVals.lhs
@@ -9,9 +9,18 @@
 module PrelVals where
 
 IMP_Ubiq()
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
 IMPORT_DELOOPER(IdLoop)		( UnfoldingGuidance(..), mkUnfolding, nullSpecEnv, SpecEnv )
-import Id		( SYN_IE(Id), GenId, mkImported, mkTemplateLocals )
+#else
+import {-# SOURCE #-} CoreUnfold ( UnfoldingGuidance(..), mkUnfolding )
+import {-# SOURCE #-} SpecEnv    ( SpecEnv, nullSpecEnv )
+#endif
+
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
 IMPORT_DELOOPER(PrelLoop)
+#endif
+
+import Id		( SYN_IE(Id), GenId, mkImported, mkTemplateLocals )
 
 -- friends:
 import PrelMods
diff --git a/ghc/compiler/prelude/TysWiredIn.lhs b/ghc/compiler/prelude/TysWiredIn.lhs
index 59241ac37dfbe1f2dfa29ecf664d7d1b4e40c3c3..3e3a71bf579add58395f5bfd8da39e527c081f21 100644
--- a/ghc/compiler/prelude/TysWiredIn.lhs
+++ b/ghc/compiler/prelude/TysWiredIn.lhs
@@ -86,10 +86,17 @@ module TysWiredIn (
 --import Kind
 
 IMP_Ubiq()
-IMPORT_DELOOPER(TyLoop)	--( mkDataCon, mkTupleCon, StrictnessMark(..) )
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
+IMPORT_DELOOPER(TyLoop)	( mkDataCon, mkTupleCon, StrictnessMark(..) )
 IMPORT_DELOOPER(IdLoop)	( SpecEnv, nullSpecEnv, 
 		          mkTupleCon, mkDataCon, 
 			  StrictnessMark(..) )
+#else
+import {-# SOURCE #-} Id ( Id, mkDataCon, mkTupleCon, StrictnessMark(..) )
+import {-# SOURCE #-} SpecEnv ( SpecEnv, nullSpecEnv )
+import {-# SOURCE #-} Type ( Type )
+import {-# SOURCE #-} TyVar ( TyVar )
+#endif
 
 -- friends:
 import PrelMods