#ifdef around non-portable Data.Generics.Basics
[ghc-base.git] / Data / Complex.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Complex
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  provisional
9 -- Portability :  portable
10 --
11 -- Complex numbers.
12 --
13 -----------------------------------------------------------------------------
14
15 module Data.Complex
16         (
17         -- * Rectangular form
18           Complex((:+))
19
20         , realPart      -- :: (RealFloat a) => Complex a -> a
21         , imagPart      -- :: (RealFloat a) => Complex a -> a
22         -- * Polar form
23         , mkPolar       -- :: (RealFloat a) => a -> a -> Complex a
24         , cis           -- :: (RealFloat a) => a -> Complex a
25         , polar         -- :: (RealFloat a) => Complex a -> (a,a)
26         , magnitude     -- :: (RealFloat a) => Complex a -> a
27         , phase         -- :: (RealFloat a) => Complex a -> a
28         -- * Conjugate
29         , conjugate     -- :: (RealFloat a) => Complex a -> Complex a
30
31         -- Complex instances:
32         --
33         --  (RealFloat a) => Eq         (Complex a)
34         --  (RealFloat a) => Read       (Complex a)
35         --  (RealFloat a) => Show       (Complex a)
36         --  (RealFloat a) => Num        (Complex a)
37         --  (RealFloat a) => Fractional (Complex a)
38         --  (RealFloat a) => Floating   (Complex a)
39         -- 
40         -- Implementation checked wrt. Haskell 98 lib report, 1/99.
41
42         )  where
43
44 import Prelude
45
46 import Data.Typeable
47 #ifndef __NHC__
48 import Data.Generics.Basics( Data )
49 #endif
50
51 #ifdef __HUGS__
52 import Hugs.Prelude(Num(fromInt), Fractional(fromDouble))
53 #endif
54
55 infix  6  :+
56
57 -- -----------------------------------------------------------------------------
58 -- The Complex type
59
60 -- | Complex numbers are an algebraic type.
61 --
62 -- For a complex number @z@, @'abs' z@ is a number with the magnitude of @z@,
63 -- but oriented in the positive real direction, whereas @'signum' z@
64 -- has the phase of @z@, but unit magnitude.
65 data (RealFloat a) => Complex a
66   = !a :+ !a    -- ^ forms a complex number from its real and imaginary
67                 -- rectangular components.
68 # if __GLASGOW_HASKELL__
69         deriving (Eq, Show, Read, Data)
70 # else
71         deriving (Eq, Show, Read)
72 # endif
73
74 -- -----------------------------------------------------------------------------
75 -- Functions over Complex
76
77 -- | Extracts the real part of a complex number.
78 realPart :: (RealFloat a) => Complex a -> a
79 realPart (x :+ _) =  x
80
81 -- | Extracts the imaginary part of a complex number.
82 imagPart :: (RealFloat a) => Complex a -> a
83 imagPart (_ :+ y) =  y
84
85 -- | The conjugate of a complex number.
86 {-# SPECIALISE conjugate :: Complex Double -> Complex Double #-}
87 conjugate        :: (RealFloat a) => Complex a -> Complex a
88 conjugate (x:+y) =  x :+ (-y)
89
90 -- | Form a complex number from polar components of magnitude and phase.
91 {-# SPECIALISE mkPolar :: Double -> Double -> Complex Double #-}
92 mkPolar          :: (RealFloat a) => a -> a -> Complex a
93 mkPolar r theta  =  r * cos theta :+ r * sin theta
94
95 -- | @'cis' t@ is a complex value with magnitude @1@
96 -- and phase @t@ (modulo @2*'pi'@).
97 {-# SPECIALISE cis :: Double -> Complex Double #-}
98 cis              :: (RealFloat a) => a -> Complex a
99 cis theta        =  cos theta :+ sin theta
100
101 -- | The function 'polar' takes a complex number and
102 -- returns a (magnitude, phase) pair in canonical form:
103 -- the magnitude is nonnegative, and the phase in the range @(-'pi', 'pi']@;
104 -- if the magnitude is zero, then so is the phase.
105 {-# SPECIALISE polar :: Complex Double -> (Double,Double) #-}
106 polar            :: (RealFloat a) => Complex a -> (a,a)
107 polar z          =  (magnitude z, phase z)
108
109 -- | The nonnegative magnitude of a complex number.
110 {-# SPECIALISE magnitude :: Complex Double -> Double #-}
111 magnitude :: (RealFloat a) => Complex a -> a
112 magnitude (x:+y) =  scaleFloat k
113                      (sqrt ((scaleFloat mk x)^(2::Int) + (scaleFloat mk y)^(2::Int)))
114                     where k  = max (exponent x) (exponent y)
115                           mk = - k
116
117 -- | The phase of a complex number, in the range @(-'pi', 'pi']@.
118 -- If the magnitude is zero, then so is the phase.
119 {-# SPECIALISE phase :: Complex Double -> Double #-}
120 phase :: (RealFloat a) => Complex a -> a
121 phase (0 :+ 0)   = 0            -- SLPJ July 97 from John Peterson
122 phase (x:+y)     = atan2 y x
123
124
125 -- -----------------------------------------------------------------------------
126 -- Instances of Complex
127
128 #include "Typeable.h"
129 INSTANCE_TYPEABLE1(Complex,complexTc,"Complex")
130
131 instance  (RealFloat a) => Num (Complex a)  where
132     {-# SPECIALISE instance Num (Complex Float) #-}
133     {-# SPECIALISE instance Num (Complex Double) #-}
134     (x:+y) + (x':+y')   =  (x+x') :+ (y+y')
135     (x:+y) - (x':+y')   =  (x-x') :+ (y-y')
136     (x:+y) * (x':+y')   =  (x*x'-y*y') :+ (x*y'+y*x')
137     negate (x:+y)       =  negate x :+ negate y
138     abs z               =  magnitude z :+ 0
139     signum 0            =  0
140     signum z@(x:+y)     =  x/r :+ y/r  where r = magnitude z
141     fromInteger n       =  fromInteger n :+ 0
142 #ifdef __HUGS__
143     fromInt n           =  fromInt n :+ 0
144 #endif
145
146 instance  (RealFloat a) => Fractional (Complex a)  where
147     {-# SPECIALISE instance Fractional (Complex Float) #-}
148     {-# SPECIALISE instance Fractional (Complex Double) #-}
149     (x:+y) / (x':+y')   =  (x*x''+y*y'') / d :+ (y*x''-x*y'') / d
150                            where x'' = scaleFloat k x'
151                                  y'' = scaleFloat k y'
152                                  k   = - max (exponent x') (exponent y')
153                                  d   = x'*x'' + y'*y''
154
155     fromRational a      =  fromRational a :+ 0
156 #ifdef __HUGS__
157     fromDouble a        =  fromDouble a :+ 0
158 #endif
159
160 instance  (RealFloat a) => Floating (Complex a) where
161     {-# SPECIALISE instance Floating (Complex Float) #-}
162     {-# SPECIALISE instance Floating (Complex Double) #-}
163     pi             =  pi :+ 0
164     exp (x:+y)     =  expx * cos y :+ expx * sin y
165                       where expx = exp x
166     log z          =  log (magnitude z) :+ phase z
167
168     sqrt 0         =  0
169     sqrt z@(x:+y)  =  u :+ (if y < 0 then -v else v)
170                       where (u,v) = if x < 0 then (v',u') else (u',v')
171                             v'    = abs y / (u'*2)
172                             u'    = sqrt ((magnitude z + abs x) / 2)
173
174     sin (x:+y)     =  sin x * cosh y :+ cos x * sinh y
175     cos (x:+y)     =  cos x * cosh y :+ (- sin x * sinh y)
176     tan (x:+y)     =  (sinx*coshy:+cosx*sinhy)/(cosx*coshy:+(-sinx*sinhy))
177                       where sinx  = sin x
178                             cosx  = cos x
179                             sinhy = sinh y
180                             coshy = cosh y
181
182     sinh (x:+y)    =  cos y * sinh x :+ sin  y * cosh x
183     cosh (x:+y)    =  cos y * cosh x :+ sin y * sinh x
184     tanh (x:+y)    =  (cosy*sinhx:+siny*coshx)/(cosy*coshx:+siny*sinhx)
185                       where siny  = sin y
186                             cosy  = cos y
187                             sinhx = sinh x
188                             coshx = cosh x
189
190     asin z@(x:+y)  =  y':+(-x')
191                       where  (x':+y') = log (((-y):+x) + sqrt (1 - z*z))
192     acos z         =  y'':+(-x'')
193                       where (x'':+y'') = log (z + ((-y'):+x'))
194                             (x':+y')   = sqrt (1 - z*z)
195     atan z@(x:+y)  =  y':+(-x')
196                       where (x':+y') = log (((1-y):+x) / sqrt (1+z*z))
197
198     asinh z        =  log (z + sqrt (1+z*z))
199     acosh z        =  log (z + (z+1) * sqrt ((z-1)/(z+1)))
200     atanh z        =  log ((1+z) / sqrt (1-z*z))