[comp.lang.smalltalk] ArrowedSpline goody

ross@prls.UUCP (Ross Morley) (09/05/90)

As promised, another goody:

This is a subclass of the standard ST80 library class Spline. It behaves just
like Spline but adds arrowheads to the curves, indicating direction. The
direction is determined by the order of the points you supply to define the
curve. An arrowhead is placed at the midpoint of each section of the curve
between adjacent pairs of defining points.

Displaying the arrowheads is very fast - displaying an ArrowedSpline is not
noticeably slower than displaying a Spline (most of the time goes into
displaying the curve). Each ArrowedSpline instance caches Forms for the
arrowheads at orientations 15 degrees apart around the circle (ie. 4 angles
in each 45 degree sector). This can be changed to any integral number of
steps per 45 degreee angle simply by changing a number in the class
initialize method and executing the method. The provision of
'initializePoints' and 'initializePoints:' methods in the public interface
allows you to reuse an instance, with a different set of points, without
recomposing the cached arrowhead forms. The cached Forms are discarded when 
the spline's form is changed, as it is then necessary to recompose them.

Try the example. Change some parameters in the example (eg. the form) and try
it again. Have fun!

--------------------------------- cut here ---------------------------------

'From Smalltalk-80, Version 2.3 of 13 June 1988 on 4 September 1990 at 5:04:45 pm'!

Spline subclass: #ArrowedSpline
	instanceVariableNames: 'arrows arrowBrush arrowHalfWidth '
	classVariableNames: 'StepsPer45degreeAngle '
	poolDictionaries: ''
	category: 'Graphics-Paths'!
ArrowedSpline comment:
'This is a Spline curve with arrowheads between each defining point (thus a Spline defined 
with N points has N-1 arrowheads). The arrowheads point in the direction from the first to 
the last point.

Instance variables:

arrows				An Array with cached arrowhead Forms at discrete angles around a full 
					circle. The number of Forms is 8*StepsPer45degreeAngle.

arrowBrush			The Form used to draw the arrowheads.

arrowHalfWidth		An Integer. No. of pixels from the center to any edge of an arrow Form.

Class variables:

StepsPerRightAngle		The number of discrete Forms cached per quarter circle.

					Copyright (c) Ross P. Morley, September 1989.
	This program is placed in the public domain. You may use and alter this program freely
	for non-commercial purposes as long as you leave this message intact.  Neither I nor
	my company will recognize any responsibility for damages arising from use of this program.
'!


!ArrowedSpline methodsFor: 'accessing'!

arrowForGradient: aPoint
	"Answer the arrow Form whose gradient is closest to the gradient defined 
	by aPoint whose x and y components are both Numbers and not both zero."

	^self arrowFormAt: (self indexForGradient: aPoint)!

