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