Complex.st
author claus
Sat, 18 Feb 1995 00:50:51 +0100
changeset 265 f014922e3b71
child 1944 9fb0b642d2ca
permissions -rw-r--r--
Initial revision

'From Smalltalk-80, Version 2.4 of 28 January 1989 on 14 May 1989 at 2:48:01 pm'!

ArithmeticValue subclass: #Complex
        instanceVariableNames: 'real imaginary '
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Magnitude-Numbers'
!

Complex comment:
'This is an implementation of complex numbers.  A complex number has real and
 imaginary parts which must be manipulated simultaneously in any numeric processing.
  Complex numbers can be used in many of the same places that regular numbers
 can be used with one major exception of comparisons, since complex numbers cannot
 be directly compared for size (except through lengths of vectors (see absolute
 value)).

Instance variables:
    real        <Number> the part of the number which can be expressed as a Real number
    imaginary   <Number> the part of the number which, in terms of how the number behaves,
                         has been multiplied by ''i'' (-1 sqrt)

Author: Kurt Hebel (hebel@uinova.cerl.uiuc.edu)'
!

!Complex methodsFor: 'accessing'!

imaginary
        "Return the imaginary part of the complex number."
        ^ imaginary
!

real
        "Return the real part of the complex number."
        ^ real
! !

!Complex methodsFor: 'arithmetic'!

* aNumber 
        "Return the product of the receiver and the argument."

        | u v |

        aNumber isComplex ifTrue:[
            u := aNumber real.
            v := aNumber imaginary.
            ^Complex real: real * u - (imaginary * v)
                     imaginary: real * v + (imaginary * u)
        ].
        ^self retry: #* coercing: aNumber
!

+ aNumber 
        "Return the sum of the receiver and the argument."

        aNumber isComplex ifTrue: [
            ^Complex real: aNumber real + real
                     imaginary: aNumber imaginary + imaginary
        ].
        ^self retry: #+ coercing: aNumber
!

- aNumber
        "Return the difference of the receiver and the argument."

        aNumber isComplex ifTrue: [
            ^Complex real: real - aNumber real
                     imaginary: imaginary - aNumber imaginary
        ].
        ^self retry: #- coercing: aNumber
!

/ aNumber 
        "Return the quotient of the receiver and the argument."

        | denom u v |

        aNumber isComplex ifTrue:[ 
            u := aNumber real.
            v := aNumber imaginary.
            denom := u * u + (v * v).
            ^Complex real: u * real + (v * imaginary) / denom
                     imaginary: u * imaginary - (v * real) / denom
        ].
        ^self retry: #/ coercing: aNumber
!

abs
        "Return the magnitude (or absolute value) of the complex number."

        ^ (real * real + (imaginary * imaginary)) sqrt
!

conjugated
        "Return the complex conjugate of this complex number."

        ^ Complex real: real imaginary: imaginary negated
! !

!Complex methodsFor: 'double dispatching'!

differenceFromFloat: argument
        ^ argument asComplex - self
!

differenceFromFraction: argument
        ^ argument asComplex - self
!

differenceFromInteger: argument
        ^ argument asComplex - self
!

productFromFloat: argument
        ^ argument asComplex * self
!

productFromFraction: argument
        ^ argument asComplex * self
!

productFromInteger: argument
        ^ argument asComplex * self
!

quotientFromFloat: argument
        ^ argument asComplex / self
!

quotientFromFraction: argument
        ^ argument asComplex / self
!

quotientFromInteger: argument
        ^ argument asComplex / self
!

sumFromFloat: argument
        ^ argument asComplex + self
!

sumFromFraction: argument
        ^ argument asComplex + self
!

sumFromInteger: argument
        ^ argument asComplex + self
! !

!Complex methodsFor: 'mathematical functions'!

angle
        "Return the radian angle for this Complex number."

        real < 0 ifTrue: [
            imaginary < 0 ifTrue: [
                ^ (imaginary / real) arcTan - Float pi
            ].
            ^ Float pi + (imaginary / real) arcTan
        ].
        ^ (imaginary / real) arcTan
!

exp
        "Return the complex exponential of the receiver."

        ^ imaginary cos % imaginary sin * real exp
!

sqrt
        "Return the square root of the receiver"

        | u v |
        (imaginary = 0 and: [real >= 0]) ifTrue: [^real sqrt].
        v := (self abs - real / 2) sqrt.
        u := imaginary / 2 / v.
        ^Complex real: u imaginary: v

        "-4 asComplex sqrt"
        "-4 asComplex sqrt squared"
! !

!Complex methodsFor: 'comparing'!

= aNumber
        ^ (aNumber real = real) and:[aNumber imaginary = imaginary]
!

< aNumber
        ^Number
                raise: #unorderedSignal
                receiver: self
                selector: #<
                arg: aNumber
                errorString: 'Complex numbers are not well ordered'!

hash
        "Hash is implemented because equals is implemented."

        ^ real hash
! !

!Complex methodsFor: 'testing'!

