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