e6d64d5eedcb820753f01bd0f35e49e03576ece4
[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 These 'numeric' enumerations come straight from the Report
130
131 \begin{code}
132 numericEnumFrom         :: (Fractional a) => a -> [a]
133 numericEnumFrom         =  iterate (+1)
134
135 numericEnumFromThen     :: (Fractional a) => a -> a -> [a]
136 numericEnumFromThen n m =  iterate (+(m-n)) n
137
138 numericEnumFromTo       :: (Ord a, Fractional a) => a -> a -> [a]
139 numericEnumFromTo n m   = takeWhile (<= m + 1/2) (numericEnumFrom n)
140
141 numericEnumFromThenTo   :: (Ord a, Fractional a) => a -> a -> a -> [a]
142 numericEnumFromThenTo e1 e2 e3 = takeWhile pred (numericEnumFromThen e1 e2)
143                                 where
144                                  mid = (e2 - e1) / 2
145                                  pred | e2 > e1   = (<= e3 + mid)
146                                       | otherwise = (>= e3 + mid)
147 \end{code}
148
149
150 %*********************************************************
151 %*                                                      *
152 \subsection{Instances for @Int@}
153 %*                                                      *
154 %*********************************************************
155
156 \begin{code}
157 instance  Real Int  where
158     toRational x        =  toInteger x % 1
159
160 instance  Integral Int  where
161     toInteger i = int2Integer i  -- give back a full-blown Integer
162     toInt x     = x
163
164     -- Following chks for zero divisor are non-standard (WDP)
165     a `quot` b  =  if b /= 0
166                    then a `quotInt` b
167                    else error "Prelude.Integral.quot{Int}: divide by 0"
168     a `rem` b   =  if b /= 0
169                    then a `remInt` b
170                    else error "Prelude.Integral.rem{Int}: divide by 0"
171
172     x `div` y = x `divInt` y
173     x `mod` y = x `modInt` y
174
175     a `quotRem` b = a `quotRemInt` b
176     a `divMod`  b = a `divModInt`  b
177 \end{code}
178
179
180 %*********************************************************
181 %*                                                      *
182 \subsection{Instances for @Integer@}
183 %*                                                      *
184 %*********************************************************
185
186 \begin{code}
187 instance  Real Integer  where
188     toRational x        =  x % 1
189
190 instance  Integral Integer where
191     toInteger n      = n
192     toInt n          = integer2Int 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     (x:%y) <= (x':%y')  =  x * y' <= x' * y
214     (x:%y) <  (x':%y')  =  x * y' <  x' * y
215
216 instance  (Integral a)  => Num (Ratio a)  where
217     (x:%y) + (x':%y')   =  reduce (x*y' + x'*y) (y*y')
218     (x:%y) - (x':%y')   =  reduce (x*y' - x'*y) (y*y')
219     (x:%y) * (x':%y')   =  reduce (x * x') (y * y')
220     negate (x:%y)       =  (-x) :% y
221     abs (x:%y)          =  abs x :% y
222     signum (x:%_)       =  signum x :% 1
223     fromInteger x       =  fromInteger x :% 1
224
225 instance  (Integral a)  => Fractional (Ratio a)  where
226     (x:%y) / (x':%y')   =  (x*y') % (y*x')
227     recip (x:%y)        =  if x < 0 then (-y) :% (-x) else y :% x
228     fromRational (x:%y) =  fromInteger x :% fromInteger y
229
230 instance  (Integral a)  => Real (Ratio a)  where
231     toRational (x:%y)   =  toInteger x :% toInteger y
232
233 instance  (Integral a)  => RealFrac (Ratio a)  where
234     properFraction (x:%y) = (fromInteger (toInteger q), r:%y)
235                           where (q,r) = quotRem x y
236
237 instance  (Integral a)  => Show (Ratio a)  where
238     showsPrec p (x:%y)  =  showParen (p > ratio_prec)
239                                (shows x . showString " % " . shows y)
240
241 ratio_prec :: Int
242 ratio_prec = 7
243
244 instance  (Integral a)  => Enum (Ratio a)  where
245     succ x              =  x + 1
246     pred x              =  x - 1
247
248     toEnum n            =  fromInt n :% 1
249     fromEnum            =  fromInteger . truncate
250
251     enumFrom            =  numericEnumFrom
252     enumFromThen        =  numericEnumFromThen
253     enumFromTo          =  numericEnumFromTo
254     enumFromThenTo      =  numericEnumFromThenTo
255 \end{code}
256
257
258 %*********************************************************
259 %*                                                      *
260 \subsection{Overloaded numeric functions}
261 %*                                                      *
262 %*********************************************************
263
264 \begin{code}
265 showSigned :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
266 showSigned showPos p x 
267    | x < 0     = showParen (p > 6) (showChar '-' . showPos (-x))
268    | otherwise = showPos x
269
270 even, odd       :: (Integral a) => a -> Bool
271 even n          =  n `rem` 2 == 0
272 odd             =  not . even
273
274 -------------------------------------------------------
275 {-# SPECIALISE (^) ::
276         Integer -> Integer -> Integer,
277         Integer -> Int -> Integer,
278         Int -> Int -> Int #-}
279 (^)             :: (Num a, Integral b) => a -> b -> a
280 _ ^ 0           =  1
281 x ^ n | n > 0   =  f x (n-1) x
282                    where f _ 0 y = y
283                          f a d y = g a d  where
284                                    g b i | even i  = g (b*b) (i `quot` 2)
285                                          | otherwise = f b (i-1) (b*y)
286 _ ^ _           = error "Prelude.^: negative exponent"
287
288 {- SPECIALISE (^^) ::
289         Rational -> Int -> Rational #-}
290 (^^)            :: (Fractional a, Integral b) => a -> b -> a
291 x ^^ n          =  if n >= 0 then x^n else recip (x^(negate n))
292
293
294 -------------------------------------------------------
295 gcd             :: (Integral a) => a -> a -> a
296 gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
297 gcd x y         =  gcd' (abs x) (abs y)
298                    where gcd' a 0  =  a
299                          gcd' a b  =  gcd' b (a `rem` b)
300
301 lcm             :: (Integral a) => a -> a -> a
302 {-# SPECIALISE lcm :: Int -> Int -> Int #-}
303 lcm _ 0         =  0
304 lcm 0 _         =  0
305 lcm x y         =  abs ((x `quot` (gcd x y)) * y)
306
307
308 {-# RULES
309 "Int.gcd"      forall a b . gcd  a b = gcdInt a b
310 "Integer.gcd"  forall a b . gcd  a b = gcdInteger  a b
311 "Integer.lcm"  forall a b . lcm  a b = lcmInteger  a b
312  #-}
313 \end{code}