1 -----------------------------------------------------------------------------
3 -- Module : Data.Complex
4 -- Copyright : (c) The University of Glasgow 2001
5 -- License : BSD-style (see the file libraries/base/LICENSE)
7 -- Maintainer : libraries@haskell.org
8 -- Stability : provisional
9 -- Portability : portable
13 -----------------------------------------------------------------------------
20 , realPart -- :: (RealFloat a) => Complex a -> a
21 , imagPart -- :: (RealFloat a) => Complex a -> a
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
29 , conjugate -- :: (RealFloat a) => Complex a -> Complex a
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)
40 -- Implementation checked wrt. Haskell 98 lib report, 1/99.
49 import Hugs
.Prelude
(Num
(fromInt
), Fractional
(fromDouble
))
54 -- -----------------------------------------------------------------------------
57 -- | Complex numbers are an algebraic type.
59 -- For a complex number @z@, @'abs' z@ is a number with the magnitude of @z@,
60 -- but oriented in the positive real direction, whereas @'signum' z@
61 -- has the phase of @z@, but unit magnitude.
62 data (RealFloat a
) => Complex a
63 = !a
:+ !a
-- ^ forms a complex number from its real and imaginary
64 -- rectangular components.
65 deriving (Eq
, Read, Show)
67 -- -----------------------------------------------------------------------------
68 -- Functions over Complex
70 -- | Extracts the real part of a complex number.
71 realPart :: (RealFloat a
) => Complex a
-> a
74 -- | Extracts the imaginary part of a complex number.
75 imagPart :: (RealFloat a
) => Complex a
-> a
78 -- | The conjugate of a complex number.
79 {-# SPECIALISE conjugate :: Complex Double -> Complex Double #-}
80 conjugate :: (RealFloat a
) => Complex a
-> Complex a
81 conjugate (x
:+y
) = x
:+ (-y
)
83 -- | Form a complex number from polar components of magnitude and phase.
84 {-# SPECIALISE mkPolar :: Double -> Double -> Complex Double #-}
85 mkPolar :: (RealFloat a
) => a
-> a
-> Complex a
86 mkPolar r theta
= r
* cos theta
:+ r
* sin theta
88 -- | @'cis' t@ is a complex value with magnitude @1@
89 -- and phase @t@ (modulo @2*'pi'@).
90 {-# SPECIALISE cis :: Double -> Complex Double #-}
91 cis :: (RealFloat a
) => a
-> Complex a
92 cis theta
= cos theta
:+ sin theta
94 -- | The function 'polar' takes a complex number and
95 -- returns a (magnitude, phase) pair in canonical form:
96 -- the magnitude is nonnegative, and the phase in the range @(-'pi', 'pi']@;
97 -- if the magnitude is zero, then so is the phase.
98 {-# SPECIALISE polar :: Complex Double -> (Double,Double) #-}
99 polar :: (RealFloat a
) => Complex a
-> (a
,a
)
100 polar z
= (magnitude z
, phase z
)
102 -- | The nonnegative magnitude of a complex number.
103 {-# SPECIALISE magnitude :: Complex Double -> Double #-}
104 magnitude :: (RealFloat a
) => Complex a
-> a
105 magnitude (x
:+y
) = scaleFloat k
106 (sqrt ((scaleFloat mk x
)^
(2::Int) + (scaleFloat mk y
)^
(2::Int)))
107 where k
= max (exponent x
) (exponent y
)
110 -- | The phase of a complex number, in the range @(-'pi', 'pi']@.
111 -- If the magnitude is zero, then so is the phase.
112 {-# SPECIALISE phase :: Complex Double -> Double #-}
113 phase :: (RealFloat a
) => Complex a
-> a
114 phase (0 :+ 0) = 0 -- SLPJ July 97 from John Peterson
115 phase (x
:+y
) = atan2 y x
118 -- -----------------------------------------------------------------------------
119 -- Instances of Complex
121 #include
"Typeable.h"
122 INSTANCE_TYPEABLE1
(Complex,complexTc
,"Complex")
124 instance (RealFloat a
) => Num
(Complex a
) where
125 {-# SPECIALISE instance Num (Complex Float) #-}
126 {-# SPECIALISE instance Num (Complex Double) #-}
127 (x
:+y
) + (x
':+y
') = (x
+x
') :+ (y
+y
')
128 (x
:+y
) - (x
':+y
') = (x
-x
') :+ (y
-y
')
129 (x
:+y
) * (x
':+y
') = (x
*x
'-y
*y
') :+ (x
*y
'+y
*x
')
130 negate (x
:+y
) = negate x
:+ negate y
131 abs z
= magnitude z
:+ 0
133 signum z
@(x
:+y
) = x
/r
:+ y
/r
where r
= magnitude z
134 fromInteger n
= fromInteger n
:+ 0
136 fromInt n
= fromInt n
:+ 0
139 instance (RealFloat a
) => Fractional
(Complex a
) where
140 {-# SPECIALISE instance Fractional (Complex Float) #-}
141 {-# SPECIALISE instance Fractional (Complex Double) #-}
142 (x
:+y
) / (x
':+y
') = (x
*x
''+y
*y
'') / d
:+ (y
*x
''-x
*y
'') / d
143 where x
'' = scaleFloat k x
'
144 y
'' = scaleFloat k y
'
145 k
= - max (exponent x
') (exponent y
')
148 fromRational a
= fromRational a
:+ 0
150 fromDouble a
= fromDouble a
:+ 0
153 instance (RealFloat a
) => Floating
(Complex a
) where
154 {-# SPECIALISE instance Floating (Complex Float) #-}
155 {-# SPECIALISE instance Floating (Complex Double) #-}
157 exp (x
:+y
) = expx
* cos y
:+ expx
* sin y
159 log z
= log (magnitude z
) :+ phase z
162 sqrt z
@(x
:+y
) = u
:+ (if y
< 0 then -v
else v
)
163 where (u
,v
) = if x
< 0 then (v
',u
') else (u
',v
')
165 u
' = sqrt ((magnitude z
+ abs x
) / 2)
167 sin (x
:+y
) = sin x
* cosh y
:+ cos x
* sinh y
168 cos (x
:+y
) = cos x
* cosh y
:+ (- sin x
* sinh y
)
169 tan (x
:+y
) = (sinx
*coshy
:+cosx
*sinhy
)/(cosx
*coshy
:+(-sinx
*sinhy
))
175 sinh (x
:+y
) = cos y
* sinh x
:+ sin y
* cosh x
176 cosh (x
:+y
) = cos y
* cosh x
:+ sin y
* sinh x
177 tanh (x
:+y
) = (cosy
*sinhx
:+siny
*coshx
)/(cosy
*coshx
:+siny
*sinhx
)
183 asin z
@(x
:+y
) = y
':+(-x
')
184 where (x
':+y
') = log (((-y
):+x
) + sqrt (1 - z
*z
))
186 where (x
'':+y
'') = log (z
+ ((-y
'):+x
'))
187 (x
':+y
') = sqrt (1 - z
*z
)
188 atan z
@(x
:+y
) = y
':+(-x
')
189 where (x
':+y
') = log (((1-y
):+x
) / sqrt (1+z
*z
))
191 asinh z
= log (z
+ sqrt (1+z
*z
))
192 acosh z
= log (z
+ (z
+1) * sqrt ((z
-1)/(z
+1)))
193 atanh z
= log ((1+z
) / sqrt (1-z
*z
))