diff --git a/ghc/lib/ghc/PrelBase.lhs b/ghc/lib/ghc/PrelBase.lhs
index 87fd4d0462443c5b99aa4c3f68c2a8e8a193acab..891d45c964bb212874f26ea9ec8d66eabdc8d907 100644
--- a/ghc/lib/ghc/PrelBase.lhs
+++ b/ghc/lib/ghc/PrelBase.lhs
@@ -345,10 +345,6 @@ instance Enum () where
     enumFromTo () () 	= [()]
     enumFromThenTo () () () = [()]
 
-instance Bounded () where
-    minBound = ()
-    maxBound = ()
-
 instance  Show ()  where
     showsPrec p () = showString "()"
     showList ls    = showList__ (showsPrec 0) ls
@@ -399,10 +395,6 @@ efttCh now step done
     go now | done now  = []
 	   | otherwise = C# (chr# now) : go (now +# step)
 
-instance  Bounded Char  where
-    minBound            =  '\0'
-    maxBound            =  '\255'
-
 instance  Show Char  where
     showsPrec p '\'' = showString "'\\''"
     showsPrec p c    = showChar '\'' . showLitChar c . showChar '\''
@@ -532,10 +524,6 @@ eftInt now step
     go now = I# now : go (now +# step)
 
 
-instance  Bounded Int where
-    minBound =  -2147483647            -- **********************
-    maxBound =  2147483647	       -- **********************
-
 instance  Num Int  where
     (+)	   x y =  plusInt x y
     (-)	   x y =  minusInt x y
diff --git a/ghc/lib/ghc/PrelBounded.lhs b/ghc/lib/ghc/PrelBounded.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..240f27781ecd2984eb941847c52f1a275afd4701
--- /dev/null
+++ b/ghc/lib/ghc/PrelBounded.lhs
@@ -0,0 +1,28 @@
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
+%
+\section[PrelBounded]{Module @PrelBounded@}
+
+Instances of Bounded for various datatypes.
+
+\begin{code}
+{-# OPTIONS -fno-implicit-prelude #-}
+
+module PrelBounded where
+
+import PrelBase
+import CCall				-- for the dependency analyser,
+					-- due to the use of litlits below.
+
+instance Bounded () where
+    minBound = ()
+    maxBound = ()
+
+instance  Bounded Char  where
+    minBound =  '\0'
+    maxBound =  '\255'
+
+instance  Bounded Int where
+    minBound =  ``-2147483648''		-- GHC <= 2.09 had this at -2147483647
+    maxBound =  2147483647
+\end{code}
diff --git a/ghc/lib/required/Prelude.lhs b/ghc/lib/required/Prelude.lhs
index 92d173f321213f532b17b267dd0b621df764dffd..7f0dcc1861d487fb238a1a285e7577acc4ebf745 100644
--- a/ghc/lib/required/Prelude.lhs
+++ b/ghc/lib/required/Prelude.lhs
@@ -69,6 +69,7 @@ import PrelNum
 import PrelTup
 import PrelMaybe
 import PrelEither
+import PrelBounded
 import Monad
 import Maybe
 import Error	( error )