X-Git-Url: http://git.haskell.org/packages/base.git/blobdiff_plain/41e8fba828acbae1751628af50849f5352b27873..e5fc2e5810611504ceef9ba52c1ad508b5f5c7dc:/Numeric.hs diff --git a/Numeric.hs b/Numeric.hs index 4b202d0..88b2e1a 100644 --- a/Numeric.hs +++ b/Numeric.hs @@ -1,11 +1,12 @@ -{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-} +{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE NoImplicitPrelude, MagicHash #-} ----------------------------------------------------------------------------- -- | -- Module : Numeric -- Copyright : (c) The University of Glasgow 2002 -- License : BSD-style (see the file libraries/base/LICENSE) --- +-- -- Maintainer : libraries@haskell.org -- Stability : provisional -- Portability : portable @@ -19,19 +20,21 @@ module Numeric ( -- * Showing - showSigned, -- :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS + showSigned, - showIntAtBase, -- :: Integral a => a -> (a -> Char) -> a -> ShowS - showInt, -- :: Integral a => a -> ShowS - showHex, -- :: Integral a => a -> ShowS - showOct, -- :: Integral a => a -> ShowS + showIntAtBase, + showInt, + showHex, + showOct, - 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 + showEFloat, + showFFloat, + showGFloat, + showFFloatAlt, + showGFloatAlt, + showFloat, - floatToDigits, -- :: (RealFloat a) => Integer -> a -> ([Int], Int) + floatToDigits, -- * Reading @@ -39,25 +42,23 @@ module Numeric ( -- and 'readDec' is the \`dual\' of 'showInt'. -- The inconsistent naming is a historical accident. - readSigned, -- :: (Real a) => ReadS a -> ReadS a + readSigned, - 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 + readInt, + readDec, + readOct, + readHex, - readFloat, -- :: (RealFloat a) => ReadS a + readFloat, - lexDigits, -- :: ReadS String + lexDigits, -- * Miscellaneous - fromRat, -- :: (RealFloat a) => Rational -> a + fromRat, ) where -#ifdef __GLASGOW_HASKELL__ import GHC.Base import GHC.Read import GHC.Real @@ -67,16 +68,7 @@ import GHC.Show import Data.Maybe import Text.ParserCombinators.ReadP( ReadP, readP_to_S, pfail ) import qualified Text.Read.Lex as L -#else -import Data.Char -#endif - -#ifdef __HUGS__ -import Hugs.Prelude -import Hugs.Numeric -#endif -#ifdef __GLASGOW_HASKELL__ -- ----------------------------------------------------------------------------- -- Reading @@ -89,17 +81,17 @@ readInt :: Num a readInt base isDigit valDigit = readP_to_S (L.readIntP base isDigit valDigit) -- | Read an unsigned number in octal notation. -readOct :: Num a => ReadS a +readOct :: (Eq a, Num a) => ReadS a readOct = readP_to_S L.readOctP -- | Read an unsigned number in decimal notation. -readDec :: Num a => ReadS a +readDec :: (Eq a, Num a) => ReadS a readDec = readP_to_S L.readDecP -- | Read an unsigned number in hexadecimal notation. -- Both upper or lower case letters are allowed. -readHex :: Num a => ReadS a -readHex = readP_to_S L.readHexP +readHex :: (Eq a, Num a) => ReadS a +readHex = readP_to_S L.readHexP -- | Reads an /unsigned/ 'RealFrac' value, -- expressed in decimal scientific notation. @@ -110,9 +102,8 @@ readFloatP :: RealFrac a => ReadP a readFloatP = do tok <- L.lex case tok of - L.Rat y -> return (fromRational y) - L.Int i -> return (fromInteger i) - _ -> pfail + L.Number n -> return $ fromRational $ L.numberToRational n + _ -> pfail -- It's turgid to have readSigned work using list comprehensions, -- but it's specified as a ReadS to ReadS transformer @@ -179,7 +170,7 @@ showEFloat :: (RealFloat a) => Maybe Int -> a -> ShowS showFFloat :: (RealFloat a) => Maybe Int -> a -> ShowS -- | Show a signed 'RealFloat' value --- using standard decimal notation for arguments whose absolute value lies +-- using standard decimal notation for arguments whose absolute value lies -- between @0.1@ and @9,999,999@, and scientific notation otherwise. -- -- In the call @'showGFloat' digs val@, if @digs@ is 'Nothing', @@ -190,14 +181,31 @@ showGFloat :: (RealFloat a) => Maybe Int -> a -> ShowS showEFloat d x = showString (formatRealFloat FFExponent d x) showFFloat d x = showString (formatRealFloat FFFixed d x) showGFloat d x = showString (formatRealFloat FFGeneric d x) -#endif /* __GLASGOW_HASKELL__ */ + +-- | Show a signed 'RealFloat' value +-- using standard decimal notation (e.g. @245000@, @0.0015@). +-- +-- This behaves as 'showFFloat', except that a decimal point +-- is always guaranteed, even if not needed. +showFFloatAlt :: (RealFloat a) => Maybe Int -> a -> ShowS + +-- | Show a signed 'RealFloat' value +-- using standard decimal notation for arguments whose absolute value lies +-- between @0.1@ and @9,999,999@, and scientific notation otherwise. +-- +-- This behaves as 'showFFloat', except that a decimal point +-- is always guaranteed, even if not needed. +showGFloatAlt :: (RealFloat a) => Maybe Int -> a -> ShowS + +showFFloatAlt d x = showString (formatRealFloatAlt FFFixed d True x) +showGFloatAlt d x = showString (formatRealFloatAlt FFGeneric d True x) -- --------------------------------------------------------------------------- -- Integer printing functions -- | Shows a /non-negative/ 'Integral' number using the base specified by the -- first argument, and the character representation specified by the second. -showIntAtBase :: Integral a => a -> (Int -> Char) -> a -> ShowS +showIntAtBase :: (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS showIntAtBase base toChr n0 r0 | base <= 1 = error ("Numeric.showIntAtBase: applied to unsupported base " ++ show base) | n0 < 0 = error ("Numeric.showIntAtBase: applied to negative number " ++ show n0) @@ -212,9 +220,9 @@ showIntAtBase base toChr n0 r0 r' = c : r -- | Show /non-negative/ 'Integral' numbers in base 16. -showHex :: Integral a => a -> ShowS +showHex :: (Integral a,Show a) => a -> ShowS showHex = showIntAtBase 16 intToDigit -- | Show /non-negative/ 'Integral' numbers in base 8. -showOct :: Integral a => a -> ShowS +showOct :: (Integral a, Show a) => a -> ShowS showOct = showIntAtBase 8 intToDigit