haskell2010-1.1.2.0: Compatibility with Haskell 2010

Safe HaskellSafe
LanguageHaskell2010

Data.Complex

Contents

Synopsis

Rectangular form

data Complex a :: * -> * Source

Complex numbers are an algebraic type.

For a complex number z, abs z is a number with the magnitude of z, but oriented in the positive real direction, whereas signum z has the phase of z, but unit magnitude.

Constructors

!a :+ !a infix 6

forms a complex number from its real and imaginary rectangular components.

Instances

Eq a => Eq (Complex a) 
RealFloat a => Floating (Complex a) 
RealFloat a => Fractional (Complex a) 
Data a => Data (Complex a) 
RealFloat a => Num (Complex a) 
Read a => Read (Complex a) 
Show a => Show (Complex a) 
Typeable (* -> *) Complex 

realPart :: RealFloat a => Complex a -> a Source

Extracts the real part of a complex number.

imagPart :: RealFloat a => Complex a -> a Source

Extracts the imaginary part of a complex number.

Polar form

mkPolar :: RealFloat a => a -> a -> Complex a Source

Form a complex number from polar components of magnitude and phase.

cis :: RealFloat a => a -> Complex a Source

cis t is a complex value with magnitude 1 and phase t (modulo 2*pi).

polar :: RealFloat a => Complex a -> (a, a) Source

The function polar takes a complex number and returns a (magnitude, phase) pair in canonical form: the magnitude is nonnegative, and the phase in the range (-pi, pi]; if the magnitude is zero, then so is the phase.

magnitude :: RealFloat a => Complex a -> a Source

The nonnegative magnitude of a complex number.

phase :: RealFloat a => Complex a -> a Source

The phase of a complex number, in the range (-pi, pi]. If the magnitude is zero, then so is the phase.

Conjugate

conjugate :: RealFloat a => Complex a -> Complex a Source

The conjugate of a complex number.

Specification

 module Data.Complex(Complex((:+)), realPart, imagPart, conjugate, mkPolar,

                     cis, polar, magnitude, phase)  where



 infix  6  :+



 data  (RealFloat a)     => Complex a = !a :+ !a  deriving (Eq,Read,Show)





 realPart, imagPart :: (RealFloat a) => Complex a -> a

 realPart (x:+y)        =  x

 imagPart (x:+y)        =  y



 conjugate      :: (RealFloat a) => Complex a -> Complex a

 conjugate (x:+y) =  x :+ (-y)



 mkPolar                :: (RealFloat a) => a -> a -> Complex a

 mkPolar r theta        =  r * cos theta :+ r * sin theta



 cis            :: (RealFloat a) => a -> Complex a

 cis theta      =  cos theta :+ sin theta



 polar          :: (RealFloat a) => Complex a -> (a,a)

 polar z                =  (magnitude z, phase z)



 magnitude :: (RealFloat a) => Complex a -> a

 magnitude (x:+y) =  scaleFloat k

                    (sqrt ((scaleFloat mk x)^2 + (scaleFloat mk y)^2))

                   where k  = max (exponent x) (exponent y)

                         mk = - k



 phase :: (RealFloat a) => Complex a -> a

 phase (0 :+ 0) = 0

 phase (x :+ y) = atan2 y x





 instance  (RealFloat a) => Num (Complex a)  where

     (x:+y) + (x':+y') =  (x+x') :+ (y+y')

     (x:+y) - (x':+y') =  (x-x') :+ (y-y')

     (x:+y) * (x':+y') =  (x*x'-y*y') :+ (x*y'+y*x')

     negate (x:+y)     =  negate x :+ negate y

     abs z             =  magnitude z :+ 0

     signum 0          =  0

     signum z@(x:+y)   =  x/r :+ y/r  where r = magnitude z

     fromInteger n     =  fromInteger n :+ 0



 instance  (RealFloat a) => Fractional (Complex a)  where

     (x:+y) / (x':+y') =  (x*x''+y*y'') / d :+ (y*x''-x*y'') / d

                          where x'' = scaleFloat k x'

                                y'' = scaleFloat k y'

                                k   = - max (exponent x') (exponent y')

                                d   = x'*x'' + y'*y''



     fromRational a    =  fromRational a :+ 0



 instance  (RealFloat a) => Floating (Complex a)       where

     pi             =  pi :+ 0

     exp (x:+y)     =  expx * cos y :+ expx * sin y

                       where expx = exp x

     log z          =  log (magnitude z) :+ phase z



     sqrt 0         =  0

     sqrt z@(x:+y)  =  u :+ (if y < 0 then -v else v)

                       where (u,v) = if x < 0 then (v',u') else (u',v')

                             v'    = abs y / (u'*2)

                             u'    = sqrt ((magnitude z + abs x) / 2)



     sin (x:+y)     =  sin x * cosh y :+ cos x * sinh y

     cos (x:+y)     =  cos x * cosh y :+ (- sin x * sinh y)

     tan (x:+y)     =  (sinx*coshy:+cosx*sinhy)/(cosx*coshy:+(-sinx*sinhy))

                       where sinx  = sin x

                             cosx  = cos x

                             sinhy = sinh y

                             coshy = cosh y



     sinh (x:+y)    =  cos y * sinh x :+ sin  y * cosh x

     cosh (x:+y)    =  cos y * cosh x :+ sin y * sinh x

     tanh (x:+y)    =  (cosy*sinhx:+siny*coshx)/(cosy*coshx:+siny*sinhx)

                       where siny  = sin y

                             cosy  = cos y

                             sinhx = sinh x

                             coshx = cosh x



     asin z@(x:+y)  =  y':+(-x')

                       where  (x':+y') = log (((-y):+x) + sqrt (1 - z*z))

     acos z@(x:+y)  =  y'':+(-x'')

                       where (x'':+y'') = log (z + ((-y'):+x'))

                             (x':+y')   = sqrt (1 - z*z)

     atan z@(x:+y)  =  y':+(-x')

                       where (x':+y') = log (((1-y):+x) / sqrt (1+z*z))



     asinh z        =  log (z + sqrt (1+z*z))

     acosh z        =  log (z + (z+1) * sqrt ((z-1)/(z+1)))

     atanh z        =  log ((1+z) / sqrt (1-z*z))