[project @ 2002-02-12 11:44:54 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelReal.lhs
1 % ------------------------------------------------------------------------------
2 % $Id: PrelReal.lhs,v 1.16 2001/09/26 16:27:04 simonpj Exp $
3 %
4 % (c) The University of Glasgow, 1994-2000
5 %
6
7 \section[PrelReal]{Module @PrelReal@}
8
9 The types
10
11         Ratio, Rational
12
13 and the classes
14
15         Real
16         Integral
17         Fractional
18         RealFrac
19
20
21 \begin{code}
22 {-# OPTIONS -fno-implicit-prelude #-}
23
24 module PrelReal where
25
26 import {-# SOURCE #-} PrelErr
27 import PrelBase
28 import PrelNum
29 import PrelList
30 import PrelEnum
31 import PrelShow
32
33 infixr 8  ^, ^^
34 infixl 7  /, `quot`, `rem`, `div`, `mod`
35
36 default ()              -- Double isn't available yet, 
37                         -- and we shouldn't be using defaults anyway
38 \end{code}
39
40
41 %*********************************************************
42 %*                                                      *
43 \subsection{The @Ratio@ and @Rational@ types}
44 %*                                                      *
45 %*********************************************************
46
47 \begin{code}
48 data  (Integral a)      => Ratio a = !a :% !a  deriving (Eq)
49 type  Rational          =  Ratio Integer
50 \end{code}
51
52
53 \begin{code}
54 {-# SPECIALISE (%) :: Integer -> Integer -> Rational #-}
55 (%)                     :: (Integral a) => a -> a -> Ratio a
56 numerator, denominator  :: (Integral a) => Ratio a -> a
57 \end{code}
58
59 \tr{reduce} is a subsidiary function used only in this module .
60 It normalises a ratio by dividing both numerator and denominator by
61 their greatest common divisor.
62
63 \begin{code}
64 reduce ::  (Integral a) => a -> a -> Ratio a
65 {-# SPECIALISE reduce :: Integer -> Integer -> Rational #-}
66 reduce _ 0              =  error "Ratio.%: zero denominator"
67 reduce x y              =  (x `quot` d) :% (y `quot` d)
68                            where d = gcd x y
69 \end{code}
70
71 \begin{code}
72 x % y                   =  reduce (x * signum y) (abs y)
73
74 numerator   (x :% _)    =  x
75 denominator (_ :% y)    =  y
76 \end{code}
77
78
79 %*********************************************************
80 %*                                                      *
81 \subsection{Standard numeric classes}
82 %*                                                      *
83 %*********************************************************
84
85 \begin{code}
86 class  (Num a, Ord a) => Real a  where
87     toRational          ::  a -> Rational
88
89 class  (Real a, Enum a) => Integral a  where
90     quot, rem, div, mod :: a -> a -> a
91     quotRem, divMod     :: a -> a -> (a,a)
92     toInteger           :: a -> Integer
93
94     n `quot` d          =  q  where (q,_) = quotRem n d
95     n `rem` d           =  r  where (_,r) = quotRem n d
96     n `div` d           =  q  where (q,_) = divMod n d
97     n `mod` d           =  r  where (_,r) = divMod n d
98     divMod n d          =  if signum r == negate (signum d) then (q-1, r+d) else qr
99                            where qr@(q,r) = quotRem n d
100
101 class  (Num a) => Fractional a  where
102     (/)                 :: a -> a -> a
103     recip               :: a -> a
104     fromRational        :: Rational -> a
105
106     recip x             =  1 / x
107     x / y               = x * recip y
108
109 class  (Real a, Fractional a) => RealFrac a  where
110     properFraction      :: (Integral b) => a -> (b,a)
111     truncate, round     :: (Integral b) => a -> b
112     ceiling, floor      :: (Integral b) => a -> b
113
114     truncate x          =  m  where (m,_) = properFraction x
115     
116     round x             =  let (n,r) = properFraction x
117                                m     = if r < 0 then n - 1 else n + 1
118                            in case signum (abs r - 0.5) of
119                                 -1 -> n
120                                 0  -> if even n then n else m
121                                 1  -> m
122     
123     ceiling x           =  if r > 0 then n + 1 else n
124                            where (n,r) = properFraction x
125     
126     floor x             =  if r < 0 then n - 1 else n
127                            where (n,r) = properFraction x
128 \end{code}
129
130
131 These 'numeric' enumerations come straight from the Report
132
133 \begin{code}
134 numericEnumFrom         :: (Fractional a) => a -> [a]
135 numericEnumFrom         =  iterate (+1)
136
137 numericEnumFromThen     :: (Fractional a) => a -> a -> [a]
138 numericEnumFromThen n m =  iterate (+(m-n)) n
139
140 numericEnumFromTo       :: (Ord a, Fractional a) => a -> a -> [a]
141 numericEnumFromTo n m   = takeWhile (<= m + 1/2) (numericEnumFrom n)
142
143 numericEnumFromThenTo   :: (Ord a, Fractional a) => a -> a -> a -> [a]
144 numericEnumFromThenTo e1 e2 e3 = takeWhile pred (numericEnumFromThen e1 e2)
145                                 where
146                                  mid = (e2 - e1) / 2
147                                  pred | e2 > e1   = (<= e3 + mid)
148                                       | otherwise = (>= e3 + mid)
149 \end{code}
150
151
152 %*********************************************************
153 %*                                                      *
154 \subsection{Instances for @Int@}
155 %*                                                      *
156 %*********************************************************
157
158 \begin{code}
159 instance  Real Int  where
160     toRational x        =  toInteger x % 1
161
162 instance  Integral Int  where
163     toInteger i = int2Integer i  -- give back a full-blown Integer
164
165     -- Following chks for zero divisor are non-standard (WDP)
166     a `quot` b  =  if b /= 0
167                    then a `quotInt` b
168                    else error "Prelude.Integral.quot{Int}: divide by 0"
169     a `rem` b   =  if b /= 0
170                    then a `remInt` b
171                    else error "Prelude.Integral.rem{Int}: divide by 0"
172
173     x `div` y = x `divInt` y
174     x `mod` y = x `modInt` y
175
176     a `quotRem` b = a `quotRemInt` b
177     a `divMod`  b = a `divModInt`  b
178 \end{code}
179
180
181 %*********************************************************
182 %*                                                      *
183 \subsection{Instances for @Integer@}
184 %*                                                      *
185 %*********************************************************
186
187 \begin{code}
188 instance  Real Integer  where
189     toRational x        =  x % 1
190
191 instance  Integral Integer where
192     toInteger n      = n
193
194     n `quot` d = n `quotInteger` d
195     n `rem`  d = n `remInteger`  d
196
197     n `div` d   =  q  where (q,_) = divMod n d
198     n `mod` d   =  r  where (_,r) = divMod n d
199
200     a `divMod` b = a `divModInteger` b
201     a `quotRem` b = a `quotRemInteger` b
202 \end{code}
203
204
205 %*********************************************************
206 %*                                                      *
207 \subsection{Instances for @Ratio@}
208 %*                                                      *
209 %*********************************************************
210
211 \begin{code}
212 instance  (Integral a)  => Ord (Ratio a)  where
213     {-# SPECIALIZE instance Ord Rational #-}
214     (x:%y) <= (x':%y')  =  x * y' <= x' * y
215     (x:%y) <  (x':%y')  =  x * y' <  x' * y
216
217 instance  (Integral a)  => Num (Ratio a)  where
218     {-# SPECIALIZE instance Num Rational #-}
219     (x:%y) + (x':%y')   =  reduce (x*y' + x'*y) (y*y')
220     (x:%y) - (x':%y')   =  reduce (x*y' - x'*y) (y*y')
221     (x:%y) * (x':%y')   =  reduce (x * x') (y * y')
222     negate (x:%y)       =  (-x) :% y
223     abs (x:%y)          =  abs x :% y
224     signum (x:%_)       =  signum x :% 1
225     fromInteger x       =  fromInteger x :% 1
226
227 instance  (Integral a)  => Fractional (Ratio a)  where
228     {-# SPECIALIZE instance Fractional Rational #-}
229     (x:%y) / (x':%y')   =  (x*y') % (y*x')
230     recip (x:%y)        =  y % x
231     fromRational (x:%y) =  fromInteger x :% fromInteger y
232
233 instance  (Integral a)  => Real (Ratio a)  where
234     {-# SPECIALIZE instance Real Rational #-}
235     toRational (x:%y)   =  toInteger x :% toInteger y
236
237 instance  (Integral a)  => RealFrac (Ratio a)  where
238     {-# SPECIALIZE instance RealFrac Rational #-}
239     properFraction (x:%y) = (fromInteger (toInteger q), r:%y)
240                           where (q,r) = quotRem x y
241
242 instance  (Integral a)  => Show (Ratio a)  where
243     {-# SPECIALIZE instance Show Rational #-}
244     showsPrec p (x:%y)  =  showParen (p > ratio_prec)
245                                (shows x . showString " % " . shows y)
246
247 ratio_prec :: Int
248 ratio_prec = 7
249
250 instance  (Integral a)  => Enum (Ratio a)  where
251     {-# SPECIALIZE instance Enum Rational #-}
252     succ x              =  x + 1
253     pred x              =  x - 1
254
255     toEnum n            =  fromInteger (int2Integer n) :% 1
256     fromEnum            =  fromInteger . truncate
257
258     enumFrom            =  numericEnumFrom
259     enumFromThen        =  numericEnumFromThen
260     enumFromTo          =  numericEnumFromTo
261     enumFromThenTo      =  numericEnumFromThenTo
262 \end{code}
263
264
265 %*********************************************************
266 %*                                                      *
267 \subsection{Coercions}
268 %*                                                      *
269 %*********************************************************
270
271 \begin{code}
272 fromIntegral :: (Integral a, Num b) => a -> b
273 fromIntegral = fromInteger . toInteger
274
275 {-# RULES
276 "fromIntegral/Int->Int" fromIntegral = id :: Int -> Int
277     #-}
278
279 realToFrac :: (Real a, Fractional b) => a -> b
280 realToFrac = fromRational . toRational
281
282 {-# RULES
283 "realToFrac/Int->Int" realToFrac = id :: Int -> Int
284     #-}
285
286 -- For backward compatibility
287 {-# DEPRECATED fromInt "use fromIntegral instead" #-}
288 fromInt :: Num a => Int -> a
289 fromInt = fromIntegral
290
291 -- For backward compatibility
292 {-# DEPRECATED toInt "use fromIntegral instead" #-}
293 toInt :: Integral a => a -> Int
294 toInt = fromIntegral
295 \end{code}
296
297 %*********************************************************
298 %*                                                      *
299 \subsection{Overloaded numeric functions}
300 %*                                                      *
301 %*********************************************************
302
303 \begin{code}
304 showSigned :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
305 showSigned showPos p x 
306    | x < 0     = showParen (p > 6) (showChar '-' . showPos (-x))
307    | otherwise = showPos x
308
309 even, odd       :: (Integral a) => a -> Bool
310 even n          =  n `rem` 2 == 0
311 odd             =  not . even
312
313 -------------------------------------------------------
314 {-# SPECIALISE (^) ::
315         Integer -> Integer -> Integer,
316         Integer -> Int -> Integer,
317         Int -> Int -> Int #-}
318 (^)             :: (Num a, Integral b) => a -> b -> a
319 _ ^ 0           =  1
320 x ^ n | n > 0   =  f x (n-1) x
321                    where f _ 0 y = y
322                          f a d y = g a d  where
323                                    g b i | even i  = g (b*b) (i `quot` 2)
324                                          | otherwise = f b (i-1) (b*y)
325 _ ^ _           = error "Prelude.^: negative exponent"
326
327 {-# SPECIALISE (^^) ::
328         Rational -> Int -> Rational #-}
329 (^^)            :: (Fractional a, Integral b) => a -> b -> a
330 x ^^ n          =  if n >= 0 then x^n else recip (x^(negate n))
331
332
333 -------------------------------------------------------
334 gcd             :: (Integral a) => a -> a -> a
335 gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
336 gcd x y         =  gcd' (abs x) (abs y)
337                    where gcd' a 0  =  a
338                          gcd' a b  =  gcd' b (a `rem` b)
339
340 lcm             :: (Integral a) => a -> a -> a
341 {-# SPECIALISE lcm :: Int -> Int -> Int #-}
342 lcm _ 0         =  0
343 lcm 0 _         =  0
344 lcm x y         =  abs ((x `quot` (gcd x y)) * y)
345
346
347 {-# RULES
348 "gcd/Int->Int->Int"             gcd = gcdInt
349 "gcd/Integer->Integer->Integer" gcd = gcdInteger
350 "lcm/Integer->Integer->Integer" lcm = lcmInteger
351  #-}
352
353 integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
354 integralEnumFrom n = map fromInteger [toInteger n .. toInteger (maxBound `asTypeOf` n)]
355
356 integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a]
357 integralEnumFromThen n1 n2
358   | i_n2 >= i_n1  = map fromInteger [i_n1, i_n2 .. toInteger (maxBound `asTypeOf` n1)]
359   | otherwise     = map fromInteger [i_n1, i_n2 .. toInteger (minBound `asTypeOf` n1)]
360   where
361     i_n1 = toInteger n1
362     i_n2 = toInteger n2
363
364 integralEnumFromTo :: Integral a => a -> a -> [a]
365 integralEnumFromTo n m = map fromInteger [toInteger n .. toInteger m]
366
367 integralEnumFromThenTo :: Integral a => a -> a -> a -> [a]
368 integralEnumFromThenTo n1 n2 m
369   = map fromInteger [toInteger n1, toInteger n2 .. toInteger m]
370 \end{code}