[project @ 1999-12-20 10:34:27 by simonpj]
[ghc-hetmet.git] / ghc / lib / std / PrelReal.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1996
3 %
4
5 \section[PrelReal]{Module @PrelReal@}
6
7 The types
8
9         Ratio, Rational
10
11 and the classes
12
13         Real
14         Integral
15         Fractional
16         RealFrac
17
18
19 \begin{code}
20 {-# OPTIONS -fno-implicit-prelude #-}
21
22 module PrelReal where
23
24 import {-# SOURCE #-} PrelErr
25 import PrelBase
26 import PrelNum
27 import PrelList
28 import PrelEnum
29 import PrelShow
30
31 infixr 8  ^, ^^
32 infixl 7  /, `quot`, `rem`, `div`, `mod`
33
34 default ()              -- Double isn't available yet, 
35                         -- and we shouldn't be using defaults anyway
36 \end{code}
37
38
39 %*********************************************************
40 %*                                                      *
41 \subsection{The @Ratio@ and @Rational@ types}
42 %*                                                      *
43 %*********************************************************
44
45 \begin{code}
46 data  (Integral a)      => Ratio a = !a :% !a  deriving (Eq)
47 type  Rational          =  Ratio Integer
48 \end{code}
49
50
51 \begin{code}
52 {-# SPECIALISE (%) :: Integer -> Integer -> Rational #-}
53 (%)                     :: (Integral a) => a -> a -> Ratio a
54 numerator, denominator  :: (Integral a) => Ratio a -> a
55 \end{code}
56
57 \tr{reduce} is a subsidiary function used only in this module .
58 It normalises a ratio by dividing both numerator and denominator by
59 their greatest common divisor.
60
61 \begin{code}
62 reduce ::  (Integral a) => a -> a -> Ratio a
63 reduce _ 0              =  error "Ratio.%: zero denominator"
64 reduce x y              =  (x `quot` d) :% (y `quot` d)
65                            where d = gcd x y
66 \end{code}
67
68 \begin{code}
69 x % y                   =  reduce (x * signum y) (abs y)
70
71 numerator   (x :% _)    =  x
72 denominator (_ :% y)    =  y
73 \end{code}
74
75
76 %*********************************************************
77 %*                                                      *
78 \subsection{Standard numeric classes}
79 %*                                                      *
80 %*********************************************************
81
82 \begin{code}
83 class  (Num a, Ord a) => Real a  where
84     toRational          ::  a -> Rational
85
86 class  (Real a, Enum a) => Integral a  where
87     quot, rem, div, mod :: a -> a -> a
88     quotRem, divMod     :: a -> a -> (a,a)
89     toInteger           :: a -> Integer
90     toInt               :: a -> Int -- partain: Glasgow extension
91
92     n `quot` d          =  q  where (q,_) = quotRem n d
93     n `rem` d           =  r  where (_,r) = quotRem n d
94     n `div` d           =  q  where (q,_) = divMod n d
95     n `mod` d           =  r  where (_,r) = divMod n d
96     divMod n d          =  if signum r == negate (signum d) then (q-1, r+d) else qr
97                            where qr@(q,r) = quotRem n d
98
99 class  (Num a) => Fractional a  where
100     (/)                 :: a -> a -> a
101     recip               :: a -> a
102     fromRational        :: Rational -> a
103
104     recip x             =  1 / x
105     x / y               = x * recip y
106
107 class  (Real a, Fractional a) => RealFrac a  where
108     properFraction      :: (Integral b) => a -> (b,a)
109     truncate, round     :: (Integral b) => a -> b
110     ceiling, floor      :: (Integral b) => a -> b
111
112     truncate x          =  m  where (m,_) = properFraction x
113     
114     round x             =  let (n,r) = properFraction x
115                                m     = if r < 0 then n - 1 else n + 1
116                            in case signum (abs r - 0.5) of
117                                 -1 -> n
118                                 0  -> if even n then n else m
119                                 1  -> m
120     
121     ceiling x           =  if r > 0 then n + 1 else n
122                            where (n,r) = properFraction x
123     
124     floor x             =  if r < 0 then n - 1 else n
125                            where (n,r) = properFraction x
126 \end{code}
127
128
129 %*********************************************************
130 %*                                                      *
131 \subsection{Instances for @Int@}
132 %*                                                      *
133 %*********************************************************
134
135 \begin{code}
136 instance  Real Int  where
137     toRational x        =  toInteger x % 1
138
139 instance  Integral Int  where
140     toInteger i = int2Integer i  -- give back a full-blown Integer
141     toInt x     = x
142
143     -- Following chks for zero divisor are non-standard (WDP)
144     a `quot` b  =  if b /= 0
145                    then a `quotInt` b
146                    else error "Prelude.Integral.quot{Int}: divide by 0"
147     a `rem` b   =  if b /= 0
148                    then a `remInt` b
149                    else error "Prelude.Integral.rem{Int}: divide by 0"
150
151     x `div` y = x `divInt` y
152     x `mod` y = x `modInt` y
153
154     a `quotRem` b = a `quotRemInt` b
155     a `divMod`  b = a `divModInt`  b
156 \end{code}
157
158
159 %*********************************************************
160 %*                                                      *
161 \subsection{Instances for @Integer@}
162 %*                                                      *
163 %*********************************************************
164
165 \begin{code}
166 instance  Real Integer  where
167     toRational x        =  x % 1
168
169 instance  Integral Integer where
170     toInteger n      = n
171     toInt n          = integer2Int n
172
173     n `quot` d = n `quotInteger` d
174     n `rem`  d = n `remInteger`  d
175
176     n `div` d   =  q  where (q,_) = divMod n d
177     n `mod` d   =  r  where (_,r) = divMod n d
178
179     a `divMod` b = a `divModInteger` b
180     a `quotRem` b = a `quotRemInteger` b
181 \end{code}
182
183
184 %*********************************************************
185 %*                                                      *
186 \subsection{Instances for @Ratio@}
187 %*                                                      *
188 %*********************************************************
189
190 \begin{code}
191 instance  (Integral a)  => Ord (Ratio a)  where
192     (x:%y) <= (x':%y')  =  x * y' <= x' * y
193     (x:%y) <  (x':%y')  =  x * y' <  x' * y
194
195 instance  (Integral a)  => Num (Ratio a)  where
196     (x:%y) + (x':%y')   =  reduce (x*y' + x'*y) (y*y')
197     (x:%y) - (x':%y')   =  reduce (x*y' - x'*y) (y*y')
198     (x:%y) * (x':%y')   =  reduce (x * x') (y * y')
199     negate (x:%y)       =  (-x) :% y
200     abs (x:%y)          =  abs x :% y
201     signum (x:%_)       =  signum x :% 1
202     fromInteger x       =  fromInteger x :% 1
203
204 instance  (Integral a)  => Fractional (Ratio a)  where
205     (x:%y) / (x':%y')   =  (x*y') % (y*x')
206     recip (x:%y)        =  if x < 0 then (-y) :% (-x) else y :% x
207     fromRational (x:%y) =  fromInteger x :% fromInteger y
208
209 instance  (Integral a)  => Real (Ratio a)  where
210     toRational (x:%y)   =  toInteger x :% toInteger y
211
212 instance  (Integral a)  => RealFrac (Ratio a)  where
213     properFraction (x:%y) = (fromInteger (toInteger q), r:%y)
214                           where (q,r) = quotRem x y
215
216 instance  (Integral a)  => Show (Ratio a)  where
217     showsPrec p (x:%y)  =  showParen (p > ratio_prec)
218                                (shows x . showString " % " . shows y)
219
220 ratio_prec :: Int
221 ratio_prec = 7
222
223 instance  (Integral a)  => Enum (Ratio a)  where
224     succ x              =  x + 1
225     pred x              =  x - 1
226
227     toEnum n            =  fromInt n :% 1
228     fromEnum            =  fromInteger . truncate
229
230     enumFrom            =  bounded_iterator True (1)
231     enumFromThen n m    =  bounded_iterator (diff >= 0) diff n 
232                         where diff = m - n
233
234 bounded_iterator :: (Ord a, Num a) => Bool -> a -> a -> [a]
235 bounded_iterator inc step v 
236    | inc      && v > new_v = [v]  -- oflow
237    | not inc  && v < new_v = [v]  -- uflow
238    | otherwise             = v : bounded_iterator inc step new_v
239   where
240    new_v = v + step
241 \end{code}
242
243
244 %*********************************************************
245 %*                                                      *
246 \subsection{Overloaded numeric functions}
247 %*                                                      *
248 %*********************************************************
249
250 \begin{code}
251 showSigned :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
252 showSigned showPos p x 
253    | x < 0     = showParen (p > 6) (showChar '-' . showPos (-x))
254    | otherwise = showPos x
255
256 even, odd       :: (Integral a) => a -> Bool
257 even n          =  n `rem` 2 == 0
258 odd             =  not . even
259
260 -------------------------------------------------------
261 {-# SPECIALISE (^) ::
262         Integer -> Integer -> Integer,
263         Integer -> Int -> Integer,
264         Int -> Int -> Int #-}
265 (^)             :: (Num a, Integral b) => a -> b -> a
266 _ ^ 0           =  1
267 x ^ n | n > 0   =  f x (n-1) x
268                    where f _ 0 y = y
269                          f a d y = g a d  where
270                                    g b i | even i  = g (b*b) (i `quot` 2)
271                                          | otherwise = f b (i-1) (b*y)
272 _ ^ _           = error "Prelude.^: negative exponent"
273
274 {- SPECIALISE (^^) ::
275         Rational -> Int -> Rational #-}
276 (^^)            :: (Fractional a, Integral b) => a -> b -> a
277 x ^^ n          =  if n >= 0 then x^n else recip (x^(negate n))
278
279
280 -------------------------------------------------------
281 gcd             :: (Integral a) => a -> a -> a
282 gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
283 gcd x y         =  gcd' (abs x) (abs y)
284                    where gcd' a 0  =  a
285                          gcd' a b  =  gcd' b (a `rem` b)
286
287 lcm             :: (Integral a) => a -> a -> a
288 {-# SPECIALISE lcm :: Int -> Int -> Int #-}
289 lcm _ 0         =  0
290 lcm 0 _         =  0
291 lcm x y         =  abs ((x `quot` (gcd x y)) * y)
292
293
294 {-# RULES
295 "Int.gcd"      forall a b . gcd  a b = gcdInt a b
296 "Integer.gcd"  forall a b . gcd  a b = gcdInteger  a b
297 "Integer.lcm"  forall a b . lcm  a b = lcmInteger  a b
298  #-}
299 \end{code}