help-smalltalk
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[Help-smalltalk] [PATCH] Complex package


From: Paolo Bonzini
Subject: [Help-smalltalk] [PATCH] Complex package
Date: Sat, 21 Jul 2007 11:33:15 +0200
User-agent: Thunderbird 2.0.0.5 (Macintosh/20070716)

I noticed that GST does not have complex numbers. This adds them, as well as adding hyperbolic functions.

Paolo
2007-07-17  Paolo Bonzini  <address@hidden>

        * kernel/Number.st: Add hyperbolic functions.

        * packages/complex/Complex.st: New.
        * packages/complex/complextests.st: New.


--- orig/configure.ac
+++ mod/configure.ac
@@ -246,6 +246,7 @@ GST_PACKAGE([BloxTK], [blox/tk],
    [gst_cv_tcltk_libs],
    [Makefile], [blox-tk.la])
 GST_PACKAGE([Browser], [browser])
+GST_PACKAGE([Complex], [complex])
 GST_PACKAGE([Continuations], [continuations])
 GST_PACKAGE([DebugTools], [debug])
 GST_PACKAGE([DB], [db])


--- orig/kernel/Number.st
+++ mod/kernel/Number.st
@@ -345,9 +345,7 @@ retryDivisionCoercing: aNumber
     exception if aNumber is zero"
 
     aNumber = 0 ifTrue: [ self zeroDivide ].
-    ^self negative == aNumber negative
-       ifTrue: [ self rem: aNumber ]
-       ifFalse: [ (self rem: aNumber) + aNumber ]
+    ^self - ((self // aNumber) * aNumber)
 !
 
 quo: aNumber
@@ -586,12 +584,12 @@ arcTan: x
        ^self generality < x generality
            ifTrue: [
                x generality < 0.0e generality
-                   ifTrue: [ FloatD pi * self sign / -2 ]
-                   ifFalse: [ x class pi * self sign / -2 ]]
+                   ifTrue: [ FloatD pi * self sign / 2 ]
+                   ifFalse: [ x class pi * self sign / 2 ]]
            ifFalse: [
                self generality < 0.0e generality
-                   ifTrue: [ FloatD pi * self sign / -2 ]
-                   ifFalse: [ self class pi * self sign / -2 ]]].
+                   ifTrue: [ FloatD pi * self sign / 2 ]
+                   ifFalse: [ self class pi * self sign / 2 ]]].
 
     result := (self / x) arcTan.
     ^x < 0
@@ -602,6 +600,33 @@ arcTan: x
                ifTrue: [ result - result class pi ] ]
 !
 
+cosh
+    "Answer the hyperbolic cosine of the receiver."
+    ^(self exp + self negated exp) / 2!
+
+sinh
+    "Answer the hyperbolic sine of the receiver."
+    ^(self exp - self negated exp) / 2!
+
+tanh
+    "Answer the hyperbolic tangent of the receiver."
+    | ep en |
+    ep := self exp.
+    en := self negated exp.
+    ^(ep - en) / (ep + en)!
+
+arcCosh
+    "Answer the hyperbolic arc-cosine of the receiver."
+    ^(self + (self squared - 1) sqrt) ln!
+
+arcSinh
+    "Answer the hyperbolic arc-sine of the receiver."
+    ^(self + (self squared + 1) sqrt) ln!
+
+arcTanh
+    "Answer the hyperbolic arc-tangent of the receiver."
+    ^((1 + self) / (1 - self)) ln / 2!
+
 sqrt
     "Answer the square root of the receiver"
     ^self asFloatD sqrt



* added files

