f2cef50dc264244ea8632b30e3239d4d0f932776
[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         ( Complex((:+))
17         
18         , realPart      -- :: (RealFloat a) => Complex a -> a
19         , imagPart      -- :: (RealFloat a) => Complex a -> a
20         , conjugate     -- :: (RealFloat a) => Complex a -> Complex a
21         , mkPolar       -- :: (RealFloat a) => a -> a -> Complex a
22         , cis           -- :: (RealFloat a) => a -> Complex a
23         , polar         -- :: (RealFloat a) => Complex a -> (a,a)
24         , magnitude     -- :: (RealFloat a) => Complex a -> a
25         , phase         -- :: (RealFloat a) => Complex a -> a
26         
27         -- Complex instances:
28         --
29         --  (RealFloat a) => Eq         (Complex a)
30         --  (RealFloat a) => Read       (Complex a)
31         --  (RealFloat a) => Show       (Complex a)
32         --  (RealFloat a) => Num        (Complex a)
33         --  (RealFloat a) => Fractional (Complex a)
34         --  (RealFloat a) => Floating   (Complex a)
35         -- 
36         -- Implementation checked wrt. Haskell 98 lib report, 1/99.
37
38         )  where
39
40 import Prelude
41
42 #ifndef __NHC__
43 import Data.Dynamic
44 #endif
45
46 #ifdef __HUGS__
47 import Hugs.Prelude(Num(fromInt), Fractional(fromDouble))
48 #endif
49
50 infix  6  :+
51
52 -- -----------------------------------------------------------------------------
53 -- The Complex type
54
55 data  (RealFloat a)     => Complex a = !a :+ !a  deriving (Eq, Read, Show)
56
57
58 -- -----------------------------------------------------------------------------
59 -- Functions over Complex
60
61 realPart, imagPart :: (RealFloat a) => Complex a -> a
62 realPart (x :+ _) =  x
63 imagPart (_ :+ y) =  y
64
65 {-# SPECIALISE conjugate :: Complex Double -> Complex Double #-}
66 conjugate        :: (RealFloat a) => Complex a -> Complex a
67 conjugate (x:+y) =  x :+ (-y)
68
69 {-# SPECIALISE mkPolar :: Double -> Double -> Complex Double #-}
70 mkPolar          :: (RealFloat a) => a -> a -> Complex a
71 mkPolar r theta  =  r * cos theta :+ r * sin theta
72
73 {-# SPECIALISE cis :: Double -> Complex Double #-}
74 cis              :: (RealFloat a) => a -> Complex a
75 cis theta        =  cos theta :+ sin theta
76
77 {-# SPECIALISE polar :: Complex Double -> (Double,Double) #-}
78 polar            :: (RealFloat a) => Complex a -> (a,a)
79 polar z          =  (magnitude z, phase z)
80
81 {-# SPECIALISE magnitude :: Complex Double -> Double #-}
82 magnitude :: (RealFloat a) => Complex a -> a
83 magnitude (x:+y) =  scaleFloat k
84                      (sqrt ((scaleFloat mk x)^(2::Int) + (scaleFloat mk y)^(2::Int)))
85                     where k  = max (exponent x) (exponent y)
86                           mk = - k
87
88 {-# SPECIALISE phase :: Complex Double -> Double #-}
89 phase :: (RealFloat a) => Complex a -> a
90 phase (0 :+ 0)   = 0            -- SLPJ July 97 from John Peterson
91 phase (x:+y)     = atan2 y x
92
93
94 -- -----------------------------------------------------------------------------
95 -- Instances of Complex
96
97 #ifndef __NHC__
98 #include "Typeable.h"
99 INSTANCE_TYPEABLE1(Complex,complexTc,"Complex")
100 #endif
101
102 instance  (RealFloat a) => Num (Complex a)  where
103     {-# SPECIALISE instance Num (Complex Float) #-}
104     {-# SPECIALISE instance Num (Complex Double) #-}
105     (x:+y) + (x':+y')   =  (x+x') :+ (y+y')
106     (x:+y) - (x':+y')   =  (x-x') :+ (y-y')
107     (x:+y) * (x':+y')   =  (x*x'-y*y') :+ (x*y'+y*x')
108     negate (x:+y)       =  negate x :+ negate y
109     abs z               =  magnitude z :+ 0
110     signum 0            =  0
111     signum z@(x:+y)     =  x/r :+ y/r  where r = magnitude z
112     fromInteger n       =  fromInteger n :+ 0
113 #ifdef __HUGS__
114     fromInt n           =  fromInt n :+ 0
115 #endif
116
117 instance  (RealFloat a) => Fractional (Complex a)  where
118     {-# SPECIALISE instance Fractional (Complex Float) #-}
119     {-# SPECIALISE instance Fractional (Complex Double) #-}
120     (x:+y) / (x':+y')   =  (x*x''+y*y'') / d :+ (y*x''-x*y'') / d
121                            where x'' = scaleFloat k x'
122                                  y'' = scaleFloat k y'
123                                  k   = - max (exponent x') (exponent y')
124                                  d   = x'*x'' + y'*y''
125
126     fromRational a      =  fromRational a :+ 0
127 #ifdef __HUGS__
128     fromDouble a        =  fromDouble a :+ 0
129 #endif
130
131 instance  (RealFloat a) => Floating (Complex a) where
132     {-# SPECIALISE instance Floating (Complex Float) #-}
133     {-# SPECIALISE instance Floating (Complex Double) #-}
134     pi             =  pi :+ 0
135     exp (x:+y)     =  expx * cos y :+ expx * sin y
136                       where expx = exp x
137     log z          =  log (magnitude z) :+ phase z
138
139     sqrt 0         =  0
140     sqrt z@(x:+y)  =  u :+ (if y < 0 then -v else v)
141                       where (u,v) = if x < 0 then (v',u') else (u',v')
142                             v'    = abs y / (u'*2)
143                             u'    = sqrt ((magnitude z + abs x) / 2)
144
145     sin (x:+y)     =  sin x * cosh y :+ cos x * sinh y
146     cos (x:+y)     =  cos x * cosh y :+ (- sin x * sinh y)
147     tan (x:+y)     =  (sinx*coshy:+cosx*sinhy)/(cosx*coshy:+(-sinx*sinhy))
148                       where sinx  = sin x
149                             cosx  = cos x
150                             sinhy = sinh y
151                             coshy = cosh y
152
153     sinh (x:+y)    =  cos y * sinh x :+ sin  y * cosh x
154     cosh (x:+y)    =  cos y * cosh x :+ sin y * sinh x
155     tanh (x:+y)    =  (cosy*sinhx:+siny*coshx)/(cosy*coshx:+siny*sinhx)
156                       where siny  = sin y
157                             cosy  = cos y
158                             sinhx = sinh x
159                             coshx = cosh x
160
161     asin z@(x:+y)  =  y':+(-x')
162                       where  (x':+y') = log (((-y):+x) + sqrt (1 - z*z))
163     acos z         =  y'':+(-x'')
164                       where (x'':+y'') = log (z + ((-y'):+x'))
165                             (x':+y')   = sqrt (1 - z*z)
166     atan z@(x:+y)  =  y':+(-x')
167                       where (x':+y') = log (((1-y):+x) / sqrt (1+z*z))
168
169     asinh z        =  log (z + sqrt (1+z*z))
170     acosh z        =  log (z + (z+1) * sqrt ((z-1)/(z+1)))
171     atanh z        =  log ((1+z) / sqrt (1-z*z))