[EHN]StarMorph, take 2

Karl Ramberg karl.ramberg at chello.se
Mon Sep 25 18:40:09 UTC 2000


I enhanced the StarMorph to use three handles: 
The center one to move the star around.
A middle one to set the depth of the points, blue color for a change.
A outer one to set the size of the star.

The two latter can switch places so the outer becomes the inner etc.
Also note that the halo menu for the StarMorph now includes 
a Points choice that let you set the number of points on your star.

The only issue I see on it is that the handles don't show in the 'right' 
place all the time. Have to dive into the handles code to fix this...

Have fun, be a star :-)

Karl
-------------- next part --------------
'From Squeak2.9alpha of 13 June 2000 [latest update: #2657] on 25 September 2000 at 8:25:34 pm'!
PolygonMorph subclass: #StarMorph
	instanceVariableNames: 'points pt innerExt outerExt '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/24/2000 17:51'!
addCustomMenuItems: aMenu hand: aHandMorph
	
	super addCustomMenuItems: aMenu hand: aHandMorph.
	aMenu add: 'Points' action:  #inputPoints.

	! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/25/2000 19:59'!
addHandles
	| handle strokeOrigin p |
	handles ifNotNil: [handles do: [:hh | hh delete]].
	strokeOrigin _ 0 at 0.
	vertices do: [:each | strokeOrigin _ strokeOrigin + each].
	strokeOrigin _ strokeOrigin // vertices size.	"average is the center"
	handles _ Array new: 3.
		handle _ EllipseMorph newBounds: (Rectangle center: strokeOrigin extent: 8 at 8)
				color: Color yellow.
		handle on: #mouseStillDown send: #dragVertex:fromHandle:vertIndex:
				to: self withValue: #center.
		self addMorph: handle.
	handles at: 1 put: handle.	"The center one!!!!"
		p _ vertices at: 2.	"The middle one"
		handle _ EllipseMorph newBounds: (Rectangle center: p + (borderWidth//2) extent: 8 at 8)
				color: Color blue.
		handle on: #mouseStillDown send: #dragVertex:fromHandle:vertIndex:
				to: self withValue: #middle.
		self addMorph: handle.
	handles at: 2 put: handle.	"The middle one!!!!"
	p _ vertices at: 3	"an outside one".
		handle _ EllipseMorph newBounds: (Rectangle center: p + (borderWidth//2) extent: 8 at 8)
				color: Color yellow.
		handle on: #mouseStillDown send: #dragVertex:fromHandle:vertIndex:
				to: self withValue: #outside.
		self addMorph: handle.
	handles at: 3 put: handle.	"The outside one!!!!"
	self changed! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/25/2000 19:56'!
dragVertex: evt fromHandle: handle vertIndex: label 
	| oldR strokeOrigin offset |
	label == #center
		ifTrue: [offset _ evt cursorPoint - (handles at: 1) bounds center.
			self position: self position + offset].

label == #middle
		ifTrue: [strokeOrigin _ (handles at: 1) bounds center.
			pt _ strokeOrigin - evt cursorPoint - ((handles at: 2) extent // 2).
			innerExt _ pt r.
			oldR _ outerExt.
			vertices _ (0 to: 359 by: 360 // vertices size)
						collect: [:angle | (Point r: (oldR _ oldR = outerExt
											ifFalse: [outerExt]
											ifTrue: [innerExt]) degrees: angle + pt degrees)
								+ strokeOrigin].
			(handles at: 2)
				position: evt cursorPoint].

	label == #outside
		ifTrue: [strokeOrigin _ (handles at: 1) bounds center.
			pt _ strokeOrigin - evt cursorPoint - ((handles at: 3) extent // 3).
			outerExt _ pt r.
			oldR _ innerExt.
			vertices _ (0 to: 359 by: 360 // vertices size)
						collect: [:angle | (Point r: (oldR _ oldR = innerExt
											ifFalse: [innerExt]
											ifTrue: [outerExt]) degrees: angle + pt degrees)
								+ strokeOrigin].
			(handles at: 3)
				position: evt cursorPoint].
	self computeBounds! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/24/2000 17:49'!
handlesMouseDown
	^true! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/24/2000 17:49'!
initialize
	super initialize.
	borderWidth _ 1.
	borderColor _ Color black.
	pt _ 10 @ 10.
	points _ 5.
	self updateDrawing! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/24/2000 17:48'!
inputPoints
	points _ FillInTheBlank request: 'Number of Points on the star:'.
	self updateDrawing! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/24/2000 16:47'!
mouseDown: evt

	^ evt shiftPressed
		ifTrue: [((owner isKindOf: PolygonMorph) and: [owner includesHandle: self])
					ifTrue: ["Prevent insertion handles from getting edited"
							^ super mouseDown: evt].
				self toggleHandles.
				handles ifNil: [^ self].
				]
		ifFalse: [super mouseDown: evt]! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/24/2000 17:47'!
points: aInteger 
	^ points _ aInteger! !

!StarMorph methodsFor: 'as yet unclassified' stamp: 'kfr 9/25/2000 20:22'!
updateDrawing
	| strokeOrigin oldR |
	strokeOrigin _ self bounds center.
	outerExt _ pt r.
	innerExt _ outerExt//2.
	oldR _ outerExt.
	vertices _ (0 to: 359 by: 360 // points // 2)
				collect: [:angle | (Point r: (oldR _ oldR = innerExt
									ifTrue: [outerExt]
									ifFalse: [innerExt]) degrees: angle + pt degrees)
						+ strokeOrigin].
	self position: self position.
	self computeBounds! !



More information about the Squeak-dev mailing list