Adjust behaviour of gcd
[ghc-base.git] / Numeric.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Numeric
6 -- Copyright   :  (c) The University of Glasgow 2002
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  portable
12 --
13 -- Odds and ends, mostly functions for reading and showing
14 -- 'RealFloat'-like kind of values.
15 --
16 -----------------------------------------------------------------------------
17
18 module Numeric (
19
20         -- * Showing
21
22         showSigned,       -- :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
23
24         showIntAtBase,    -- :: Integral a => a -> (a -> Char) -> a -> ShowS
25         showInt,          -- :: Integral a => a -> ShowS
26         showHex,          -- :: Integral a => a -> ShowS
27         showOct,          -- :: Integral a => a -> ShowS
28
29         showEFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
30         showFFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
31         showGFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
32         showFloat,        -- :: (RealFloat a) => a -> ShowS
33
34         floatToDigits,    -- :: (RealFloat a) => Integer -> a -> ([Int], Int)
35
36         -- * Reading
37
38         -- | /NB:/ 'readInt' is the \'dual\' of 'showIntAtBase',
39         -- and 'readDec' is the \`dual\' of 'showInt'.
40         -- The inconsistent naming is a historical accident.
41
42         readSigned,       -- :: (Real a) => ReadS a -> ReadS a
43
44         readInt,          -- :: (Integral a) => a -> (Char -> Bool)
45                           --         -> (Char -> Int) -> ReadS a
46         readDec,          -- :: (Integral a) => ReadS a
47         readOct,          -- :: (Integral a) => ReadS a
48         readHex,          -- :: (Integral a) => ReadS a
49
50         readFloat,        -- :: (RealFloat a) => ReadS a
51
52         lexDigits,        -- :: ReadS String
53
54         -- * Miscellaneous
55
56         fromRat,          -- :: (RealFloat a) => Rational -> a
57
58         ) where
59
60 #ifdef __GLASGOW_HASKELL__
61 import GHC.Base
62 import GHC.Read
63 import GHC.Real
64 import GHC.Float
65 import GHC.Num
66 import GHC.Show
67 import Data.Maybe
68 import Text.ParserCombinators.ReadP( ReadP, readP_to_S, pfail )
69 import qualified Text.Read.Lex as L
70 #else
71 import Data.Char
72 #endif
73
74 #ifdef __HUGS__
75 import Hugs.Prelude
76 import Hugs.Numeric
77 #endif
78
79 #ifdef __GLASGOW_HASKELL__
80 -- -----------------------------------------------------------------------------
81 -- Reading
82
83 -- | Reads an /unsigned/ 'Integral' value in an arbitrary base.
84 readInt :: Num a
85   => a                  -- ^ the base
86   -> (Char -> Bool)     -- ^ a predicate distinguishing valid digits in this base
87   -> (Char -> Int)      -- ^ a function converting a valid digit character to an 'Int'
88   -> ReadS a
89 readInt base isDigit valDigit = readP_to_S (L.readIntP base isDigit valDigit)
90
91 -- | Read an unsigned number in octal notation.
92 readOct :: Num a => ReadS a
93 readOct = readP_to_S L.readOctP
94
95 -- | Read an unsigned number in decimal notation.
96 readDec :: Num a => ReadS a
97 readDec = readP_to_S L.readDecP
98
99 -- | Read an unsigned number in hexadecimal notation.
100 -- Both upper or lower case letters are allowed.
101 readHex :: Num a => ReadS a
102 readHex = readP_to_S L.readHexP 
103
104 -- | Reads an /unsigned/ 'RealFrac' value,
105 -- expressed in decimal scientific notation.
106 readFloat :: RealFrac a => ReadS a
107 readFloat = readP_to_S readFloatP
108
109 readFloatP :: RealFrac a => ReadP a
110 readFloatP =
111   do tok <- L.lex
112      case tok of
113        L.Rat y  -> return (fromRational y)
114        L.Int i  -> return (fromInteger i)
115        _        -> pfail
116
117 -- It's turgid to have readSigned work using list comprehensions,
118 -- but it's specified as a ReadS to ReadS transformer
119 -- With a bit of luck no one will use it.
120
121 -- | Reads a /signed/ 'Real' value, given a reader for an unsigned value.
122 readSigned :: (Real a) => ReadS a -> ReadS a
123 readSigned readPos = readParen False read'
124                      where read' r  = read'' r ++
125                                       (do
126                                         ("-",s) <- lex r
127                                         (x,t)   <- read'' s
128                                         return (-x,t))
129                            read'' r = do
130                                (str,s) <- lex r
131                                (n,"")  <- readPos str
132                                return (n,s)
133
134 -- -----------------------------------------------------------------------------
135 -- Showing
136
137 -- | Show /non-negative/ 'Integral' numbers in base 10.
138 showInt :: Integral a => a -> ShowS
139 showInt n0 cs0
140     | n0 < 0    = error "Numeric.showInt: can't show negative numbers"
141     | otherwise = go n0 cs0
142     where
143     go n cs
144         | n < 10    = case unsafeChr (ord '0' + fromIntegral n) of
145             c@(C# _) -> c:cs
146         | otherwise = case unsafeChr (ord '0' + fromIntegral r) of
147             c@(C# _) -> go q (c:cs)
148         where
149         (q,r) = n `quotRem` 10
150
151 -- Controlling the format and precision of floats. The code that
152 -- implements the formatting itself is in @PrelNum@ to avoid
153 -- mutual module deps.
154
155 {-# SPECIALIZE showEFloat ::
156         Maybe Int -> Float  -> ShowS,
157         Maybe Int -> Double -> ShowS #-}
158 {-# SPECIALIZE showFFloat ::
159         Maybe Int -> Float  -> ShowS,
160         Maybe Int -> Double -> ShowS #-}
161 {-# SPECIALIZE showGFloat ::
162         Maybe Int -> Float  -> ShowS,
163         Maybe Int -> Double -> ShowS #-}
164
165 -- | Show a signed 'RealFloat' value
166 -- using scientific (exponential) notation (e.g. @2.45e2@, @1.5e-3@).
167 --
168 -- In the call @'showEFloat' digs val@, if @digs@ is 'Nothing',
169 -- the value is shown to full precision; if @digs@ is @'Just' d@,
170 -- then at most @d@ digits after the decimal point are shown.
171 showEFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
172
173 -- | Show a signed 'RealFloat' value
174 -- using standard decimal notation (e.g. @245000@, @0.0015@).
175 --
176 -- In the call @'showFFloat' digs val@, if @digs@ is 'Nothing',
177 -- the value is shown to full precision; if @digs@ is @'Just' d@,
178 -- then at most @d@ digits after the decimal point are shown.
179 showFFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
180
181 -- | Show a signed 'RealFloat' value
182 -- using standard decimal notation for arguments whose absolute value lies 
183 -- between @0.1@ and @9,999,999@, and scientific notation otherwise.
184 --
185 -- In the call @'showGFloat' digs val@, if @digs@ is 'Nothing',
186 -- the value is shown to full precision; if @digs@ is @'Just' d@,
187 -- then at most @d@ digits after the decimal point are shown.
188 showGFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
189
190 showEFloat d x =  showString (formatRealFloat FFExponent d x)
191 showFFloat d x =  showString (formatRealFloat FFFixed d x)
192 showGFloat d x =  showString (formatRealFloat FFGeneric d x)
193 #endif  /* __GLASGOW_HASKELL__ */
194
195 -- ---------------------------------------------------------------------------
196 -- Integer printing functions
197
198 -- | Shows a /non-negative/ 'Integral' number using the base specified by the
199 -- first argument, and the character representation specified by the second.
200 showIntAtBase :: Integral a => a -> (Int -> Char) -> a -> ShowS
201 showIntAtBase base toChr n0 r0
202   | base <= 1 = error ("Numeric.showIntAtBase: applied to unsupported base " ++ show base)
203   | n0 <  0   = error ("Numeric.showIntAtBase: applied to negative number " ++ show n0)
204   | otherwise = showIt (quotRem n0 base) r0
205    where
206     showIt (n,d) r = seq c $ -- stricter than necessary
207       case n of
208         0 -> r'
209         _ -> showIt (quotRem n base) r'
210      where
211       c  = toChr (fromIntegral d)
212       r' = c : r
213
214 -- | Show /non-negative/ 'Integral' numbers in base 16.
215 showHex :: Integral a => a -> ShowS
216 showHex = showIntAtBase 16 intToDigit
217
218 -- | Show /non-negative/ 'Integral' numbers in base 8.
219 showOct :: Integral a => a -> ShowS
220 showOct = showIntAtBase 8  intToDigit