diff --git a/ghc/lib/std/PrelList.lhs b/ghc/lib/std/PrelList.lhs
index 9f10b65af8bcbaf6aa67d2e851424900bd01eec4..8773bf292012516d7b12f05601b03bdbb9184d32 100644
--- a/ghc/lib/std/PrelList.lhs
+++ b/ghc/lib/std/PrelList.lhs
@@ -20,7 +20,12 @@ module PrelList (
    lines, words, unlines, unwords, reverse, and, or,
    any, all, elem, notElem, lookup,
    sum, product, maximum, minimum, concatMap,
-   zip, zip3, zipWith, zipWith3, unzip, unzip3
+   zip, zip3, zipWith, zipWith3, unzip, unzip3,
+
+   -- non-standard, but hidden when creating the Prelude
+   -- export list.
+   takeUInt
+
  ) where
 
 import {-# SOURCE #-} PrelErr ( error )
@@ -200,23 +205,23 @@ splitAt _     _           =  errorNegativeIdx "splitAt"
 
 #else /* hack away */
 take	:: Int -> [b] -> [b]
-take (I# n#) xs = takeUInt n# xs
+take (I# n#) xs = takeUInt n# xs []
 
 -- The general code for take, below, checks n <= maxInt
 -- No need to check for maxInt overflow when specialised
 -- at type Int or Int# since the Int must be <= maxInt
 
-takeUInt :: Int# -> [b] -> [b]
-takeUInt n xs
-  | n >=# 0#  =  take_unsafe_UInt n xs
+takeUInt :: Int# -> [b] -> [b] -> [b]
+takeUInt n xs rs
+  | n >=# 0#  =  take_unsafe_UInt n xs rs
   | otherwise =  errorNegativeIdx "take"
 
-take_unsafe_UInt :: Int# -> [b] -> [b]
-take_unsafe_UInt 0# _     = []
-take_unsafe_UInt m  ls    =
+take_unsafe_UInt :: Int# -> [b] -> [b] -> [b]
+take_unsafe_UInt 0#  _ rs  = rs
+take_unsafe_UInt m  ls rs  =
   case ls of
-    []     -> ls
-    (x:xs) -> x : take_unsafe_UInt (m -# 1#) xs
+    []     -> rs
+    (x:xs) -> x : take_unsafe_UInt (m -# 1#) xs rs
 
 drop		:: Int -> [b] -> [b]
 drop (I# n#) ls
diff --git a/ghc/lib/std/PrelNum.lhs b/ghc/lib/std/PrelNum.lhs
index b565a9893bc4a40b5739f1c465205c959d400989..4f09ebdd31b318f0b214c5c65db5caca47bb7824 100644
--- a/ghc/lib/std/PrelNum.lhs
+++ b/ghc/lib/std/PrelNum.lhs
@@ -339,7 +339,7 @@ their greatest common divisor.
 
 \begin{code}
 reduce ::  (Integral a) => a -> a -> Ratio a
-reduce _ 0		=  error "{Ratio.%}: zero denominator"
+reduce _ 0		=  error "Ratio.%: zero denominator"
 reduce x y		=  (x `quot` d) :% (y `quot` d)
 			   where d = gcd x y
 \end{code}
diff --git a/ghc/lib/std/PrelNumExtra.lhs b/ghc/lib/std/PrelNumExtra.lhs
index 274b36e19abed73093f35247c6ca98b588cb62e6..5ba5ebd1fe5c1bfb3d112e4a233be6e00f29b376 100644
--- a/ghc/lib/std/PrelNumExtra.lhs
+++ b/ghc/lib/std/PrelNumExtra.lhs
@@ -517,9 +517,22 @@ normalize r = if r < 1 then
 		    tn = 10^n
 		in  if x >= tn then norm ee (x/tn) (e+n) else norm (ee-1) x e
 
-drop0 :: String -> String
-drop0 "" = ""
-drop0 (c:cs) = c : fromMaybe [] (dropTrailing0s cs) --WAS (yuck): reverse (dropWhile (=='0') (reverse cs))
+prR :: Int -> Rational -> Int -> String
+prR n r e  | r <  1  = prR n (r*10) (e-1)		-- final adjustment
+prR n r e  | r >= 10 = prR n (r/10) (e+1)
+prR n r e0
+  | e > 0 && e < 8   = takeN e s ('.' : drop0 (drop e s) [])
+  | e <= 0 && e > -3 = '0': '.' : takeN (-e) (repeat '0') (drop0 s [])
+  | otherwise	     =  h : '.' : drop0 t ('e':show e0)
+   where
+	s@(h:t) = show ((round (r * 10^n))::Integer)
+	e       = e0+1
+	
+	takeN (I# n#) ls rs = takeUInt n# ls rs
+
+drop0 :: String -> String -> String
+drop0     [] rs = rs
+drop0 (c:cs) rs = c : fromMaybe rs (dropTrailing0s cs) --WAS (yuck): reverse (dropWhile (=='0') (reverse cs))
   where
    dropTrailing0s []       = Nothing
    dropTrailing0s ('0':xs) = 
@@ -531,18 +544,6 @@ drop0 (c:cs) = c : fromMaybe [] (dropTrailing0s cs) --WAS (yuck): reverse (dropW
       Nothing -> Just [x]
       Just ls -> Just (x:ls)
 
-prR :: Int -> Rational -> Int -> String
-prR n r e | r <  1  = prR n (r*10) (e-1)		-- final adjustment
-prR n r e | r >= 10 = prR n (r/10) (e+1)
-prR n r e0 =
-	let s = show ((round (r * 10^n))::Integer)
-	    e = e0+1
-	in  if e > 0 && e < 8 then
-		take e s ++ "." ++ drop0 (drop e s)
-	    else if e <= 0 && e > -3 then
-	        "0." ++ take (-e) (repeat '0') ++ drop0 s
-	    else
-	        head s : "."++ drop0 (tail s) ++ "e" ++ show e0
 \end{code}
 
 [In response to a request for documentation of how fromRational works,
@@ -712,7 +713,7 @@ formatRealFloat fmt decs x
        Just dec ->
         let dec' = max dec 1 in
         case is of
-         [0] -> '0':'.':take dec' (repeat '0') ++ "e0"
+         [0] -> '0' :'.' : take dec' (repeat '0') ++ "e0"
          _ ->
           let
 	   (ei,is') = roundTo base (dec'+1) is
diff --git a/ghc/lib/std/Prelude.lhs b/ghc/lib/std/Prelude.lhs
index 1b9c8e699a26a68b2253f3dcaa539f52c4783b1e..7ad15ac4e037e9d493bec66a438929600baa0be7 100644
--- a/ghc/lib/std/Prelude.lhs
+++ b/ghc/lib/std/Prelude.lhs
@@ -65,7 +65,7 @@ module Prelude (
   ) where
 
 import PrelBase
-import PrelList
+import PrelList hiding ( takeUInt )
 import PrelRead
 import PrelNum
 import PrelNumExtra