form: aForm 
	"Make the argument, aForm, the receiver's form.
	Compose a new arrowBrush and recompute the arrowHalfWidth.
	Invalidate the cached arrowhead forms so they will be recomputed."

	| brushWidth |
	super form: aForm.
	brushWidth _ (self form width * 2 // 3) max: 1.
	(arrowBrush _ Form extent: brushWidth asPoint) 
		offset: (brushWidth // 2) negated asPoint; 
		black.
	arrowHalfWidth _ (self form width * 2.5) rounded.
	self initializeArrowsArray!

initializePoints
	"Reinitialize the collection of points so a new set can be added."

	self initializeCollectionOfPoints!

initializePoints: anInteger
	"Reinitialize the collection of points so a new set can be added, specifying the initial size."

	self initializeCollectionOfPoints: anInteger! !

!ArrowedSpline methodsFor: 'displaying'!

displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger mask: aForm 
	"Method for display of a Spline curve approximated by straight line segments."

	| segment steps a b c d t |
	segment _ Line new.
	segment form: self form.
	segment beginPoint: self first.
	1 to: self size-1 do:		"for each knot"
		[:k | 
			"taylor series coefficients"
		d _ self at: k.
		c _ (derivatives at: 1) at: k.
		b _ ((derivatives at: 2) at: k) / 2.0.
		a _ ((derivatives at: 3) at: k) / 6.0.
			"arrowhead"
		(self arrowForGradient: a * 0.75 + b + c) 	"3at^2 + 2bt + c, for t=0.5"
			displayOn: aDisplayMedium
			at: a * 0.5 + b * 0.5 + c * 0.5 + d + aPoint 	"at^3 + bt^2 + ct + d, for t=0.5"
			clippingBox: clipRect
			rule: anInteger
			mask: aForm.
			"guess stepping parameter"
		steps _ ((derivatives at: 2) at: k) abs + ((derivatives at: 2) at: k+1) abs.
		steps _ 5 max: (steps x + steps y) // 100.
		1 to: steps - 1 do: 
			[:j | 
			t _ j asFloat / steps.
			segment endPoint: a * t + b * t + c * t + d.	"at^3 + bt^2 + ct + d"
			segment
				displayOn: aDisplayMedium
				at: aPoint
				clippingBox: clipRect
				rule: anInteger
				mask: aForm.
			segment beginPoint: segment endPoint].
		segment endPoint: (self at: k+1).
		segment
			displayOn: aDisplayMedium
			at: aPoint
			clippingBox: clipRect
			rule: anInteger
			mask: aForm.
		segment beginPoint: segment endPoint]! !

!ArrowedSpline methodsFor: 'private'!

arrowFormAt: anInteger
	"Answer the cached arrow Form at index anInteger, composing it if necessary."

	(arrows at: anInteger) isNil
		ifTrue: [self composeArrowFormAt: anInteger].
	^arrows at: anInteger!

composeArrowFormAt: anInteger
	"Compose the arrow Form at anInteger index in the cache array."

	| arrowForm quadrant index dx dy tip bb |
	arrowForm _ Form extent: (2*arrowHalfWidth + 1) asPoint. 
	quadrant _ anInteger-1 // self class stepsPerRightAngle.
	index _ anInteger-1 \\ self class stepsPerRightAngle.
	index <= self class stepsPer45degreeAngle
		ifTrue: [
			dx _ 0.71*arrowHalfWidth.	"1/(2 sqrt) factor for 45 degree rotation"
			dy _ dx * index / self class stepsPer45degreeAngle]
		ifFalse: [
			dy _ 0.71*arrowHalfWidth.	"1/(2 sqrt) factor for 45 degree rotation"
			dx _ dy * (self class stepsPerRightAngle - index) / self class stepsPer45degreeAngle].
	quadrant = 1 ifTrue: [tip _ dx. dx _ dy negated. dy _ tip].
	quadrant = 2 ifTrue: [dx _ dx negated. dy _ dy negated].
	quadrant = 3 ifTrue: [tip _ dy. dy _ dx negated. dx _ tip].
	bb _ BitBlt
		destForm: arrowForm
		sourceForm: arrowBrush
		halftoneForm: nil
		combinationRule: Form under
		destOrigin: 0@0
		sourceOrigin: 0@0
		extent: arrowBrush extent
		clipRect: arrowForm boundingBox.
	tip _ arrowHalfWidth asPoint + (dx@dy) rounded.	"pull tip forward along axis (angles go to 27 deg.)"
	bb drawFrom: tip 	"draw arm to point arrowHalfWidth out at -135 degrees off axis from center"
		to: arrowHalfWidth asPoint - ((dx-dy)@(dx+dy)) rounded.
	bb drawFrom: tip  	"draw arm to point arrowHalfWidth out at +135 degrees off axis from center"
		to: arrowHalfWidth asPoint - ((dx+dy)@(dy-dx)) rounded.
	arrowForm offset: self form relativeRectangle center - arrowHalfWidth.
	arrows at: anInteger put: arrowForm!

indexForGradient: aPoint
	"Answer the arrows array index (an Integer) for the arrow closest to the gradient defined 
	by aPoint whose x and y components are both Numbers and not both zero."

	| dx dy tmp flipped |
	dx _ aPoint x abs.
	dy _ aPoint y abs.
	(flipped _ dy > dx) ifTrue: [tmp_dx. dx_dy. dy_tmp].	"ensure dy<=dx"
	tmp _ (self class stepsPer45degreeAngle * dy/dx) rounded.
	flipped 				"map back to right angle sector"
		ifTrue: [tmp _ self class stepsPerRightAngle - tmp].
	aPoint x negative			"map to top semicircle"
		ifTrue: [tmp _ 2 * self class stepsPerRightAngle - tmp].
	aPoint y negative			"map to full circle"
		ifTrue: [tmp _ 4 * self class stepsPerRightAngle - tmp].
	^ (tmp \\ (4 * self class stepsPerRightAngle)) + 1	"map to array index"!

initializeArrowsArray
	"Create a new Array for caching arrowhead Forms."

	arrows _ Array new: 4 * self class stepsPerRightAngle! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

ArrowedSpline class
	instanceVariableNames: ''!


!ArrowedSpline class methodsFor: 'accessing'!

stepsPer45degreeAngle

	^StepsPer45degreeAngle!

stepsPerRightAngle

	^ 2 * self stepsPer45degreeAngle! !

!ArrowedSpline class methodsFor: 'class initialization'!

initialize
	"(Re)initialize the class and invalidate the arrow caches of any instances."
	"ArrowedSpline initialize"

	StepsPer45degreeAngle _ 4.
	self allInstances do: [:anAS | anAS initializeArrowsArray]! !

!ArrowedSpline class methodsFor: 'examples'!

splineSample
	"Designate points on the Path by clicking the red button.  Terminate 
	by pressing any other button.  A curve will be displayed, through the 
	selected points, using a square black form."

	"ArrowedSpline splineSample."

	| splineCurve aForm flag|
	aForm _ Form new extent: 3@3.
	aForm black.
	splineCurve _ self new.
	splineCurve form: aForm.
	flag _ true.
	[flag] whileTrue:
		[Sensor waitButton.
		 Sensor redButtonPressed
			ifTrue: 
				[splineCurve add: Sensor waitButton. 
				 Sensor waitNoButton.
				 aForm displayOn: Display at: splineCurve last]
			ifFalse: [flag_false]].
	splineCurve computeCurve.
	splineCurve isEmpty 
		ifFalse: [splineCurve displayOn: Display at: 0@0 rule: Form under.
				Sensor waitNoButton].
 	^splineCurve! !

ArrowedSpline initialize!

--------------------------------- cut here ---------------------------------

-- 
Ross P. Morley                                  pyramid!prls!ross
Philips Research, Sunnyvale                     philabs!prls!ross
811 E. Arques Ave (MS02)			ross@prls.uucp
Sunnyvale, CA 94088-3409                        Tel. (408) 991 5057