isComplex

        ^true
!

isReal
        "Return true if this Complex number has a zero imaginary part."
        ^ imaginary = 0
!

isZero
        "Answer whether 'self = self class zero'.  We can't use #= because
        #= is defined in terms of #isZero"

        ^real isZero and: [imaginary isZero]
!

sign

        ^Complex real: real sign imaginary: imaginary sign
! !

!Complex methodsFor: 'coercing'!

coerce: aNumber

        ^aNumber asComplex
!

generality

        ^150
! !

!Complex methodsFor: 'converting'!

asComplex

        ^self
!

asFloat

        imaginary = 0 ifTrue: [^real asFloat].
        ^Number
                raise: #coercionErrorSignal
                receiver: self
                selector: #asFloat
                errorString: 'Can''t coerce an instance of Complex to a Float'
!

asInteger

        imaginary = 0 ifTrue: [^real asInteger].
        ^Number
                raise: #coercionErrorSignal
                receiver: self
                selector: #asInteger
                errorString: 'Can''t coerce an instance of Complex to an Integer'
!

asPoint
        "Return the complex number as a point."
        ^ real @ imaginary
!

reduceGeneralityIfPossible
        "Answer the receiver transformed to a lower generality, if such a 
        transformation is possible without losing information. If not, answer 
        the receiver"

        imaginary isZero
                ifTrue: [^real]
                ifFalse: [^self]
! !

!Complex methodsFor: 'printing'!

printString
        ^ '(' , real printString, '%', imaginary printString, ')'
!

printOn: aStream
        aStream nextPut: $(.
        real storeOn: aStream.
        aStream nextPutAll: '%'.
        imaginary storeOn: aStream.
        aStream nextPut: $).
!

storeOn: aStream
        aStream nextPut: $(.
        real storeOn: aStream.
        aStream nextPutAll: '%'.
        imaginary storeOn: aStream.
        aStream nextPut: $).
! !

!Complex methodsFor: 'private'!

setReal: u setImaginary: v
        real := u.
        imaginary := v.
! !


!Complex class methodsFor: 'instance creation'!

fromReal: aNumber
        "Create a new complex number from the given real number."
        ^ self basicNew setReal: aNumber setImaginary: 0
!

real: u imaginary: v
        "Create a new complex number with the given real and imaginary parts.  If the
         imaginary part is zero, return the real part of the number."
        ^v = 0 ifTrue: [u]
               ifFalse: [self basicNew setReal: u setImaginary: v]
! !

!Complex class methodsFor: 'exception handling'!

trapImaginary: aBlock
        "Complex trapImaginary: [-27 sqrt]"

        | send |

        ^Number domainErrorSignal handle: [ :ex |
            send := ex parameter.
            (send selector = #sqrt or: [send selector = #sqrtTruncated]) ifTrue: [
	        send receiver: send receiver asComplex.
                ex proceedWith: send value
	    ] ifFalse: [
		ex reject
	    ]
	] do: aBlock
! !

!Complex class methodsFor: 'constants access'!

unity
        "Answer the value which allows, for any given arithmetic value, the following to be true

         aNumber * aNumber class unity = aNumber

        This must be true regardless of how a given subclass chooses to define #*"

        ^self fromReal: 1
!

zero
        "Answer the value which allows, for any given arithmetic value, the following to be true

                aNumber + aNumber class zero = aNumber

        This must be true regardless of how a given subclass chooses to define #+"

        ^self fromReal: 0
! !

!ArithmeticValue methodsFor: 'testing'!

isComplex
        "Answer whether the receiver has an imaginary part"

        ^false
!

isReal
        ^ true
! !

!Number methodsFor: 'mathematical functions'!

conjugated
        "Return the complex conjugate of this Number."
        ^ self
!

imaginary
        "Return the imaginary part of this Number."
        ^ 0
!

real
        "Return the real part of this Number."
        ^ self
! !

!Number methodsFor: 'converting'!

% aNumber 
        "Answer a complex number with the receiver as the real part and 
        aNumber as the imaginary part"

        ^Complex real: self imaginary: aNumber
!

asComplex
        "Answer a complex number with the receiver as the real part and 
        zero as the imaginary part"

        ^Complex fromReal: self
! !

!Point methodsFor: 'converting'!

asComplex
        "Return a complex number whose real and imaginary components are the x and y
         coordinates of the receiver."
        ^ x % y
! !

" The above file is a Manchester Goodie.  It is distributed freely on condition
 that you observe these conditions in respect of the whole Goodie, and on
 any significant part of it which is separately transmitted or stored:
        * You must ensure that every copy includes this notice, and that
          source and author(s) of the material are acknowledged.
        * These conditions must be imposed on anyone who receives a copy.
        * The material shall not be used for commercial gain without the prior
          written consent of the author(s).

 For more information about the Manchester Goodies Library (from which 
 this file was distributed) send e-mail:
        To: goodies-lib@cs.man.ac.uk
        Subject: help 
"!