[project @ 2000-02-25 22:41:41 by andy]
[ghc-hetmet.git] / ghc / lib / std / Numeric.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1997-99
3 %
4 \section[Numeric]{Numeric interface}
5
6 Odds and ends, mostly functions for reading and showing
7 \tr{RealFloat}-like kind of values.
8
9
10 \begin{code}
11 module Numeric
12
13         ( fromRat          -- :: (RealFloat a) => Rational -> a
14         , showSigned       -- :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
15         , readSigned       -- :: (Real a) => ReadS a -> ReadS a
16         , showInt          -- :: Integral a => a -> ShowS
17         , readInt          -- :: (Integral a) => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
18         
19         , readDec          -- :: (Integral a) => ReadS a
20         , readOct          -- :: (Integral a) => ReadS a
21         , readHex          -- :: (Integral a) => ReadS a
22
23         , showEFloat       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
24         , showFFloat       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
25         , showGFloat       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
26         , showFloat        -- :: (RealFloat a) => a -> ShowS
27         , readFloat        -- :: (RealFloat a) => ReadS a
28         
29          
30         , floatToDigits    -- :: (RealFloat a) => Integer -> a -> ([Int], Int)
31         , lexDigits        -- :: ReadS String
32
33           -- Implementation checked wrt. Haskell 98 lib report, 1/99.
34         ) where
35
36 import Char
37
38 #ifndef __HUGS__
39         -- GHC imports
40 import Prelude          -- For dependencies
41 import PrelBase         ( Char(..) )
42 import PrelRead         -- Lots of things
43 import PrelReal         ( showSigned )
44 import PrelFloat        ( fromRat, FFFormat(..), 
45                           formatRealFloat, floatToDigits, showFloat
46                         )
47 import PrelNum          ( ord_0 )
48 #else
49         -- Hugs imports
50 import Array
51 #endif
52
53 \end{code}
54
55 #ifndef __HUGS__
56
57 \begin{code}
58 showInt :: Integral a => a -> ShowS
59 showInt i rs
60   | i < 0     = error "Numeric.showInt: can't show negative numbers"
61   | otherwise = go i rs
62     where
63      go n r = 
64       case quotRem n 10 of                 { (n', d) ->
65       case chr (ord_0 + fromIntegral d) of { C# c# -> -- stricter than necessary
66       let
67         r' = C# c# : r
68       in
69       if n' == 0 then r' else go n' r'
70       }}
71 \end{code}
72
73 Controlling the format and precision of floats. The code that
74 implements the formatting itself is in @PrelNum@ to avoid
75 mutual module deps.
76
77 \begin{code}
78 showEFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
79 showFFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
80 showGFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
81
82 showEFloat d x =  showString (formatRealFloat FFExponent d x)
83 showFFloat d x =  showString (formatRealFloat FFFixed d x)
84 showGFloat d x =  showString (formatRealFloat FFGeneric d x)
85
86 \end{code}
87
88 #else   
89
90 %*********************************************************
91 %*                                                      *
92         All of this code is for Hugs only
93         GHC gets it from PrelFloat!
94 %*                                                      *
95 %*********************************************************
96
97 \begin{code}
98 -- This converts a rational to a floating.  This should be used in the
99 -- Fractional instances of Float and Double.
100
101 fromRat :: (RealFloat a) => Rational -> a
102 fromRat x = 
103     if x == 0 then encodeFloat 0 0              -- Handle exceptional cases
104     else if x < 0 then - fromRat' (-x)          -- first.
105     else fromRat' x
106
107 -- Conversion process:
108 -- Scale the rational number by the RealFloat base until
109 -- it lies in the range of the mantissa (as used by decodeFloat/encodeFloat).
110 -- Then round the rational to an Integer and encode it with the exponent
111 -- that we got from the scaling.
112 -- To speed up the scaling process we compute the log2 of the number to get
113 -- a first guess of the exponent.
114 fromRat' :: (RealFloat a) => Rational -> a
115 fromRat' x = r
116   where b = floatRadix r
117         p = floatDigits r
118         (minExp0, _) = floatRange r
119         minExp = minExp0 - p            -- the real minimum exponent
120         xMin = toRational (expt b (p-1))
121         xMax = toRational (expt b p)
122         p0 = (integerLogBase b (numerator x) -
123               integerLogBase b (denominator x) - p) `max` minExp
124         f = if p0 < 0 then 1 % expt b (-p0) else expt b p0 % 1
125         (x', p') = scaleRat (toRational b) minExp xMin xMax p0 (x / f)
126         r = encodeFloat (round x') p'
127
128 -- Scale x until xMin <= x < xMax, or p (the exponent) <= minExp.
129 scaleRat :: Rational -> Int -> Rational -> Rational -> 
130              Int -> Rational -> (Rational, Int)
131 scaleRat b minExp xMin xMax p x =
132     if p <= minExp then
133         (x, p)
134     else if x >= xMax then
135         scaleRat b minExp xMin xMax (p+1) (x/b)
136     else if x < xMin  then
137         scaleRat b minExp xMin xMax (p-1) (x*b)
138     else
139         (x, p)
140
141 -- Exponentiation with a cache for the most common numbers.
142 minExpt = 0::Int
143 maxExpt = 1100::Int
144 expt :: Integer -> Int -> Integer
145 expt base n =
146     if base == 2 && n >= minExpt && n <= maxExpt then
147         expts!n
148     else
149         base^n
150
151 expts :: Array Int Integer
152 expts = array (minExpt,maxExpt) [(n,2^n) | n <- [minExpt .. maxExpt]]
153
154 -- Compute the (floor of the) log of i in base b.
155 -- Simplest way would be just divide i by b until it's smaller then b,
156 -- but that would be very slow!  We are just slightly more clever.
157 integerLogBase :: Integer -> Integer -> Int
158 integerLogBase b i =
159      if i < b then
160         0
161      else
162         -- Try squaring the base first to cut down the number of divisions.
163         let l = 2 * integerLogBase (b*b) i
164             doDiv :: Integer -> Int -> Int
165             doDiv i l = if i < b then l else doDiv (i `div` b) (l+1)
166         in  doDiv (i `div` (b^l)) l
167
168
169 -- Misc utilities to show integers and floats 
170
171 showEFloat     :: (RealFloat a) => Maybe Int -> a -> ShowS
172 showFFloat     :: (RealFloat a) => Maybe Int -> a -> ShowS
173 showGFloat     :: (RealFloat a) => Maybe Int -> a -> ShowS
174 showFloat      :: (RealFloat a) => a -> ShowS
175
176 showEFloat d x =  showString (formatRealFloat FFExponent d x)
177 showFFloat d x =  showString (formatRealFloat FFFixed d x)
178 showGFloat d x =  showString (formatRealFloat FFGeneric d x)
179 showFloat      =  showGFloat Nothing 
180
181 -- These are the format types.  This type is not exported.
182
183 data FFFormat = FFExponent | FFFixed | FFGeneric
184
185 formatRealFloat :: (RealFloat a) => FFFormat -> Maybe Int -> a -> String
186 formatRealFloat fmt decs x = s
187   where base = 10
188         s = if isNaN x then 
189                 "NaN"
190             else if isInfinite x then 
191                 if x < 0 then "-Infinity" else "Infinity"
192             else if x < 0 || isNegativeZero x then 
193                 '-' : doFmt fmt (floatToDigits (toInteger base) (-x))
194             else 
195                 doFmt fmt (floatToDigits (toInteger base) x)
196         doFmt fmt (is, e) =
197             let ds = map intToDigit is
198             in  case fmt of
199                 FFGeneric -> 
200                     doFmt (if e < 0 || e > 7 then FFExponent else FFFixed)
201                           (is, e)
202                 FFExponent ->
203                     case decs of
204                     Nothing ->
205                         case ds of
206                          ['0'] -> "0.0e0"
207                          [d]   -> d : ".0e" ++ show (e-1)
208                          d:ds  -> d : '.' : ds ++ 'e':show (e-1)
209                     Just dec ->
210                         let dec' = max dec 1 in
211                         case is of
212                          [0] -> '0':'.':take dec' (repeat '0') ++ "e0"
213                          _ ->
214                           let (ei, is') = roundTo base (dec'+1) is
215                               d:ds = map intToDigit
216                                          (if ei > 0 then init is' else is')
217                           in d:'.':ds  ++ "e" ++ show (e-1+ei)
218                 FFFixed ->
219                     case decs of
220                     Nothing ->
221                         let f 0 s ds = mk0 s ++ "." ++ mk0 ds
222                             f n s "" = f (n-1) (s++"0") ""
223                             f n s (d:ds) = f (n-1) (s++[d]) ds
224                             mk0 "" = "0"
225                             mk0 s = s
226                         in  f e "" ds
227                     Just dec ->
228                         let dec' = max dec 0 in
229                         if e >= 0 then
230                             let (ei, is') = roundTo base (dec' + e) is
231                                 (ls, rs) = splitAt (e+ei) (map intToDigit is')
232                             in  (if null ls then "0" else ls) ++ 
233                                 (if null rs then "" else '.' : rs)
234                         else
235                             let (ei, is') = roundTo base dec'
236                                               (replicate (-e) 0 ++ is)
237                                 d : ds = map intToDigit
238                                             (if ei > 0 then is' else 0:is')
239                             in  d : '.' : ds
240
241 roundTo :: Int -> Int -> [Int] -> (Int, [Int])
242 roundTo base d is = case f d is of
243                 (0, is) -> (0, is)
244                 (1, is) -> (1, 1 : is)
245   where b2 = base `div` 2
246         f n [] = (0, replicate n 0)
247         f 0 (i:_) = (if i >= b2 then 1 else 0, [])
248         f d (i:is) = 
249             let (c, ds) = f (d-1) is
250                 i' = c + i
251             in  if i' == base then (1, 0:ds) else (0, i':ds)
252
253 --
254 -- Based on "Printing Floating-Point Numbers Quickly and Accurately"
255 -- by R.G. Burger and R. K. Dybvig, in PLDI 96.
256 -- This version uses a much slower logarithm estimator.  It should be improved.
257
258 -- This function returns a list of digits (Ints in [0..base-1]) and an
259 -- exponent.
260
261 floatToDigits :: (RealFloat a) => Integer -> a -> ([Int], Int)
262
263 floatToDigits _ 0 = ([0], 0)
264 floatToDigits base x =
265     let (f0, e0) = decodeFloat x
266         (minExp0, _) = floatRange x
267         p = floatDigits x
268         b = floatRadix x
269         minExp = minExp0 - p            -- the real minimum exponent
270         -- Haskell requires that f be adjusted so denormalized numbers
271         -- will have an impossibly low exponent.  Adjust for this.
272         (f, e) = let n = minExp - e0
273                  in  if n > 0 then (f0 `div` (b^n), e0+n) else (f0, e0)
274
275         (r, s, mUp, mDn) =
276            if e >= 0 then
277                let be = b^e in
278                if f == b^(p-1) then
279                    (f*be*b*2, 2*b, be*b, b)
280                else
281                    (f*be*2, 2, be, be)
282            else
283                if e > minExp && f == b^(p-1) then
284                    (f*b*2, b^(-e+1)*2, b, 1)
285                else
286                    (f*2, b^(-e)*2, 1, 1)
287         k = 
288             let k0 =
289                     if b==2 && base==10 then
290                         -- logBase 10 2 is slightly bigger than 3/10 so
291                         -- the following will err on the low side.  Ignoring
292                         -- the fraction will make it err even more.
293                         -- Haskell promises that p-1 <= logBase b f < p.
294                         (p - 1 + e0) * 3 `div` 10
295                     else
296                         ceiling ((log (fromInteger (f+1)) + 
297                                  fromInt e * log (fromInteger b)) / 
298                                   log (fromInteger base))
299                 fixup n =
300                     if n >= 0 then
301                         if r + mUp <= expt base n * s then n else fixup (n+1)
302                     else
303                         if expt base (-n) * (r + mUp) <= s then n
304                                                            else fixup (n+1)
305             in  fixup k0
306
307         gen ds rn sN mUpN mDnN =
308             let (dn, rn') = (rn * base) `divMod` sN
309                 mUpN' = mUpN * base
310                 mDnN' = mDnN * base
311             in  case (rn' < mDnN', rn' + mUpN' > sN) of
312                 (True,  False) -> dn : ds
313                 (False, True)  -> dn+1 : ds
314                 (True,  True)  -> if rn' * 2 < sN then dn : ds else dn+1 : ds
315                 (False, False) -> gen (dn:ds) rn' sN mUpN' mDnN'
316         rds =
317             if k >= 0 then
318                 gen [] r (s * expt base k) mUp mDn
319             else
320                 let bk = expt base (-k)
321                 in  gen [] (r * bk) s (mUp * bk) (mDn * bk)
322     in  (map toInt (reverse rds), k)
323 \end{code}
324 #endif