--- /dev/null   2007-07-18 00:40:21.000000000 +0300
+++ mod/packages/complex/Complex.st
@@ -0,0 +1,459 @@
+"======================================================================
+|
+|   Complex number declarations
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007 Free Software Foundation, Inc.
+| Written by Paolo Bonzini
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+Number subclass: #Complex
+       instanceVariableNames: 're im'
+       classVariableNames: 'Zero One I'
+       poolDictionaries: ''
+       category: 'Examples-Useful'!
+
+Complex comment: 'I provide complex numbers, with full interoperability
+with other kinds of numbers.  Complex numbers can be created from imaginary
+numbers, which in turn are created with `Complex i'' or the #i method
+(e.g. `3 i'').  Alternatively, they can be created from polar numbers.'!
+
+!Complex class methodsFor: 'instance creation'!
+
+initialize
+    "Initialize some common complex numbers."
+    Zero := Complex basicNew setReal: 0 imaginary: 0.
+    One := Complex basicNew setReal: 1 imaginary: 0.
+    I := Complex real: 0 imaginary: 1!
+
+i
+    "Return the imaginary unit, -1 sqrt."
+    ^I!
+
+new
+   self shouldNotImplement!
+
+rho: dist theta: angle
+    "Return a complex number whose absolute value is dist and whose
+     argument is angle."
+    ^Complex
+       realResult: dist * angle cos
+       imaginary: dist * angle sin!
+
+realResult: re imaginary: im
+    "Private - Return a new complex number knowing that re and im have the
+     same generality."
+    im = 0 ifTrue: [ ^re ].
+    ^self basicNew setReal: re imaginary: im!
+
+real: re imaginary: im
+    "Return a complex number with the given real and imaginary parts."
+    im = 0 ifTrue: [ ^re ].
+    re isComplex ifTrue: [ ^re + im i ].
+    im isComplex ifTrue: [ ^re + im i ].
+
+    re generality = im generality
+       ifTrue: [ ^self basicNew setReal: re imaginary: im ].
+
+    ^re generality < im generality
+       ifTrue: [ ^self basicNew setReal: (im coerce: re) imaginary: im ]
+       ifFalse: [ ^self basicNew setReal: re imaginary: (re coerce: im) ]! !
+
+!Complex methodsFor: 'math'!
+
++ z
+    "Sum the receiver with the (real or complex) number z."
+    ^Complex
+       realResult: self real + z real
+       imaginary: self imaginary + z imaginary!
+
+- z
+    "Subtract the (real or complex) number z from the receiver."
+    ^Complex
+       realResult: self real - z real
+       imaginary: self imaginary - z imaginary!
+
+* z
+    "Multiply the receiver by the (real or complex) number z."
+    z isComplex ifFalse: [
+       ^Complex
+           realResult: self real * z
+           imaginary: self imaginary * z ].
+    ^Complex
+       realResult: (self real * z real) - (self imaginary * z imaginary)
+       imaginary: (self real * z imaginary) + (self imaginary * z real)!
+
+/ z
+    "Divide the receiver by the (real or complex) number z."
+    z isComplex ifFalse: [
+       ^Complex
+           realResult: self real / z
+           imaginary: self imaginary / z ].
+    ^self * z reciprocal!
+
+reciprocal
+    "Return the reciprocal of the receiver."
+    | absSquared |
+    absSquared := self absSquared.
+    ^Complex
+       realResult: self real / absSquared
+       imaginary: self imaginary negated / absSquared!
+
+abs
+    "Return the absolute value of the receiver."
+    ^(self real squared + self imaginary squared) sqrt!
+
+absSquared
+    "Return the squared absolute value of the receiver."
+    ^(self real squared + self imaginary squared)!
+
+conjugate
+    "Return the complex conjugate of the receiver."
+    ^Complex
+       realResult: self real
+       imaginary: self imaginary negated!
+
+!Complex methodsFor: 'transcendental functions'!
+
+exp
+    "Return e raised to the receiver."
+    | expRe |
+    expRe := self real exp.
+    ^Complex
+       realResult: expRe * self imaginary cos
+       imaginary: expRe * self imaginary sin!
+
+sqrt
+    "Return the square root of the receiver.  Can be improved!"
+    | abs |
+    self imaginary < 0 ifTrue: [ ^self conjugate sqrt conjugate ].
+    abs := self abs.
+    ^Complex
+       realResult: ((abs + self real) / 2) sqrt
+       imaginary: ((abs - self real) / 2) sqrt!
+
+sin
+    "Return the sine of the receiver."
+    | sinhIm |
+    sinhIm := self imaginary sinh.
+    ^Complex
+       realResult: self real sin * (sinhIm squared + 1) sqrt
+       imaginary: self real cos * sinhIm!
+
+cos
+    "Return the cosine of the receiver."
+    | sinhIm |
+    sinhIm := self imaginary sinh.
+    ^Complex
+       realResult: self real cos * (sinhIm squared + 1) sqrt
+       imaginary: self real sin negated * sinhIm!
+
+sinh
+    "Return the hyperbolic sine of the receiver."
+    | sinhRe |
+    sinhRe := self real sinh.
+    ^Complex
+       realResult: sinhRe * self imaginary cos
+       imaginary: (sinhRe squared + 1) sqrt * self imaginary sin!
+
+cosh
+    "Return the hyperbolic cosine of the receiver."
+    | sinhRe |
+    sinhRe := self real sinh.
+    ^Complex
+       realResult: (sinhRe squared + 1) sqrt * self imaginary cos
+       imaginary: sinhRe * self imaginary sin!
+
+arg
+    "Return the argument of the receiver."
+    ^self imaginary arcTan: self real!
+
+arcTan
+    "Return the arc-tangent of the receiver."
+    | z |
+    z := ((Complex i + self) / (Complex i - self) asFloat) ln.
+    ^Complex real: 0 imaginary: z / 2!
+
+arcTan: aNumber
+    "Return the arc-tangent of aNumber divided by the receiver."
+    | z |
+    z := ((aNumber i + self) / (aNumber i - self) asFloat) ln.
+    ^Complex real: 0 imaginary: z / 2!
+
+ln
+    "Return the natural logarithm of the receiver."
+    ^Complex
+       realResult: self absSquared ln / 2
+       imaginary: self arg!
+
+log
+    "Return the base-10 logarithm of the receiver."
+    | ln |
+    ln := self ln.
+    ^ln / ln real class ln10! 
+
+tanh
+    "Return the hyperbolic tangent of the receiver."
+    ^self sinh / self cosh!
+
+tan
+    "Return the tangent of the receiver."
+    ^self sin / self cos! !
+
+!Complex methodsFor: 'comparing'!
+
+< aNumber
+    ^self abs < aNumber abs!
+
+<= aNumber
+    ^self abs <= aNumber abs!
+
+>= aNumber
+    ^self abs >= aNumber abs!
+
+> aNumber
+    ^self abs > aNumber abs!
+
+= aNumber
+    aNumber isNumber ifFalse: [ ^false ].
+    ^self real = aNumber real and: [ self imaginary = aNumber imaginary ]!
+
+~= aNumber
+    aNumber isNumber ifFalse: [ ^true ].
+    ^self real ~= aNumber real or: [ self imaginary ~= aNumber imaginary ]!
+
+hash
+    ^self real hash bitXor: self imaginary hash!
+
+!Complex methodsFor: 'converting'!
+
+asFloat
+    ^Complex
+       real: self real asFloat
+       imaginary: self imaginary asFloat!
+
+asFloatD
+    ^Complex
+       real: self real asFloatD
+       imaginary: self imaginary asFloatD!
+
+asFloatE
+    ^Complex
+       real: self real asFloatE
+       imaginary: self imaginary asFloatE!
+
+asFloatQ
+    ^Complex
+       real: self real asFloatQ
+       imaginary: self imaginary asFloatQ!
+
+asFraction
+    ^Complex
+       real: self real asFraction
+       imaginary: self imaginary asFraction!
+
+asExactFraction
+    ^Complex
+       real: self real asExactFraction
+       imaginary: self imaginary asExactFraction!
+
+floor
+    ^Complex
+       real: self real floor
+       imaginary: self imaginary floor!
+
+ceiling
+    ^Complex
+       real: self real ceiling
+       imaginary: self imaginary ceiling!
+
+truncated
+    ^Complex
+       real: self real truncated
+       imaginary: self imaginary truncated!
+
+rounded
+    ^Complex
+       real: self real rounded
+       imaginary: self imaginary rounded! !
+
+!Complex methodsFor: 'printing'!
+
+printOn: aStream
+    aStream
+       nextPut: $(;
+       print: self real;
+       nextPut: $+;
+       print: self imaginary;
+       nextPut: $i;
+       nextPut: $)!
+
+storeOn: aStream
+    aStream
+       nextPut: $(;
+       store: self real;
+       nextPut: $+;
+       store: self imaginary;
+       nextPutAll: ' i)'!
+
+!Complex methodsFor: 'creation/coercion'!
+
+isComplex 
+    ^true!
+
+zero
+    ^Zero!
+
+one
+    ^One!
+
+generality
+    ^re generality + 1000!
+
+real
+    ^re!
+
+imaginary
+    ^im!
+
+coerce: aNumber
+    aNumber isComplex
+       ifFalse: [ ^Complex basicNew setReal: aNumber imaginary: aNumber zero ].
+
+    ^Complex basicNew
+       setReal: (re coerce: aNumber real)
+       imaginary: (re coerce: aNumber imaginary)!
+
+setReal: real imaginary: imag
+    re := real.
+    im := imag!
+
+i
+    "Return the receiver multiplied by the imaginary unit."
+    ^Complex real: self imaginary negated imaginary: self real!
+
+!Number methodsFor: 'accessing'!
+
+real
+    "Return the real part of the receiver."
+    ^self
+!
+
+imaginary
+    "Return the imaginary part of the receiver, which is zero."
+    ^self zero
+!
+
+conjugate
+    "Return the receiver, which is the same as its conjugate."
+    ^self
+!
+
+isComplex 
+    ^false!
+
+absSquared
+    "Return the square of the receiver, which is also the squared absolute
+     value for real numbers."
+    ^self squared
+!
+
+raisedTo: aNumber
+    "Return the receiver, raised to aNumber.  This may answer a complex number
+     if the receiver is negative."
+    | log theta |
+    aNumber isComplex ifFalse: [
+       ^Complex
+           rho: (self absSquared raisedTo: aNumber / 2)
+           theta: (self arg * aNumber) ].
+    log := self abs ln.
+    theta := self arg.
+    ^Complex
+       rho: ((aNumber real * log) - (aNumber imaginary * theta)) exp
+       theta: (aNumber real * theta) + (aNumber imaginary * log)!
+
+arg
+    "Return the argument of the receiver."
+    ^self >= 0 ifTrue: [ 0.0d ] ifFalse: [ FloatD pi ]
+!
+
+i
+    "Return the receiver multiplied by the imaginary unit."
+    ^Complex real: self zero imaginary: self
+! !
+
+!Float methodsFor: 'private'!
+
+primLn
+    "Answer the natural logarithm of the receiver"
+    <primitive: VMpr_Float_ln>
+    self primitiveFailed
+!
+
+primSqrt
+    "Answer the square root of the receiver"
+    <primitive: VMpr_Float_sqrt>
+    self primitiveFailed
+!
+
+!Float methodsFor: 'transcendental functions'!
+
+arg
+    "Return the argument of the receiver."
+    ^self >= 0 ifTrue: [ self zero ] ifFalse: [ self class pi ]
+!
+
+ln
+    "Answer the natural logarithm of the receiver"
+    self >= 0 ifTrue: [ ^self primLn ].
+    ^Complex real: self negated primLn imaginary: self class pi
+!
+
+sqrt
+    "Answer the square root of the receiver"
+    self >= 0 ifTrue: [ ^self primSqrt ].
+    ^Complex real: 0 imaginary: self negated primSqrt
+! !
+
+!Number methodsFor: 'transcendental functions'!
+
+arcCos
+    "Return the arc-cosine of the receiver."
+    | z |
+    z := (Complex real: self imaginary: ((1 - self squared) sqrt)) ln.
+    ^Complex real: 0 imaginary: z negated!
+
+arcSin
+    "Return the arc-sine of the receiver."
+    | z |
+    z := (Complex real: ((1 - self squared) sqrt) imaginary: self) ln.
+    ^Complex real: 0 imaginary: z negated! !
+
+Float methodDictionary
+    removeKey: #arcSin;
+    removeKey: #arcCos!
+
+Complex initialize!



--- /dev/null
+++ mod/packages/complex/complextests.st
@@ -0,0 +1,339 @@
+"======================================================================
+|
+|   Complex numbers test suite
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007 Free Software Foundation, Inc.
+| Written by Paolo Bonzini
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+PackageLoader fileInPackage: #Complex!
+PackageLoader fileInPackage: #SUnit!
+
+TestCase subclass: #ComplexTest
+       instanceVariableNames: ''
+       classVariableNames: ''
+       poolDictionaries: ''
+       category: 'Examples-Useful'!
+
+!ComplexTest methodsFor: 'asserting'!
+
+assert: x closeTo: y
+    self assert: (x closeTo: y)
+! !
+
+!ComplexTest methodsFor: 'unit tests'!
+
+testI
+    self assert: Complex i real == 0.
+    self assert: Complex i imaginary == 1.
+    self assert: Complex i == Complex i.
+    self assert: 1 i real == 0.
+    self assert: 1 i imaginary == 1.
+    self assert: Complex i i == -1!
+
+testPolar
+    self assert: (Complex rho: 1 theta: 0) = 1.
+    self assert: (Complex rho: 1 theta: FloatD pi / 2) closeTo: Complex i.
+    self assert: (Complex rho: 1 theta: FloatD pi) closeTo: -1.
+    self assert: (Complex rho: 2 theta: 0) = 2!
+
+testCartesion
+    self assert: (Complex real: 1 imaginary: 0) == 1.
+    self assert: (Complex real: Complex i imaginary: 0) = Complex i.
+    self assert: (Complex real: 0 imaginary: Complex i) == -1.
+    self assert: (Complex real: 1 imaginary: Complex i) == 0.
+    self assert: (Complex real: 1 imaginary: 1) real == 1.
+    self assert: (Complex real: 1 imaginary: 1) imaginary == 1.
+    self assert: (Complex real: 1 imaginary: 1.0) real isFloat.
+    self assert: (Complex real: 1.0 imaginary: 1) imaginary isFloat!
+
+testPlus
+    self assert: (1 + 2 i) real == 1.
+    self assert: (1 + 2 i) imaginary == 2.
+    self assert: 0.5 i + (1 + 2 i) = (1 + 2.5 i).
+    self assert: 0.5 + (1 + 2 i) = (1.5 + 2 i).
+    self assert: (3 + 4 i) + (1 + 2 i) = (4 + 6 i)!
+
+testMinus
+    self assert: (1 - 2 i) real == 1.
+    self assert: (1 - 2 i) imaginary == -2.
+    self assert: 0.5 i - (1 + 2 i) = (-1 + -1.5 i).
+    self assert: 0.5 - (1 + 2 i) = (-0.5 + -2 i).
+    self assert: (3 + 4 i) - (1 + 3 i) = (2 + 1 i).
+    self assert: (1 + 2.0 i) - (1 + 2 i) = 0.
+    self assert: (1.0 + 2 i) - (1 + 2 i) = 0!
+
+testMultiply
+    self assert: Complex i * Complex i = -1.
+    self assert: Complex i * 1 = Complex i.
+    self assert: Complex i * 0.5 = 0.5 i.
+    self assert: (3 + 4 i) * (1 + 2 i) = (-5 + 10 i)!
+
+testDivide
+    self assert: Complex i / Complex i == 1.
+    self assert: Complex i / 1 = Complex i.
+    self assert: Complex i / 0.5 = 2 i.
+    self assert: ((3 + 4 i) / (1 + 2 i)) = ((22 - 4 i) / 10).
+    self assert: ((3 + 4 i) / (1 + 2 i)) real * 10 == 22.
+    self assert: ((3 + 4 i) / (1 + 2 i)) imaginary * 10 == -4!
+
+testReciprocal
+    self assert: Complex i reciprocal real == 0.
+    self assert: Complex i reciprocal imaginary == -1.
+    self assert: (1 + 2 i) reciprocal real * 5 == 1.
+    self assert: (1 + 2 i) reciprocal imaginary * 5 == -2!
+
+testAbs
+    self assert: (3 + 4 i) abs = 5.
+    self assert: (3 - 4 i) abs = 5.
+    self assert: (-3 + 4 i) abs = 5.
+    self assert: (-3 - 4 i) abs = 5!
+
+testAbsSquared
+    self assert: (3 + 4 i) absSquared == 25.
+    self assert: (3 - 4 i) absSquared == 25.
+    self assert: (-3 + 4 i) absSquared == 25.
+    self assert: (-3 - 4 i) absSquared == 25!
+
+testConjugate
+    self assert: Complex i * Complex i conjugate == 1.
+    self assert: (3 + 4 i) conjugate = (3 - 4 i).
+    self assert: 3 conjugate == 3!
+
+testExp
+    self assert: (FloatD pi negated i) exp closeTo: -1.
+    self assert: (FloatD pi i) exp closeTo: -1.
+    self assert: (FloatD pi i / 2) exp closeTo: Complex i.
+    self assert: (1 + FloatD pi i) exp closeTo: 1 exp negated!
+
+testSin
+    self assert: 1 i sin imaginary = 1 sinh.
+    self assert: (FloatD pi + 1 i) sin imaginary = -1 sinh.
+    self assert: (FloatD pi / 2 + 1 i) sin real = 1 cosh!
+
+testCos
+    self assert: 1 i cos = 1 cosh!
+
+testSinh
+    self assert: FloatD pi i sinh closeTo: 0!
+
+testCosh
+    self assert: FloatD pi i cosh closeTo: -1!
+
+testArcCos
+    self assert: 1 cosh arcCos real closeTo: 0.
+    self assert: 1 cosh arcCos imaginary closeTo: 1!
+
+testArcSin
+    self assert: 1 cosh arcSin imaginary closeTo: -1.
+    self assert: 1 cosh arcSin real closeTo: FloatD pi / 2!
+
+testArcTan
+    self assert: 1 tanh i arcTan real closeTo: 0.
+    self assert: 1 tanh i arcTan imaginary closeTo: 1.
+    self assert: (Complex i arcTan: 1 tanh reciprocal) real closeTo: 0.
+    self assert: (Complex i arcTan: 1 tanh reciprocal) imaginary closeTo: 1!
+
+testArg
+    self assert: -1 arg closeTo: FloatD pi.
+    self assert: Complex i arg closeTo: (FloatD pi / 2).
+    self assert: (1 + 1 i) arg closeTo: (FloatD pi / 4)!
+
+testSqrt
+    self assert: -1 sqrt isComplex.
+    self deny: 1 sqrt isComplex.
+    self assert: -1 sqrt = Complex i.
+    self assert: Complex i sqrt real = Complex i sqrt imaginary.
+    self assert: (3 + 4 i) sqrt = (2+1i)!
+
+testLn
+    self assert: -1 ln isComplex.
+    self deny: 1 ln isComplex.
+    self assert: -1 ln imaginary closeTo: FloatD pi.
+    self assert: (1 + 1 i) ln real * 2 closeTo: 2 ln.
+    self assert: (1 + 1 i) ln imaginary closeTo: (FloatD pi / 4)!
+
+testLog
+    "Return the base-10 logarithm of the receiver."
+    self assert: (1 + 1 i) log real * 2 = 2 log!
+
+testTanh
+    "Return the hyperbolic tangent of the receiver."
+    self assert: Complex i tanh closeTo: 1 tan i!
+
+testTan
+    "Return the tangent of the receiver."
+    self assert: Complex i tan closeTo: 1 tanh i!
+
+testLess
+    self deny: (1 + 1 i) < 1.
+    self deny: (1 + 1 i) < -1.
+    self deny: (3 + 4 i) < 5.
+    self deny: (3 + 4 i) < -5.
+    self deny: (3 + 4 i) < (4 + 3 i).
+    self deny: (3 + 4 i) < (4 - 3 i).
+    self deny: (3 - 4 i) < (4 + 3 i).
+    self deny: (3 - 4 i) < (4 - 3 i).
+    self assert: (1 + 1 i) < 10.
+    self assert: (1 + 1 i) < -10!
+
+testLessEqual
+    self deny: (1 + 1 i) <= 1.
+    self deny: (1 + 1 i) <= -1.
+    self assert: (3 + 4 i) <= 5.
+    self assert: (3 + 4 i) <= -5.
+    self assert: (3 + 4 i) <= (4 + 3 i).
+    self assert: (3 + 4 i) <= (4 - 3 i).
+    self assert: (3 - 4 i) <= (4 + 3 i).
+    self assert: (3 - 4 i) <= (4 - 3 i).
+    self assert: (1 + 1 i) <= 10.
+    self assert: (1 + 1 i) <= -10!
+
+testGreaterEqual
+    self assert: (1 + 1 i) >= 1.
+    self assert: (1 + 1 i) >= -1.
+    self assert: (3 + 4 i) >= 5.
+    self assert: (3 + 4 i) >= -5.
+    self assert: (3 + 4 i) >= (4 + 3 i).
+    self assert: (3 + 4 i) >= (4 - 3 i).
+    self assert: (3 - 4 i) >= (4 + 3 i).
+    self assert: (3 - 4 i) >= (4 - 3 i).
+    self deny: (1 + 1 i) >= 10.
+    self deny: (1 + 1 i) >= -10!
+
+testGreater
+    self assert: (1 + 1 i) > 1.
+    self assert: (1 + 1 i) > -1.
+    self deny: (3 + 4 i) > 5.
+    self deny: (3 + 4 i) > -5.
+    self deny: (3 + 4 i) > (4 + 3 i).
+    self deny: (3 + 4 i) > (4 - 3 i).
+    self deny: (3 - 4 i) > (4 + 3 i).
+    self deny: (3 - 4 i) > (4 - 3 i).
+    self deny: (1 + 1 i) > 10.
+    self deny: (1 + 1 i) > -10!
+
+testEqual
+    self assert: (3 + 4 i) = (3 + 4 i).
+    self assert: (3 + 4 i) = (3.0 + 4.0 i).
+    self deny: (3 + 4 i) = 5.
+    self deny: (3 + 4 i) = -5.
+    self deny: (3 + 4 i) = (4 + 3 i).
+    self deny: (3 + 4 i) = (4 - 3 i).
+    self deny: (3 - 4 i) = (4 + 3 i).
+    self deny: (3 - 4 i) = (4 - 3 i)!
+
+testNotEqual
+    self deny: (3 + 4 i) ~= (3 + 4 i).
+    self deny: (3 + 4 i) ~= (3.0 + 4.0 i).
+    self assert: (3 + 4 i) ~= 5.
+    self assert: (3 + 4 i) ~= -5.
+    self assert: (3 + 4 i) ~= (4 + 3 i).
+    self assert: (3 + 4 i) ~= (4 - 3 i).
+    self assert: (3 - 4 i) ~= (4 + 3 i).
+    self assert: (3 - 4 i) ~= (4 - 3 i)!
+
+testHash
+    self assert: (3 + 4 i) hash = (3 + 4 i) hash.
+    self assert: (3 + 4 i) hash = (3.0 + 4.0 i) hash!
+
+testAsFloat
+    self assert: (3 + 4 i) asFloat real isFloat.
+    self assert: (3 + 4 i) asFloat imaginary isFloat!
+
+testAsFloatD
+    self assert: (3 + 4 i) asFloatD real isFloat.
+    self assert: (3 + 4 i) asFloatD imaginary isFloat!
+
+testAsFloatE
+    self assert: (3 + 4 i) asFloatE real isFloat.
+    self assert: (3 + 4 i) asFloatE imaginary isFloat!
+
+testAsFloatQ
+    self assert: (3 + 4 i) asFloatQ real isFloat.
+    self assert: (3 + 4 i) asFloatQ imaginary isFloat!
+
+testAsFraction
+    self deny: (3.0 + 4 i) asFraction real isFloat.
+    self deny: (3.0 + 4 i) asFraction imaginary isFloat!
+
+testAsExactFraction
+    self deny: (3.0 + 4 i) asFraction real isFloat.
+    self deny: (3.0 + 4 i) asFraction imaginary isFloat!
+
+testFloor
+    self assert: (3.5 + 4.5 i) floor real == 3.
+    self assert: (3.5 + 4.5 i) floor imaginary == 4.
+    self assert: (-2.5 - 3.5 i) floor real == -3.
+    self assert: (-2.5 - 3.5 i) floor imaginary == -4!
+
+testCeiling
+    self assert: (2.5 + 3.5 i) ceiling real == 3.
+    self assert: (2.5 + 3.5 i) ceiling imaginary == 4.
+    self assert: (-3.5 - 4.5 i) ceiling real == -3.
+    self assert: (-3.5 - 4.5 i) ceiling imaginary == -4!
+
+testTruncated
+    self assert: (3.5 + 4.5 i) truncated real == 3.
+    self assert: (3.5 + 4.5 i) truncated imaginary == 4.
+    self assert: (-3.5 - 4.5 i) truncated real == -3.
+    self assert: (-3.5 - 4.5 i) truncated imaginary == -4!
+
+testRounded
+    self assert: (3.25 + 3.75 i) rounded real == 3.
+    self assert: (3.25 + 3.75 i) rounded imaginary == 4.
+    self assert: (-3.25 - 3.75 i) rounded real == -3.
+    self assert: (-3.25 - 3.75 i) rounded imaginary == -4!
+
+testIsComplex 
+    self assert: Complex i isComplex.
+    self deny: (Complex real: 5 imaginary: 0) isComplex.
+    self deny: 5 isComplex!
+
+testZero
+    self assert: Complex i zero = 0.
+    self assert: 0 = Complex i zero!
+
+testOne
+    self assert: Complex i one = 1.
+    self assert: 1 = Complex i one!
+
+testReal
+    self assert: 5 real == 5.
+    self assert: 5.0 real = 5.0.
+    self assert: Complex i real = 0.
+    self assert: Complex i one real = 1!
+
+testImaginary
+    self assert: 5 imaginary == 0.
+    self assert: 5.0 imaginary = 0.
+    self assert: Complex i imaginary = 1.
+    self assert: Complex i one imaginary = 0!
+
+testRaisedTo
+    self assert: (Complex i raisedTo: Complex i) closeTo: (Float pi / -2) exp.
+    self assert: (1 raisedTo: Complex i) = 1! !

reply via email to

[Prev in Thread] Current Thread [Next in Thread]