Squeak to be exact.  This is a changeset you can fileIn to Squeak.

'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 29 September 2004 at 
3:00:29 pm'!
Number subclass: #ComplexNumber
        instanceVariableNames: 'realPart imaginaryPart '
        classVariableNames: ''
        poolDictionaries: ''
        category: 'My stuff'!

!ComplexNumber commentStamp: 'kjs 9/29/2004 14:46' prior: 0!
A bare-bones complex-number implementation sufficient for drawing the Mandelbrot set.

"i _ ComplexNumber fromReal: 0 andImaginary: 1."
"i * i"

Structure:
 realPart               Number
 imagPart               Number

This class doesn't support most of the things you would expect a complex number class 
to support, such as numeric coercion, subtraction, etc.!

Morph subclass: #MandelMorph
        instanceVariableNames: 'scale lake wheel pixels maxiter '
        classVariableNames: ''
        poolDictionaries: ''
        category: 'My stuff'!

!MandelMorph commentStamp: 'kjs 9/29/2004 14:57' prior: 0!
A really bad way to draw a Mandelbrot set: override drawOn to render it anew every time
it's exposed!!  Actually practical to do with modern machines, but still a little 
unresponsive.

MandelMorph new openInHand.

Structure:
 scale                  Float -- the width or height of the visible part of the 
complex plane
 lake                   Color -- the color to paint points inside the set, 
traditionally blue or black
 wheel                  Array of Colors -- colors to paint points in successive 
approximations to the set.
 pixels                 Integer -- the number of horizontal or vertical subdivisions 
in the morph.
 maxiter                Integer -- the maximum number of iterations to try to 
approximate the set.
!


!ComplexNumber methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 02:36'!
imag
        ^ imaginaryPart! !

!ComplexNumber methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 02:35'!
real
        ^ realPart! !

!ComplexNumber methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 02:26'!
setRealPart: newRealPart andImaginaryPart: newImaginaryPart
        realPart _ newRealPart.
        imaginaryPart _ newImaginaryPart.
! !

!ComplexNumber methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 06:20'!
squaredMagnitude
        ^ ((realPart * realPart) + (imaginaryPart * imaginaryPart)).! !

!ComplexNumber methodsFor: 'printing' stamp: 'kjs 9/29/2004 02:49'!
printOn: aStream
        aStream nextPut: $(; nextPutAll: self class name asString; nextPutAll: ' 
withReal: '.
        self real printOn: aStream.
        aStream nextPutAll: ' andImaginary: '.
        self imag printOn: aStream.
        aStream nextPut: $).! !

!ComplexNumber methodsFor: 'arithmetic' stamp: 'kjs 9/29/2004 06:18'!
* other
        ^ ComplexNumber 
                withReal: ((realPart * other real) - (imaginaryPart * other imag))
                andImaginary: ((realPart * other imag) + (imaginaryPart * other 
real)).! !

!ComplexNumber methodsFor: 'arithmetic' stamp: 'kjs 9/29/2004 06:21'!
+ other
        ^ ComplexNumber withReal: realPart + other real andImaginary: imaginaryPart + 
other imag.! !


!ComplexNumber class methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 05:33'!
fromPoint: aPoint
        ^ ComplexNumber withReal: aPoint x andImaginary: aPoint y.
! !

!ComplexNumber class methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 02:42'!
withReal: newRealPart andImaginary: newImaginaryPart
        | obj |
        obj _ self new.
        obj setRealPart: newRealPart andImaginaryPart: newImaginaryPart.
        ^obj.! !


!MandelMorph methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 14:31'!
colorForIters: anInteger
        anInteger ifNil: [^ lake].
        ^ wheel at: 1 + ((anInteger - 1) \\ wheel size).

! !

!MandelMorph methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 14:11'!
colorForPoint: aPoint
        | c |
        c _ ComplexNumber fromPoint: (aPoint - self center) / self extent * scale.
        ^ self colorForIters: (self mandelbrotIterationsFrom: c max: maxiter).
! !

!MandelMorph methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 06:03'!
gridPointAt: x and: y scale: n
        ^ self topLeft + ((self width * (x / n)) @ (self height * (y / n))) 
asIntegerPoint
! !

!MandelMorph methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 06:29'!
mandelbrotIterationsFrom: c max: max
        | z |
        z _ ComplexNumber withReal: 0 andImaginary: 0.
        1 to: max do: [:i |
                z _ z * z + c.
                (z squaredMagnitude > 4) ifTrue: [ ^ i. ]
        ].
        ^nil.
! !

!MandelMorph methodsFor: 'as yet unclassified' stamp: 'kjs 9/29/2004 06:04'!
rectStartingAt: x and: y scale: n
        ^Rectangle 
                origin: (self gridPointAt: x and: y scale: n)
                corner: (self gridPointAt: x + 1 and: y + 1 scale: n)! !

!MandelMorph methodsFor: 'drawing' stamp: 'kjs 9/29/2004 14:08'!
drawOn: aCanvas
        0 to: (pixels - 1) do: [:x |
                0 to: (pixels - 1) do: [:y | |aRectangle|
                        aRectangle _ self rectStartingAt: x and: y scale: pixels.
                        aCanvas fillRectangle: aRectangle color: (self colorForPoint: 
aRectangle center).
                ].
        ].
! !

!MandelMorph methodsFor: 'initialization' stamp: 'kjs 9/29/2004 14:29'!
initialize
        super initialize.
        scale _ 4.0.
        lake _ Color transparent.
        wheel _ {Color blue}, (Color wheel: 15).
        pixels _ 70.
        maxiter _ 20.! !


Reply via email to