[ENH] SimpleXYGraphMorph

Jesse Welton jwelton at pacific.mps.ohio-state.edu
Wed Feb 16 20:29:53 UTC 2000



On Wed, 16 Feb 2000 ssadams at us.ibm.com wrote:
> 
> Andreas,
> I filed in the plot package and it contained lots of references to other
> MorphicWrapper (MW) classes, so I assumed it was dependent on them.  I was
> hoping to find a simple, standalone example of the plotter that didn't
> require MW, all of your wonderful math objects, and a PhD in math to boot.

I don't know if this is quite what you're looking for, but here's a simple
little PointPlotterMorph I wrote a little while back for some numerical
work I was doing.  It keeps a list of points and automatically scales to
the max and min x and y coordinates, and provides ScaleMorph axes which it
*tries* to provide nice tick-marks for.  It's rough around the edges, but
it may be useful to you (or someone).  I'd be glad to see it spruced up.
One particular problem it has, if I recall correctly, is that its behavior
is screwy if it doesn't have at least two points in its collection (or if
they are all at the same x or y).

-Jesse

-------------- next part --------------
'From Squeak 2.5 of August 6, 1999 on 16 February 2000 at 3:16:30 pm'!
RectangleMorph subclass: #PointPlotterMorph
	instanceVariableNames: 'points origin scale vertTicks horzTicks '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 12/10/1999 11:37'!
addPoint: aPoint
	points add: aPoint.
	self rescale.! !

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 12/10/1999 12:16'!
addPointButDeferRescale: aPoint
	points add: aPoint.! !

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 12/10/1999 12:01'!
addPoints: somePoints
	points addAll: somePoints.
	self rescale.! !

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 12/10/1999 11:44'!
extent: aPoint
	super extent: aPoint.
	self rescale.! !

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 11/17/1999 17:08'!
plotRectangle
	^ self topLeft + (50 at 10) corner: self bottomRight - (10 at 50)! !

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 12/10/1999 12:15'!
points: aCollection
	points := aCollection copy.
	self rescale.! !

!PointPlotterMorph methodsFor: 'as yet unclassified' stamp: 'JW 12/22/1999 16:16'!
rescale
	| minx miny maxx maxy plotRect sx sy hRound vRound |

	points size < 2 ifTrue: [ scale := 0 at 0. origin := self center. ^self ].

	minx := (points collect: [ :pt | pt x ]) min.
	maxx := (points collect: [ :pt | pt x ]) max.
	miny := (points collect: [ :pt | pt y ]) min.
	maxy := (points collect: [ :pt | pt y ]) max.

	hRound := (maxx = minx)
					ifTrue: [ minx ]
					ifFalse: [(10 raisedTo: (maxx-minx floorLog:10) - 2)].
	minx := minx roundTo: hRound.
	maxx := maxx roundTo: hRound.

	vRound := (maxy = miny)
					ifTrue: [ miny ]
					ifFalse: [(10 raisedTo: (maxy-miny floorLog:10) - 2)].
	miny := miny roundTo: vRound.
	maxy := maxy roundTo: vRound.

	plotRect := self plotRectangle.
	sx := (maxx = minx) ifTrue: [ 0 ] ifFalse: [plotRect width / (maxx - minx)].
	sy := (maxy = miny) ifTrue: [ 0 ] ifFalse: [plotRect height / (miny - maxy)].
	scale := sx @ sy.
	origin := plotRect bottomLeft - ((minx @ miny) * scale).

	horzTicks := ScaleMorph new.
	horzTicks start: minx stop: maxx
			  minorTick: hRound * 5 minorTickLength: 4
			  majorTick: hRound * 50 majorTickLength: 7
			  caption: 'Temperature'
			  tickPrintBlock: [ :x | (x roundTo: hRound) asFloat asString ] fixTemps;
		color: Color transparent;
		bounds: (plotRect bottomLeft corner: plotRect right @ self bottom );
		lock.

	vertTicks := ScaleMorph new.
	vertTicks start: maxy negated stop: miny negated
			  minorTick: vRound * 10 minorTickLength: 4
			  majorTick: vRound * 100 majorTickLength: 7
			  caption: 'Determinant'
			  tickPrintBlock: [ :y | (y roundTo: vRound) negated asFloat asString ] fixTemps;
		color: Color transparent;
		bounds: (plotRect topLeft transposed corner: (self left @ plotRect bottom) transposed).
	vertTicks := TransformationMorph new asFlexOf: vertTicks.
	vertTicks rotationDegrees: 90;
		position: self left @ plotRect top;
		lock.

	self removeAllMorphs.

	self addMorph: vertTicks.
	self addMorph: horzTicks.
	self addAllMorphs: (points collect: [ :pt | DotMorph new position: origin + (pt * scale);
															lock;
															yourself ]).
! !


More information about the Squeak-dev mailing list