X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Data%2FComplex.hs;h=369250149267dddf662073c0b77fdedea3ef62b2;hb=8073392a94dc5ab198e4758d6738a0c7f5ed68cf;hp=e0738f10b425e4ae7f864caad90cd8a0adb2dfac;hpb=9fa9bc17072a58c0bae2cce4764d38677e96ac29;p=ghc-base.git diff --git a/Data/Complex.hs b/Data/Complex.hs index e0738f1..3692501 100644 --- a/Data/Complex.hs +++ b/Data/Complex.hs @@ -1,122 +1,169 @@ +{-# LANGUAGE CPP, DeriveDataTypeable #-} +#ifdef __GLASGOW_HASKELL__ +{-# LANGUAGE StandaloneDeriving #-} +#endif + ----------------------------------------------------------------------------- -- | -- Module : Data.Complex -- Copyright : (c) The University of Glasgow 2001 --- License : BSD-style (see the file libraries/core/LICENSE) +-- License : BSD-style (see the file libraries/base/LICENSE) -- -- Maintainer : libraries@haskell.org -- Stability : provisional -- Portability : portable -- --- $Id: Complex.hs,v 1.3 2002/04/24 16:31:39 simonmar Exp $ --- -- Complex numbers. -- ----------------------------------------------------------------------------- module Data.Complex - ( Complex((:+)) - - , realPart -- :: (RealFloat a) => Complex a -> a - , imagPart -- :: (RealFloat a) => Complex a -> a - , conjugate -- :: (RealFloat a) => Complex a -> Complex a - , mkPolar -- :: (RealFloat a) => a -> a -> Complex a - , cis -- :: (RealFloat a) => a -> Complex a - , polar -- :: (RealFloat a) => Complex a -> (a,a) - , magnitude -- :: (RealFloat a) => Complex a -> a - , phase -- :: (RealFloat a) => Complex a -> a - - -- Complex instances: - -- - -- (RealFloat a) => Eq (Complex a) - -- (RealFloat a) => Read (Complex a) - -- (RealFloat a) => Show (Complex a) - -- (RealFloat a) => Num (Complex a) - -- (RealFloat a) => Fractional (Complex a) - -- (RealFloat a) => Floating (Complex a) - -- + ( + -- * Rectangular form + Complex((:+)) + + , realPart -- :: (RealFloat a) => Complex a -> a + , imagPart -- :: (RealFloat a) => Complex a -> a + -- * Polar form + , mkPolar -- :: (RealFloat a) => a -> a -> Complex a + , cis -- :: (RealFloat a) => a -> Complex a + , polar -- :: (RealFloat a) => Complex a -> (a,a) + , magnitude -- :: (RealFloat a) => Complex a -> a + , phase -- :: (RealFloat a) => Complex a -> a + -- * Conjugate + , conjugate -- :: (RealFloat a) => Complex a -> Complex a + + -- Complex instances: + -- + -- (RealFloat a) => Eq (Complex a) + -- (RealFloat a) => Read (Complex a) + -- (RealFloat a) => Show (Complex a) + -- (RealFloat a) => Num (Complex a) + -- (RealFloat a) => Fractional (Complex a) + -- (RealFloat a) => Floating (Complex a) + -- -- Implementation checked wrt. Haskell 98 lib report, 1/99. ) where import Prelude -import Data.Dynamic +import Data.Typeable +#ifdef __GLASGOW_HASKELL__ +import Data.Data (Data) +#endif + +#ifdef __HUGS__ +import Hugs.Prelude(Num(fromInt), Fractional(fromDouble)) +#endif infix 6 :+ -- ----------------------------------------------------------------------------- -- The Complex type -data (RealFloat a) => Complex a = !a :+ !a deriving (Eq, Read, Show) - +-- | 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. +data Complex a + = !a :+ !a -- ^ forms a complex number from its real and imaginary + -- rectangular components. +# if __GLASGOW_HASKELL__ + deriving (Eq, Show, Read, Data) +# else + deriving (Eq, Show, Read) +# endif -- ----------------------------------------------------------------------------- -- Functions over Complex -realPart, imagPart :: (RealFloat a) => Complex a -> a +-- | Extracts the real part of a complex number. +realPart :: (RealFloat a) => Complex a -> a realPart (x :+ _) = x + +-- | Extracts the imaginary part of a complex number. +imagPart :: (RealFloat a) => Complex a -> a imagPart (_ :+ y) = y +-- | The conjugate of a complex number. {-# SPECIALISE conjugate :: Complex Double -> Complex Double #-} -conjugate :: (RealFloat a) => Complex a -> Complex a +conjugate :: (RealFloat a) => Complex a -> Complex a conjugate (x:+y) = x :+ (-y) +-- | Form a complex number from polar components of magnitude and phase. {-# SPECIALISE mkPolar :: Double -> Double -> Complex Double #-} -mkPolar :: (RealFloat a) => a -> a -> Complex a -mkPolar r theta = r * cos theta :+ r * sin theta +mkPolar :: (RealFloat a) => a -> a -> Complex a +mkPolar r theta = r * cos theta :+ r * sin theta +-- | @'cis' t@ is a complex value with magnitude @1@ +-- and phase @t@ (modulo @2*'pi'@). {-# SPECIALISE cis :: Double -> Complex Double #-} -cis :: (RealFloat a) => a -> Complex a -cis theta = cos theta :+ sin theta +cis :: (RealFloat a) => a -> Complex a +cis theta = cos theta :+ sin theta +-- | 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. {-# SPECIALISE polar :: Complex Double -> (Double,Double) #-} -polar :: (RealFloat a) => Complex a -> (a,a) -polar z = (magnitude z, phase z) +polar :: (RealFloat a) => Complex a -> (a,a) +polar z = (magnitude z, phase z) +-- | The nonnegative magnitude of a complex number. {-# SPECIALISE magnitude :: Complex Double -> Double #-} magnitude :: (RealFloat a) => Complex a -> a magnitude (x:+y) = scaleFloat k - (sqrt ((scaleFloat mk x)^(2::Int) + (scaleFloat mk y)^(2::Int))) - where k = max (exponent x) (exponent y) - mk = - k + (sqrt (sqr (scaleFloat mk x) + sqr (scaleFloat mk y))) + where k = max (exponent x) (exponent y) + mk = - k + sqr z = z * z +-- | The phase of a complex number, in the range @(-'pi', 'pi']@. +-- If the magnitude is zero, then so is the phase. {-# SPECIALISE phase :: Complex Double -> Double #-} phase :: (RealFloat a) => Complex a -> a -phase (0 :+ 0) = 0 -- SLPJ July 97 from John Peterson -phase (x:+y) = atan2 y x +phase (0 :+ 0) = 0 -- SLPJ July 97 from John Peterson +phase (x:+y) = atan2 y x -- ----------------------------------------------------------------------------- -- Instances of Complex -#include "Dynamic.h" +#include "Typeable.h" INSTANCE_TYPEABLE1(Complex,complexTc,"Complex") instance (RealFloat a) => Num (Complex a) where {-# SPECIALISE instance Num (Complex Float) #-} {-# SPECIALISE instance Num (Complex Double) #-} - (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 + (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) = 0 + signum z@(x:+y) = x/r :+ y/r where r = magnitude z + fromInteger n = fromInteger n :+ 0 +#ifdef __HUGS__ + fromInt n = fromInt n :+ 0 +#endif instance (RealFloat a) => Fractional (Complex a) where {-# SPECIALISE instance Fractional (Complex Float) #-} {-# SPECIALISE instance Fractional (Complex Double) #-} - (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 + (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 +#ifdef __HUGS__ + fromDouble a = fromDouble a :+ 0 +#endif + +instance (RealFloat a) => Floating (Complex a) where {-# SPECIALISE instance Floating (Complex Float) #-} {-# SPECIALISE instance Floating (Complex Double) #-} pi = pi :+ 0 @@ -124,7 +171,7 @@ instance (RealFloat a) => Floating (Complex a) where where expx = exp x log z = log (magnitude z) :+ phase z - sqrt 0 = 0 + sqrt (0:+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) @@ -156,4 +203,4 @@ instance (RealFloat a) => Floating (Complex a) where 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)) + atanh z = 0.5 * log ((1.0+z) / (1.0-z))