add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Data / Ratio.hs
1 {-# LANGUAGE CPP #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.Ratio
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  stable
11 -- Portability :  portable
12 --
13 -- Standard functions on rational numbers
14 --
15 -----------------------------------------------------------------------------
16
17 module Data.Ratio
18     ( Ratio
19     , Rational
20     , (%)               -- :: (Integral a) => a -> a -> Ratio a
21     , numerator         -- :: (Integral a) => Ratio a -> a
22     , denominator       -- :: (Integral a) => Ratio a -> a
23     , approxRational    -- :: (RealFrac a) => a -> a -> Rational
24
25     -- Ratio instances: 
26     --   (Integral a) => Eq   (Ratio a)
27     --   (Integral a) => Ord  (Ratio a)
28     --   (Integral a) => Num  (Ratio a)
29     --   (Integral a) => Real (Ratio a)
30     --   (Integral a) => Fractional (Ratio a)
31     --   (Integral a) => RealFrac (Ratio a)
32     --   (Integral a) => Enum     (Ratio a)
33     --   (Read a, Integral a) => Read (Ratio a)
34     --   (Integral a) => Show     (Ratio a)
35
36   ) where
37
38 import Prelude
39
40 #ifdef __GLASGOW_HASKELL__
41 import GHC.Real         -- The basic defns for Ratio
42 #endif
43
44 #ifdef __HUGS__
45 import Hugs.Prelude(Ratio(..), (%), numerator, denominator)
46 #endif
47
48 #ifdef __NHC__
49 import Ratio (Ratio(..), (%), numerator, denominator, approxRational)
50 #else
51
52 -- -----------------------------------------------------------------------------
53 -- approxRational
54
55 -- | 'approxRational', applied to two real fractional numbers @x@ and @epsilon@,
56 -- returns the simplest rational number within @epsilon@ of @x@.
57 -- A rational number @y@ is said to be /simpler/ than another @y'@ if
58 --
59 -- * @'abs' ('numerator' y) <= 'abs' ('numerator' y')@, and
60 --
61 -- * @'denominator' y <= 'denominator' y'@.
62 --
63 -- Any real interval contains a unique simplest rational;
64 -- in particular, note that @0\/1@ is the simplest rational of all.
65
66 -- Implementation details: Here, for simplicity, we assume a closed rational
67 -- interval.  If such an interval includes at least one whole number, then
68 -- the simplest rational is the absolutely least whole number.  Otherwise,
69 -- the bounds are of the form q%1 + r%d and q%1 + r'%d', where abs r < d
70 -- and abs r' < d', and the simplest rational is q%1 + the reciprocal of
71 -- the simplest rational between d'%r' and d%r.
72
73 approxRational          :: (RealFrac a) => a -> a -> Rational
74 approxRational rat eps  =  simplest (rat-eps) (rat+eps)
75         where simplest x y | y < x      =  simplest y x
76                            | x == y     =  xr
77                            | x > 0      =  simplest' n d n' d'
78                            | y < 0      =  - simplest' (-n') d' (-n) d
79                            | otherwise  =  0 :% 1
80                                         where xr  = toRational x
81                                               n   = numerator xr
82                                               d   = denominator xr
83                                               nd' = toRational y
84                                               n'  = numerator nd'
85                                               d'  = denominator nd'
86
87               simplest' n d n' d'       -- assumes 0 < n%d < n'%d'
88                         | r == 0     =  q :% 1
89                         | q /= q'    =  (q+1) :% 1
90                         | otherwise  =  (q*n''+d'') :% n''
91                                      where (q,r)      =  quotRem n d
92                                            (q',r')    =  quotRem n' d'
93                                            nd''       =  simplest' d' r' d r
94                                            n''        =  numerator nd''
95                                            d''        =  denominator nd''
96 #endif