diff --git a/ghc/lib/glaExts/NumExts.lhs b/ghc/lib/glaExts/NumExts.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..e2f053aa800004ec25bba120118853b8af8b8d29
--- /dev/null
+++ b/ghc/lib/glaExts/NumExts.lhs
@@ -0,0 +1,55 @@
+%
+% (c) The AQUA Project, Glasgow University, 1998
+%
+
+\section[NumExts]{Misc numeric bits}
+
+\begin{code}
+module NumExts
+
+       (
+         doubleToFloat   -- :: Double -> Float
+       , floatToDouble   -- :: Double -> Float
+       , showHex         -- :: Integral a => a -> ShowS
+       , showOct         -- :: Integral a => a -> ShowS
+       ) where
+
+import Char (ord, chr)
+import PrelBase (ord_0)
+import GlaExts
+\end{code}
+
+\begin{code}
+doubleToFloat :: Double -> Float
+doubleToFloat (D# d#) = F# (double2Float# d#)
+
+floatToDouble :: Float -> Double
+floatToDouble (F# f#) = D# (float2Double# f#)
+
+showIntAtBase :: Integral a => a -> (a -> Char) -> a -> ShowS
+showIntAtBase base toChr n r
+  | n < 0  = error ("NumExts.showIntAtBase: applied to negative number " ++ show n)
+  | otherwise = 
+    case quotRem n base of { (n', d) ->
+    case toChr d        of { C# c# -> -- stricter than necessary
+    let
+	r' = C# c# : r
+    in
+    if n' == 0 then r' else showIntAtBase base toChr n' r'
+    }}
+
+showHex :: Integral a => a -> ShowS
+showHex n r = 
+ showString "0x" $
+ showIntAtBase 16 (toChrHex) n r
+ where  
+  toChrHex d
+    | d < 10    = chr (ord_0   + fromIntegral d)
+    | otherwise = chr (ord 'a' + fromIntegral (d - 10))
+
+showOct :: Integral a => a -> ShowS
+showOct n r = 
+ showString "0o" $
+ showIntAtBase 8 (toChrOct) n r
+ where toChrOct d = chr (ord_0   + fromIntegral d)
+\end{code}
diff --git a/ghc/lib/required/Numeric.lhs b/ghc/lib/required/Numeric.lhs
index e6c3f0e5df87634b86b49b240e69f182bd3289bc..42268633cd4c601b2013b3845773a5478b6c24ae 100644
--- a/ghc/lib/required/Numeric.lhs
+++ b/ghc/lib/required/Numeric.lhs
@@ -18,7 +18,6 @@ module Numeric
 	 readInt,
 
 	 readDec, readOct, readHex,
-         showDec, showOct, showHex,
 
 	 showEFloat, 
 	 showFFloat, 
@@ -82,37 +81,6 @@ showInt n r
     if n' == 0 then r' else showInt n' r'
     }}
 
-showIntAtBase :: Integral a => a -> (a -> Char) -> a -> ShowS
-showIntAtBase base toChr n r
-  = case quotRem n base of { (n', d) ->
-    case toChr d        of { C# c# -> -- stricter than necessary
-    let
-	r' = C# c# : r
-    in
-    if n' == 0 then r' else showIntAtBase base toChr n' r'
-    }}
-
-showDec :: Integral a => a -> ShowS
-showDec n r = 
- showIntAtBase 10 
-               (\ d -> chr (ord_0 + fromIntegral d)) 
-	       n r
-
-showHex :: Integral a => a -> ShowS
-showHex n r = 
- showString "0x" $
- showIntAtBase 16 (toChrHex) n r
- where  
-  toChrHex d
-    | d < 10    = chr (ord_0   + fromIntegral d)
-    | otherwise = chr (ord 'a' + fromIntegral (d - 10))
-
-showOct :: Integral a => a -> ShowS
-showOct n r = 
- showString "0o" $
- showIntAtBase 8 (toChrOct) n r
- where toChrOct d = chr (ord_0   + fromIntegral d)
-
 \end{code}
 
 Controlling the format and precision of floats. The code that