[project @ 2002-04-24 16:31:37 by simonmar]
[ghc-base.git] / Numeric.hs
index 4a4ecf4..01036b2 100644 (file)
@@ -1,14 +1,15 @@
+{-# OPTIONS -fno-implicit-prelude #-}
 -----------------------------------------------------------------------------
--- 
+-- |
 -- Module      :  Numeric
--- Copyright   :  (c) The University of Glasgow 2001
+-- Copyright   :  (c) The University of Glasgow 2002
 -- License     :  BSD-style (see the file libraries/core/LICENSE)
 -- 
 -- Maintainer  :  libraries@haskell.org
--- Stability   :  experimental
+-- Stability   :  provisional
 -- Portability :  portable
 --
--- $Id: Numeric.hs,v 1.1 2001/07/04 12:07:27 simonmar Exp $
+-- $Id: Numeric.hs,v 1.7 2002/04/24 16:31:37 simonmar Exp $
 --
 -- Odds and ends, mostly functions for reading and showing
 -- RealFloat-like kind of values.
@@ -20,50 +21,97 @@ module Numeric (
         fromRat,          -- :: (RealFloat a) => Rational -> a
        showSigned,       -- :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
        readSigned,       -- :: (Real a) => ReadS a -> ReadS a
-       showInt,          -- :: Integral a => a -> ShowS
+
        readInt,          -- :: (Integral a) => a -> (Char -> Bool)
                          --         -> (Char -> Int) -> ReadS a
-       
        readDec,          -- :: (Integral a) => ReadS a
        readOct,          -- :: (Integral a) => ReadS a
        readHex,          -- :: (Integral a) => ReadS a
 
+       showInt,          -- :: Integral a => a -> ShowS
+        showIntAtBase,    -- :: Integral a => a -> (a -> Char) -> a -> ShowS
         showHex,          -- :: Integral a => a -> ShowS
         showOct,          -- :: Integral a => a -> ShowS
         showBin,          -- :: Integral a => a -> ShowS
-        
+
        showEFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
        showFFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
        showGFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
        showFloat,        -- :: (RealFloat a) => a -> ShowS
        readFloat,        -- :: (RealFloat a) => ReadS a
        
-        
        floatToDigits,    -- :: (RealFloat a) => Integer -> a -> ([Int], Int)
        lexDigits,        -- :: ReadS String
 
-          -- general purpose number->string converter.
-        showIntAtBase,    -- :: Integral a 
-                         -- => a               -- base
-                         -- -> (a -> Char)      -- digit to char
-                         -- -> a                -- number to show.
-                         -- -> ShowS
        ) where
 
-import Prelude         -- For dependencies
 import Data.Char
 
 #ifdef __GLASGOW_HASKELL__
-import GHC.Base                ( Char(..), unsafeChr )
+import GHC.Base
 import GHC.Read
-import GHC.Real                ( showSigned )
+import GHC.Real
 import GHC.Float
+import GHC.Num
+import GHC.Show
+import Data.Maybe
+import Text.ParserCombinators.ReadP( ReadP, readP_to_S, pfail )
+import qualified Text.Read.Lex as L
 #endif
 
 #ifdef __HUGS__
 import Array
 #endif
 
+
+-- *********************************************************
+-- *                                                      *
+-- \subsection{Reading}
+-- *                                                      *
+-- *********************************************************
+
+readInt :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
+readInt base isDigit valDigit = readP_to_S (L.readIntP base isDigit valDigit)
+
+readOct, readDec, readHex :: Num a => ReadS a
+readOct = readP_to_S L.readOctP
+readDec = readP_to_S L.readDecP
+readHex = readP_to_S L.readHexP 
+
+readFloat :: RealFrac a => ReadS a
+readFloat = readP_to_S readFloatP
+
+readFloatP :: RealFrac a => ReadP a
+readFloatP =
+  do L.Number x <- L.lex
+     case L.numberToRational x of
+       Nothing -> pfail
+       Just y  -> return (fromRational y)
+
+-- It's turgid to have readSigned work using list comprehensions,
+-- but it's specified as a ReadS to ReadS transformer
+-- With a bit of luck no one will use it.
+readSigned :: (Real a) => ReadS a -> ReadS a
+readSigned readPos = readParen False read'
+                    where read' r  = read'' r ++
+                                     (do
+                                       ("-",s) <- lex r
+                                       (x,t)   <- read'' s
+                                       return (-x,t))
+                          read'' r = do
+                              (str,s) <- lex r
+                              (n,"")  <- readPos str
+                              return (n,s)
+
+
+-- *********************************************************
+-- *                                                      *
+-- \subsection{Showing}
+-- *                                                      *
+-- *********************************************************
+
+
+
 #ifdef __GLASGOW_HASKELL__
 showInt :: Integral a => a -> ShowS
 showInt n cs