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