[Pkg] The Trunk: MorphicExtras-tpr.208.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jun 29 20:40:03 UTC 2017


tim Rowledge uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-tpr.208.mcz

==================== Summary ====================

Name: MorphicExtras-tpr.208
Author: tpr
Time: 29 June 2017, 1:39:47.531472 pm
UUID: fa32d395-0aae-4754-bda1-d184dd95713c
Ancestors: MorphicExtras-nice.207

Move the rotary dial morphs into this package as suggested by Marcel.

=============== Diff against MorphicExtras-nice.207 ===============

Item was added:
+ RotaryDialMorph subclass: #BarometerMorph
+ 	instanceVariableNames: 'priorPressureIndicator'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Widgets'!
+ 
+ !BarometerMorph commentStamp: 'tpr 4/13/2017 16:48' prior: 0!
+ I am a model of a moderately visually ornate barometer, complete with curly tailed needle and the adjustable 'last pressure' needle used to help display the recent changes in pressure. In this case a d-click makes the 'last pressure' needle move to the current pressure position.
+ 
+ !

Item was added:
+ ----- Method: BarometerMorph>>buildDial (in category 'dial drawing') -----
+ buildDial
+ 	"start by making a damn big Form, twice the size we want to end up with"
+ 	|outerRadius destForm canvas tickLabel tickLength beginAngle endAngle tickAngle tickLabelSize maxTicks |
+ 	outerRadius := self height  - 1.
+ 	destForm := Form extent: self extent * 2 depth: 32.
+ 	(canvas := destForm getCanvas) fillOval: (0 at 0 extent: self extent * 2) color: Color white.
+ 	"outer ring"
+ 	self drawArcAt: destForm center radius: outerRadius thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	"inner ring"
+ 	self drawArcAt: destForm center radius: outerRadius * 0.97 thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	
+ 	"outer scale for inches of HG"
+ 	beginAngle := startAngle -360. "needs cleaning up about this"
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.8 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.73 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	"since we're going from 28in. to 31in. of Hg for the outer scale and want alternating full and half ticks as we go round we need 31-28 * 10 * 2 -> 60 ticks"
+ 	maxTicks := 31 - 28 * 10 * 2.
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	0 to: maxTicks do: [:tick|
+ 		tickLabel := nil.
+ 		tickLength := {outerRadius * 0.07. outerRadius * 0.14} atWrap: tick+1.
+ 		tick \\ 20 = 0 ifTrue: [
+ 			tickLabel := #( '28' '29' '30' '31') at: tick // 20 + 1.
+ 			tickLabelSize := 24.
+ 		] ifFalse: [
+ 			tick \\ 2 = 0 ifTrue: [
+ 				tickLabel :=  (tick // 2 \\ 10) asString.
+ 				tickLabelSize := 18.
+ 			].
+ 		].
+ 		self drawTickRadius: outerRadius * 0.73 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick * tickAngle) onCanvas: canvas.
+ 		self tickLabel: tickLabel fontSize: tickLabelSize color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) + tickLength angle: beginAngle + (tick * tickAngle) onCanvas: canvas.
+ 	].
+ 
+ 	self tickInnerLabel: 'mB' fontSize: 36 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) angle: 180 onCanvas: canvas.
+ 
+ 	"inner scale for mB"
+ 	beginAngle := startAngle -360. "needs cleaning up about this"
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.71 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.63 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	"since we're going from 948mB to 1050 for this inner scale and want thick ticks at each 10mB interval with narrow ones elsewhere we have (1050 - 948) total ticks "
+ 	maxTicks := stopValue - startValue.
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	tickLength := outerRadius * 0.07.
+ 	startValue to: stopValue do: [ :tick ||tickThickness|
+ 		tickLabel := nil.
+ 		tick \\ 10 = 0 ifTrue: [
+ 			tickLabelSize := 20.
+ 			tickThickness := 3.
+ 			tickLabel :=  tick asString.
+ 		] ifFalse: [
+ 			tickThickness := 2.
+ 		].
+ 		self drawTickRadius: outerRadius * 0.63 length: tickLength thickness: tickThickness color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		self tickInnerLabel: tickLabel fontSize: tickLabelSize color: Color black centeredAt: dialCenter radius: (outerRadius * 0.63) angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		tickLabel := nil.
+ 		tick = 970 ifTrue:[tickLabel := 'Rain'].
+ 		tick = 1000 ifTrue:[tickLabel := 'Change'].
+ 		tick = 1030 ifTrue:[tickLabel := 'Fair'].
+ 		self tickInnerLabel: tickLabel fontSize: 24 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.5) angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		
+ 	].
+ 	self tickLabel: '"Hg'  fontSize: 36 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) angle: 180 onCanvas: canvas.
+ 	
+ 	self addMorph: (destForm magnify: destForm boundingBox by: 0.5 smoothing: 2) asMorph!

Item was added:
+ ----- Method: BarometerMorph>>doubleClick: (in category 'initialize-release') -----
+ doubleClick: evt
+ 	"the user has just tapped on the glass of the barometer, so move the priorPressureIndicator to match the current value"
+ 	priorPressureIndicator rotationDegrees: needleMorph rotationDegrees!

Item was added:
+ ----- Method: BarometerMorph>>handlesMouseDown: (in category 'initialize-release') -----
+ handlesMouseDown: evt
+ 	^true!

Item was added:
+ ----- Method: BarometerMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ 	"assemble a nice barometer morph. The background is an ImageMorph with scale/dial drawn with code adapted from a generous donation of time and effort by Bob Arning; similarly for the needle"
+ 	| pointerMorph |
+ 
+ 	super initialize.
+ 	"set up as a barometer type display; running clockwise with increasing values.
+ 	A decent range for a barometer is 950mB to 1050mB; it covers most plausible weather and matches decently with an additional inches-of-Hg scale going from 28 to 31.
+ 	28in. -> 948mB and 31in. -> 1050 (to enough accuracy for a screen based widget) so we need a small tweak at the lower end of the dial. If we aim initially for 150deg each side of north we have 3deg per milliBar; to accomodate the extra 2mB we can add 6deg at the low end, which makes 1000mB sit nicely at due north.
+ 	So we will use angles of -156 to 150 and values of 948 to 1050 as our limits."
+ 
+ 	self startAngle: -156 stopAngle: 150;
+ 			startValue: 948 stopValue: 1050.
+ 	self extent: 200 at 200; color: Color transparent; borderWidth: 0.
+ 	dialCenter := self center.
+ 
+ 	"build the dial background. This is amazingly complex to think about programmatically; this example is fairly hard-coded by hand but somebody out there almost certainly has ideas about parameterizing this to amke a nice general utility"
+ 	self buildDial.
+ 
+ 	"build our fancy needle as an ImageMorph, set the position to horizontal centre and about 2/3 down so that it rotates about that point when inside the TransformationMorph"
+ 	pointerMorph := self fancyNeedleOfLength: (self height * 0.65) rounded.
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -0.65).
+ 
+ 	"we keep track of the TransformationMorph since that is what we have to rotate as the incoming pressure values change"
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	
+ 	"Add the simpler needle used to indicate the prior 'remembered' reading; we will make a click update it to the current value"
+ 	pointerMorph := self simpleNeedleOfLength: (self height * 0.35) rounded color: (Color r: 16rFF g: 16rD7 b: 16r0 range: 512).
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -1).
+ 	priorPressureIndicator :=  TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: priorPressureIndicator.
+ 	
+ 	"add a central near-to-gold colored dot. Because we just do."
+ 	self addMorph: (CircleMorph new extent: 20 at 20; color: (Color r: 16rFF g: 16rD7 b: 16r0 range: 256); center: dialCenter)
+ 	!

Item was added:
+ ----- Method: BarometerMorph>>mouseDown: (in category 'event handling') -----
+ mouseDown: evt 
+ 	"Do nothing upon mouse-down except inform the hand to watch for a  
+ 	double-click; wait until an ensuing click:, doubleClick:, or drag:  
+ 	message gets dispatched"
+ 	evt hand
+ 		waitForClicksOrDrag: self
+ 		event: evt
+ 		selectors: #( #click: #doubleClick: #doubleClickTimeout: #startDrag:)
+ 		threshold: HandMorph dragThreshold!

Item was added:
+ RotaryDialMorph subclass: #ClockDialMorph
+ 	instanceVariableNames: 'hourHandMorph'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Widgets'!
+ 
+ !ClockDialMorph commentStamp: 'tpr 6/29/2017 13:26' prior: 0!
+ A ClockDialMorph is a clock implemented as a rotary dial morph. The intersting part of this is having two needles that continuously rotate as opposed to the normal rule of having a single needle limited in range.
+ 
+ Instance Variables
+ 	hourHandMorph:		<Morph, typically wrapped ina a TransformationMorph>!

Item was added:
+ ----- Method: ClockDialMorph>>buildDial (in category 'dial drawing') -----
+ buildDial
+ 	"start by making a damn big Form, twice the size we want to end up with"
+ 	|outerRadius destForm canvas tickLabel tickLength beginAngle endAngle tickAngle maxTicks |
+ 	outerRadius := self height  - 1.
+ 	destForm := Form extent: self extent * 2 depth: 32.
+ 	(canvas := destForm getCanvas) fillOval: (0 at 0 extent: self extent * 2) color: Color white.
+ 	"outer ring"
+ 	self drawArcAt: destForm center radius: outerRadius thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	"inner ring"
+ 	self drawArcAt: destForm center radius: outerRadius * 0.97 thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	
+ 	"outer scale for degrees"
+ 	beginAngle := startAngle . 
+ 	endAngle := stopAngle.
+ 	
+ 	maxTicks := stopValue - startValue .
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	startValue to: stopValue do: [:tick|
+ 	tickLength := outerRadius * 0.07.
+ 		tickLabel := nil.
+ 		tick \\ 6 = 0 ifTrue:["tick every 6 degrees on the outer ring"
+ 			self drawTickRadius: outerRadius * 0.9 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		].
+ 		tick \\ 30 = 0 ifTrue: ["tick every 30 degrees on the inner ring"
+ 			self drawTickRadius: outerRadius * 0.83 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 			(tick \\ 30 = 0 and: [tick < 360]) ifTrue:["numbered ticks every 30 degrees, don't overwrite 0 with 360"
+ 				self tickInnerLabel: (tick // 30)  asString fontSize: 24 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.75) + tickLength angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas
+ 				]
+ 		]
+ 	].
+ 
+ 	self addMorph: (destForm magnify: destForm boundingBox by: 0.5 smoothing: 2) asMorph!

Item was added:
+ ----- Method: ClockDialMorph>>initialize (in category 'initialization') -----
+ initialize
+ 	"assemble a nice clock morph. The background is an ImageMorph with scale/dial drawn with code adapted from a generous donation of time and effort by Bob Arning; the minute needle is the inherited needleMorph and we added a new hourHandMorph. Both are simple rectangleMorphs"
+ 	| pointerMorph |
+ 
+ 	super initialize.
+ 
+ 	self startAngle: 0 stopAngle: 360;
+ 			startValue: 0 stopValue: 360.
+ 	self extent: 200 at 200; color: Color transparent; borderWidth: 0.
+ 	dialCenter := self center.
+ 
+ 	"build the dial background; basic clock with miute ticks and hour long-ticks + arabic numerals"
+ 	self buildDial.
+ 
+ 	pointerMorph := self basicNeedleOfLength: (self height * 0.45) rounded width: 4 color: Color red.
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -1).
+ 
+ 	"we keep track of the TransformationMorph since that is what we have to rotate"
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 
+ 	"additional neelde for the hours"
+ 	pointerMorph := self basicNeedleOfLength: (self height * 0.35) rounded width: 6 color: Color black.
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -1).
+ 
+ 	"we keep track of the TransformationMorph since that is what we have to rotate"
+ 	hourHandMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: hourHandMorph.
+ 		
+ 	"add a central colored dot. Because we just do."
+ 	self addMorph: (CircleMorph new extent: 8 at 8; color: Color red twiceDarker; center: dialCenter)
+ 	!

Item was added:
+ ----- Method: ClockDialMorph>>setTime: (in category 'updating') -----
+ setTime: aTime
+ 
+ 	needleMorph rotationDegrees: aTime minutes * 6 + (aTime seconds / 10).
+ 	hourHandMorph rotationDegrees: (aTime hours * 30) + (aTime minutes / 2)!

Item was added:
+ ----- Method: ClockDialMorph>>step (in category 'stepping and presenter') -----
+ step
+ 	self setTime: Time now!

Item was added:
+ ----- Method: ClockDialMorph>>stepTime (in category 'stepping and presenter') -----
+ stepTime
+ 	^5000!

Item was added:
+ RotaryDialMorph subclass: #CompassDialMorph
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Widgets'!
+ 
+ !CompassDialMorph commentStamp: 'tpr 4/14/2017 13:21' prior: 0!
+ A CompassDialMorph shows a navigation compass. Unusually for most dials it has a full 360 degree span.!

Item was added:
+ ----- Method: CompassDialMorph>>basicNeedleOfLength:width:color: (in category 'needle graphics') -----
+ basicNeedleOfLength: nLength width: nWidth color: aColor
+ 	"make a really trivial needle as a colored rhombus"
+ 	| fancy |
+     
+ 	fancy := Form extent: nWidth at nLength depth: 32.
+ 	fancy fillColor: Color transparent.
+ 	fancy getCanvas asBalloonCanvas
+ 		aaLevel: 4;
+ 		drawPolygon: (Array with: (nWidth/ 2)@0 with: (nWidth)@( nLength / 2)  with:0@(nLength / 2) with: (nWidth/ 2)@0) fillStyle: aColor borderWidth: 1 borderColor: Color black;
+ 		drawPolygon: (Array with: (nWidth)@( nLength / 2) with: (nWidth/ 2)@(nLength) with:0@(nLength / 2)  with: (nWidth)@( nLength / 2)) fillStyle: Color black borderWidth: 0 borderColor: Color black.
+ 
+ 	^fancy asMorph.
+ !

Item was added:
+ ----- Method: CompassDialMorph>>buildDial (in category 'dial drawing') -----
+ buildDial
+ 	"start by making a damn big Form, twice the size we want to end up with"
+ 	|outerRadius destForm canvas tickLabel tickLength beginAngle endAngle tickAngle maxTicks |
+ 	outerRadius := self height  - 1.
+ 	destForm := Form extent: self extent * 2 depth: 32.
+ 	(canvas := destForm getCanvas) fillOval: (0 at 0 extent: self extent * 2) color: Color white.
+ 	"outer ring"
+ 	self drawArcAt: destForm center radius: outerRadius thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	"inner ring"
+ 	self drawArcAt: destForm center radius: outerRadius * 0.97 thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	
+ 	"outer scale for degrees"
+ 	beginAngle := startAngle . 
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.9 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.83 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.55 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	"We use a simple % range, just one scale"
+ 	maxTicks := stopValue - startValue .
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	startValue to: stopValue do: [:tick|
+ 	tickLength := outerRadius * 0.07.
+ 		tickLabel := nil.
+ 		tick \\ 2 = 0 ifTrue:["tick every 2 degrees on the outer ring"
+ 			self drawTickRadius: outerRadius * 0.9 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		].
+ 		tick \\ 10 = 0 ifTrue: ["tick every 10 degrees on the inner ring"
+ 			self drawTickRadius: outerRadius * 0.83 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 			(tick \\ 30 = 0 and: [tick < 360]) ifTrue:["numbered ticks every 30 degrees, don't overwrite 0 with 360"
+ 				self tickInnerLabel: tick asString fontSize: 24 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.75) + tickLength angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas
+ 			]
+ 		].
+ 		(tick \\ 90 = 0 and: [tick < 360]) ifTrue:["Major cardianl at the full points"
+ 			tickLabel := { 'N'. 'E'. 'S'. 'W'. nil.} atWrap: tick // 90 +1.
+ 			self tickInnerLabel: tickLabel fontSize: 36 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.65) + tickLength angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas
+ 		].
+ 		(tick \\ 90 = 45 and: [tick < 360]) ifTrue:["minor cardinal at the half-points"
+ 			tickLabel := { 'NE'. 'SE'. 'SW'. 'NW'. nil.} atWrap: tick // 90 +1.
+ 			self tickInnerLabel: tickLabel fontSize: 30 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.48) + tickLength angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas
+ 		]		
+ 	].
+ 
+ 	self addMorph: (destForm magnify: destForm boundingBox by: 0.5 smoothing: 2) asMorph!

Item was added:
+ ----- Method: CompassDialMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ 	"assemble a nice compass morph. The background is an ImageMorph with scale/dial drawn with code adapted from a generous donation of time and effort by Bob Arning; similarly for the needle"
+ 	| pointerMorph |
+ 
+ 	super initialize.
+ 	"A compass runs from 0 deg to 360, clockwise. Traditional compass roses can be very ornate."
+ 
+ 	self startAngle: 0 stopAngle: 360;
+ 			startValue: 0 stopValue: 360.
+ 	self extent: 200 at 200; color: Color transparent; borderWidth: 0.
+ 	dialCenter := self center.
+ 
+ 	"build the dial background. This is amazingly complex to think about programmatically; this example is fairly hard-coded by hand but somebody out there almost certainly has ideas about parameterizing this to amke a nice general utility"
+ 	self buildDial.
+ 
+ 	"build our fancy needle as an ImageMorph, set the position to horizontal centre and about 2/3 down so that it rotates about that point when inside the TransformationMorph"
+ 	pointerMorph := self basicNeedleOfLength: (self height * 0.65) rounded width: 10 color: Color red.
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -0.5).
+ 
+ 	"we keep track of the TransformationMorph since that is what we have to rotate as the incoming pressure values change"
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 		
+ 	"add a central colored dot. Because we just do."
+ 	self addMorph: (CircleMorph new extent: 20 at 20; color: Color red twiceDarker; center: dialCenter)
+ 	!

Item was added:
+ RotaryDialMorph subclass: #HygrometerDialMorph
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Widgets'!
+ 
+ !HygrometerDialMorph commentStamp: 'tpr 4/14/2017 10:13' prior: 0!
+ A Hygrometer measures the relative humidity of the air; a HygrometerDialMorph provides a way to display the value of R.H.!

Item was added:
+ ----- Method: HygrometerDialMorph>>buildDial (in category 'dial drawing') -----
+ buildDial
+ 	"start by making a damn big Form, twice the size we want to end up with"
+ 	|outerRadius destForm canvas tickLabel tickLength beginAngle endAngle tickAngle tickLabelSize maxTicks |
+ 	outerRadius := self height  - 1.
+ 	destForm := Form extent: self extent * 2 depth: 32.
+ 	(canvas := destForm getCanvas) fillOval: (0 at 0 extent: self extent * 2) color: Color white.
+ 	"outer ring"
+ 	self drawArcAt: destForm center radius: outerRadius thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	"inner ring"
+ 	self drawArcAt: destForm center radius: outerRadius * 0.97 thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	
+ 	"just one scale for a hygrometer"
+ 	beginAngle := startAngle -360. "needs cleaning up about this"
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.8 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.73 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	"We use a simple % range, just one scale"
+ 	maxTicks := stopValue - startValue .
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	startValue to: stopValue do: [:tick|
+ 	tickLength := outerRadius * 0.07.
+ 		tickLabel := nil.
+ 		tick \\ 10 = 0 ifTrue: [
+ 			tickLabel := tick asString.
+ 			tickLabelSize := 24
+ 		] ifFalse: [
+ 			tick \\ 2 = 0 ifTrue:[
+ 				tickLabel := (tick \\ 10) asString.
+ 				tickLabelSize := 18
+ 			] ifFalse: [
+ 				tickLength := tickLength * 2
+ 			]
+ 		].
+ 		self drawTickRadius: outerRadius * 0.73 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		self tickLabel: tickLabel fontSize: tickLabelSize color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) + tickLength angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 	].
+ 
+ 	self tickLabel: '% R.H.'  fontSize: 36 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.53) angle: 180 onCanvas: canvas.
+ 	
+ 	self addMorph: (destForm magnify: destForm boundingBox by: 0.5 smoothing: 2) asMorph!

Item was added:
+ ----- Method: HygrometerDialMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ 	"Build a hygrometer. The background is an ImageMorph showing a dial derived from the same general principles as the BarometerMorph. "
+ 	| pointerMorph |
+ 	super initialize.
+ 	
+ 	self startAngle: -140 stopAngle: 140;
+ 		startValue: 25 stopValue: 100.
+ 	self extent: 200 at 200; color: Color transparent; borderWidth: 0.
+ 	dialCenter := self center.
+ 	
+ 	self buildDial.
+ 
+ 	"build our fancy needle as an ImageMorph, set the position to horizontal centre and about 2/3 down so that it rotates about that point when inside the TransformationMorph"
+ 	pointerMorph := self fancyNeedleOfLength: (self height * 0.65) rounded.
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -0.65).
+ 
+ 	"we keep track of the TransformationMorph since that is what we have to rotate as the incoming pressure values change"
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 
+ 	"add a central colored dot. Because we just do."
+ 	self addMorph: (CircleMorph new extent: 20 at 20; color: Color black; center: dialCenter)
+ !

Item was added:
+ Morph subclass: #RotaryDialMorph
+ 	instanceVariableNames: 'startAngle stopAngle startValue stopValue needleMorph needleRotationCenter dialCenter currentValue'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Widgets'!
+ 
+ !RotaryDialMorph commentStamp: 'tpr 4/13/2017 16:58' prior: 0!
+ RotaryDialMorph is the beginnings of a suite of morphs to display values in a round dial manner. Things like pressure, speed, time, voltage etc are al well absorbed from a rotary display.
+ 
+ Instance Variables
+ 	dialCenter:		<Point> - usuall the centre of the dial but consider VU meters where the pivot is pretty much at an edge.
+ 	needleMorph:		<TransformationMorph> - wrapped around the morphs that make up the value indicating needle. This might a simple rectanglemorph, a composite like an ArrowMorph, an ImageMorph , whatever.
+ 	startAngle:		<Number> - the start & stop angles are given in degrees from vertical up; although this causes much fun in working out the geometry it is much easier to think of a barometer going from -150 to +150 than  -4.1887902047863905 to  1.0471975511965976 radians. The stopAngle needs to be further clockwise than the startAngle. 
+ 	startValue:		<Number> - the start & stopValues tell us what input data we must handle. It is possible to have the stopValue smaller than the startValue and effectively have the needle move backwards. This can be useful for dial where the pivot is at the top and the needle waggles around at the bottom.
+ 	stopAngle:		<Number>
+ 	stopValue:		<Number>
+ !

Item was added:
+ ----- Method: RotaryDialMorph>>allaroundometer (in category 'examples') -----
+ allaroundometer
+ 	"set up as an all-round type display like a clock or compass"
+ 	"RotaryDialMorph new allaroundometer openInWorld"
+ 	| pointerMorph |
+ 	self startAngle: 0 stopAngle: 360;
+ 		startValue: 0 stopValue: 1.
+ 	self extent: 200 at 200;
+ 		color: Color transparent.
+ 	dialCenter := self center.
+ 	self addMorph: (CircleMorph new extent: self extent).
+ 	pointerMorph := LineMorph from: 0 at 0 to: 0@ (self height // 2) color: Color red width: 2.
+  	pointerMorph bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self inputValue: 0.25
+ 
+ 	!

Item was added:
+ ----- Method: RotaryDialMorph>>backwardsometer (in category 'examples') -----
+ backwardsometer
+ 	"set up as a backwards type display, ie +1 to left, -1 to right"
+ 	"RotaryDialMorph new backwardsometer openInWorld"
+ 	| pointerMorph |
+ 	self startAngle: -90 stopAngle: 90;
+ 		startValue: 1 stopValue: -1.
+ 	self extent: 200 at 200;
+ 		color: Color transparent.
+ 	dialCenter := self center.
+ 
+ 	self addMorph: (CircleMorph new extent: self extent).
+ 	pointerMorph := LineMorph from: 0 at 0 to: 0@ (self height // 2) color: Color red width: 2.
+  	pointerMorph bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self inputValue: 0
+ 
+ 
+ 	!

Item was added:
+ ----- Method: RotaryDialMorph>>backwardsupsidedownometer (in category 'examples') -----
+ backwardsupsidedownometer
+ 	"set up as upsidedown backwards type display, ie -1 to left, 1 to right"
+ 	"RotaryDialMorph new backwardsupsidedownometer openInWorld"
+ 	| pointerMorph |
+ 	self startAngle: 110 stopAngle: -110;
+ 		startValue: -1 stopValue: 1.
+ 	self extent: 200 at 200;
+ 		color: Color transparent.
+ 	dialCenter := self center.
+ 
+ 	self addMorph: (CircleMorph new extent: self extent).
+ 	pointerMorph := LineMorph from: 0 at 0 to: 0@ (self height // 2) color: Color blue width: 2.
+  	pointerMorph bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self inputValue: 0
+ 
+ 	!

Item was added:
+ ----- Method: RotaryDialMorph>>basicNeedleOfLength:width:color: (in category 'needle graphics') -----
+ basicNeedleOfLength: nLength width: nWidth color: aColor
+ 	"make a really trivial needle as a colored rectangle"
+ 	^RectangleMorph new extent: nWidth @ nLength; color: aColor; borderWidth: 1!

Item was added:
+ ----- Method: RotaryDialMorph>>basicometer (in category 'examples') -----
+ basicometer
+ 	"set up as a forwards type display, ie 1 to left, +1 to right"
+ 	"RotaryDialMorph new basicometer openInWorld"
+ 	| pointerMorph |
+ 	self startAngle: -90 stopAngle: 90;
+ 		startValue: -1 stopValue: 1.
+ 	self extent: 200 at 200;
+ 		color: Color transparent.
+ 	dialCenter := self center.
+ 
+ 	self addMorph: (CircleMorph new extent: self extent).
+ 	pointerMorph := LineMorph from: 0 at 0 to: 0@ (self height // 2) color: Color red width: 2.
+  	pointerMorph bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self inputValue: 0
+ 
+ 
+ 	!

Item was added:
+ ----- Method: RotaryDialMorph>>buildDial (in category 'dial drawing') -----
+ buildDial
+ 	"attempt a plausible default dial"
+ 	|outerRadius destForm canvas tickLabel tickLength beginAngle endAngle tickAngle tickLabelSize maxTicks |
+ 	outerRadius := self height  - 1.
+ 	destForm := Form extent: self extent * 2 depth: 32.
+ 	(canvas := destForm getCanvas) fillOval: (0 at 0 extent: self extent * 2) color: Color white.
+ 	"outer ring"
+ 	self drawArcAt: destForm center radius: outerRadius thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	
+ 	beginAngle := startAngle -360. "needs cleaning up about this"
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.8 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.73 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	"Since this is a wild-guess default we'll try having 1 tick per integer value"
+ 	maxTicks := stopValue - startValue.
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 		tickLength := outerRadius * 0.07.
+ 	startValue to: stopValue do: [:tick|
+ 		tickLabel := nil.
+ 		tickLabel := tick asString.
+ 		tickLabelSize := 24.
+ 		self drawTickRadius: outerRadius * 0.73 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		"self tickLabel1."
+ 		self tickLabel: tickLabel fontSize: tickLabelSize color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) + tickLength angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 	].
+ 
+ 	self addMorph: (destForm magnify: destForm boundingBox by: 0.5 smoothing: 2) asMorph!

Item was added:
+ ----- Method: RotaryDialMorph>>colorfulBasicometer (in category 'examples') -----
+ colorfulBasicometer
+ 	"set up as a forwards type display, ie 1 to left, +1 to right"
+ 	"RotaryDialMorph new colorfulBasicometer openInWorld"
+ 	| pointerMorph textM |
+ 	self startAngle: -120 stopAngle: 120;
+ 		startValue: -1 stopValue: 1.
+ 	self extent: 300 at 300;
+ 		color: GradientFillStyle sample.
+ 	dialCenter := self center.
+ 
+ 	self addMorph: (textM := TextMorph fancyPrototype).
+ 	textM extent: 250 at 30; contents: 'Wild colored RotaryDial HippieLand!!'; fontName: 'Darkmap DejuVu Sans' size: 22.
+ 	textM align: textM topCenter with:  self topCenter.
+ 	pointerMorph := CurveMorph new vertices: {0 at 0. -10@ -50. 10@ -100} color: Color yellow borderWidth: 5 borderColor: Color blue.
+ 	pointerMorph makeOpen; makeForwardArrow..
+  	pointerMorph bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self inputValue: 0
+ 
+ 
+ 	!

Item was added:
+ ----- Method: RotaryDialMorph>>drawArcAt:radius:thickness:color:beginAngle:endAngle:onForm: (in category 'dial drawing') -----
+ drawArcAt: arcCenter radius: arcRadius thickness: arcThickness color: arcColor beginAngle: beginAngle endAngle: endAngle onForm: dest
+ "angles clockwise from North in degrees; the endAngle must be clockwise of beginAngle.
+ To make life more fun we then convert to anti-clockwise-from-east radians for the geometry."
+ 
+ 	| angle lw2 stop step newPt c diff form rho cell endRho |
+    
+ 	form := Form extent: dest extent depth: 32.
+ 	lw2 := arcThickness * 0.5.
+ 	angle :=  (90 - endAngle) degreesToRadians.
+ 	stop := (90 - beginAngle) degreesToRadians min: angle + Float twoPi.
+ 	step := 0.9 / arcRadius.
+ 	[
+ 		rho := arcRadius - lw2 - 0.5.
+ 		endRho := arcRadius + lw2 + 0.5.
+ 		[rho <= endRho] whileTrue: [
+ 			cell := (rho * angle cos) rounded  @ (rho * angle sin) rounded negated.
+ 			newPt := arcCenter + cell.
+ 			diff := (cell r - arcRadius) abs.
+ 			c := diff <= lw2 ifTrue: [arcColor] ifFalse: [arcColor alpha: 1.0 - (diff - lw2)].
+ 			form colorAt: newPt put: c.
+ 			rho := rho + 0.5.
+ 		].
+ 		(angle := angle + step) <= stop
+ 	] whileTrue.
+ 	dest  getCanvas translucentImage: form at: 0 at 0.
+ !

Item was added:
+ ----- Method: RotaryDialMorph>>drawTickRadius:length:thickness:color:angle:onCanvas: (in category 'dial drawing') -----
+ drawTickRadius: radius length: length thickness: thickness color: color angle: angle  onCanvas: canvas
+ "angles clockwise from North in degrees"
+ 
+ 	| newPt cell pts rads |
+ 	rads := (90 -  angle) degreesToRadians.
+    	pts := {radius. radius + length + 0.5} collect: [ :rho |
+ 		cell := (rho * rads cos) rounded @ (rho * rads sin) rounded negated.
+ 		newPt := dialCenter * 2 + cell.
+ 	].
+ 	canvas line: pts first to: pts second width: thickness color: color
+ !

Item was added:
+ ----- Method: RotaryDialMorph>>fancyNeedleOfLength: (in category 'needle graphics') -----
+ fancyNeedleOfLength: aNumber
+ 	"we can make a fancy-schmancy barometer type needle with a curly arrow and moon-shaped tail and then scale it to a length" 
+ 	^self fancyNeedleOfLength: aNumber color: Color black!

Item was added:
+ ----- Method: RotaryDialMorph>>fancyNeedleOfLength:color: (in category 'needle graphics') -----
+ fancyNeedleOfLength: aNumber color: aColor
+ 	"we can make a fancy-schmancy barometer type needle with a curly arrow and moon-shaped tail and then scale it to a length" 
+ | fancy smaller |
+     
+ 	fancy := Form extent: 100 at 500 depth: 32.
+ 	fancy fillColor: Color white.
+ 	fancy getCanvas
+ 		fillOval: (5 at 405 extent: 90 at 90) color: aColor;
+ 		fillOval: (15 at 430 extent: 70 at 70) color: Color white;
+ 		fillRectangle: (20 at 40 extent: 60 at 60) color: aColor;
+ 		fillOval: (-348@ -200 extent: 400 at 400) color: Color white;
+ 		fillOval: (48@ -200 extent: 400 at 400) color: Color white;
+ 		fillRectangle: (48 at 10 extent: 4 at 400) color: aColor.
+ 	fancy replaceColor: Color white withColor: Color transparent.
+ 
+ 	smaller := fancy magnify: fancy boundingBox by: (aNumber / fancy boundingBox height) smoothing: 2.
+ 	^smaller asMorph.
+ !

Item was added:
+ ----- Method: RotaryDialMorph>>inputValue: (in category 'updating') -----
+ inputValue: aNumber 
+ 	"move the needleMorph to display the value; we clamp it to the range
+ 	[startValue, stopValue]"
+ 	| input newDegrees |
+ 	stopValue > startValue
+ 		ifTrue: [input := aNumber min: stopValue max: startValue]
+ 		ifFalse: [input := aNumber min: startValue max: stopValue].
+ 	currentValue := input.
+ 	newDegrees := currentValue - startValue / (stopValue - startValue) * ((stopAngle - startAngle)\\360) + startAngle.
+ 	needleMorph rotationDegrees: newDegrees \\ 360!

Item was added:
+ ----- Method: RotaryDialMorph>>simpleNeedleOfLength: (in category 'needle graphics') -----
+ simpleNeedleOfLength: aNumber
+ 
+ 	^self simpleNeedleOfLength: aNumber color: Color black!

Item was added:
+ ----- Method: RotaryDialMorph>>simpleNeedleOfLength:color: (in category 'needle graphics') -----
+ simpleNeedleOfLength: aNumber color: aColor
+ 	"we can make a simpler type needle with a curly arrow and no tail and then scale it to a length" 
+ | fancy smaller |
+     
+ 	fancy := Form extent: 100 at 500 depth: 32.
+ 	fancy fillColor: Color white.
+ 	fancy getCanvas
+ 		fillRectangle: (20 at 40 extent: 60 at 60) color: aColor;
+ 		fillOval: (-348@ -200 extent: 400 at 400) color: Color white;
+ 		fillOval: (48@ -200 extent: 400 at 400) color: Color white;
+ 		fillRectangle: (48 at 10 extent: 4 at 490) color: aColor.
+ 	fancy replaceColor: Color white withColor: Color transparent.
+ 
+ 	smaller := fancy magnify: fancy boundingBox by: (aNumber / fancy boundingBox height) smoothing: 2.
+ 	^smaller asMorph.
+ !

Item was added:
+ ----- Method: RotaryDialMorph>>startAngle:stopAngle: (in category 'accessing') -----
+ startAngle: angle1 stopAngle: angle2
+ 	"set the start and stop angles of the dial; we modulo them with 360 to keep things logical"
+ 	startAngle := angle1 \\ 360.
+ 	stopAngle := angle2 \\ 360.
+ 	
+ 	"if the two angles end up the same then we will guess that in fact the user wants a full-rotation rather than nothing. "
+ 	startAngle = stopAngle ifTrue:[
+ 		angle1 < angle2 ifTrue:[stopAngle := (startAngle +359.9) \\360].
+ 		angle2 < angle1 ifTrue:[stopAngle := (startAngle - 359.9) \\360]]
+ 	"if the input angles actually were the same then the user has made a mistake and we can't really solve it. Install a better user?"!

Item was added:
+ ----- Method: RotaryDialMorph>>startValue:stopValue: (in category 'accessing') -----
+ startValue: value1 stopValue: value2
+ 	"set the start and stop values for the dial readings. Note that they can be backwards to allow the needle to rotate counter clockwise for increasing inputs"
+ 	startValue := value1.
+ 	stopValue := value2!

Item was added:
+ ----- Method: RotaryDialMorph>>tickInnerLabel:fontSize:color:centeredAt:radius:angle:onCanvas: (in category 'dial drawing') -----
+ tickInnerLabel: aString fontSize: fSize color: aColor centeredAt: aPoint radius: radius angle: angle onCanvas: canvas
+ 	"draw the label string centered on the point radius from the centre point, at the angle. Long strings will almost certainly cause problems"
+ 	| cell font pos rads rho stringExtent f rot |
+ 	aString ifNil: [^self].
+ 	font := TextStyle default fontOfSize: fSize.
+ 	"draw the string and rotate it; we flip the angle to keep the letters kinda-sorta the right way up to read easily"
+ 	stringExtent := (StringMorph contents: aString font: font ) imageForm boundingBox extent.
+ 	f := Form extent: stringExtent depth: 32.
+ 	f getCanvas  drawString: aString in: (0 at 0 extent: stringExtent) font: font color: aColor.
+ 	(angle \\ 360 between: 90.5 and: 269.5) ifTrue:[
+ 		rot := angle - 180] ifFalse: [
+ 		rot := angle ].
+ 	f := f rotateBy: rot smoothing: 2.
+ 	
+ 	"the radius is reduced by a bit more than half the string height to fit it reasonably neatly inside the radius"
+ 	rho := radius - (stringExtent y /1.7).
+ 	rads := (90 - angle) degreesToRadians.
+ 	cell := (rho * rads cos) rounded @ (rho * rads sin) rounded negated.
+ 	pos := aPoint * 2 + cell - (f extent // 2).
+ 	canvas translucentImage: f at: pos!

Item was added:
+ ----- Method: RotaryDialMorph>>tickLabel:fontSize:color:centeredAt:radius:angle:onCanvas: (in category 'dial drawing') -----
+ tickLabel: aString fontSize: fSize color: aColor centeredAt: aPoint radius: radius angle: angle onCanvas: canvas
+ 	"draw the label string unrotated outside the radius centered on the centre point. We try to get the center of the string bounds on the relevant point but it may look odd for certain strings"
+ 	| cell font pos rads rho stringExtent |
+ 	aString ifNil: [^self].
+ 	
+ 	font := TextStyle default fontOfSize: fSize.
+ 	stringExtent := (StringMorph contents: aString font: font ) imageForm boundingBox extent.
+ 	rho := radius + (stringExtent r /2).
+ 	rads := (90 - angle) degreesToRadians.
+ 	cell := (rho * rads cos) rounded @ (rho * rads sin) rounded negated.
+ 	pos := aPoint * 2 + cell - (stringExtent // 2).
+ 	canvas drawString: aString in: (pos extent: stringExtent) font: font color: aColor!

Item was added:
+ ----- Method: RotaryDialMorph>>upsidedownometer (in category 'examples') -----
+ upsidedownometer
+ 	"set up as a forwards but upside-down type display, ie 1 to left, +1 to right"
+ 	"RotaryDialMorph new upsidedownometer openInWorld"
+ 	| pointerMorph |
+ 	self startAngle: 100 stopAngle: -100;
+ 		startValue: -1 stopValue: 1.
+ 	self extent: 200 at 200;
+ 		color: Color transparent.
+ 	dialCenter := self center.
+ 
+ 	self addMorph: (CircleMorph new extent: self extent).
+ 	pointerMorph := LineMorph from: 0 at 0 to: 0@ (self height // 2) color: Color red width: 2.
+  	pointerMorph bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self inputValue: 0
+ 
+ 
+ 	!

Item was added:
+ ----- Method: RotaryDialMorph>>vumeter (in category 'examples') -----
+ vumeter
+ 	"set up as a VU meter type display"
+ 	"RotaryDialMorph new vumeter openInWorld"
+ 	| pointerMorph |
+ 	self startAngle: 35 stopAngle: 145;
+ 			startValue: -10 stopValue: 10.
+ 	self extent: 100 at 200.
+ 	dialCenter := -60 at 100.
+ 	pointerMorph := RectangleMorph new extent: 4 at 150; color: Color black; bottomRight: 0 at 0.
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 	self addMorph: (CircleMorph new extent:  200 at 200; center: dialCenter).
+ 	self inputValue: 0.
+ 	self color: Color white; borderWidth: 3; borderColor: Color black; clipSubmorphs: true
+ 	
+ 	!

Item was added:
+ RotaryDialMorph subclass: #ThermometerDialMorph
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Widgets'!
+ 
+ !ThermometerDialMorph commentStamp: 'tpr 6/29/2017 13:29' prior: 0!
+ A ThermometerDialMorph is a rotary thermometer; the default is to set the range to typical outdoor temperatures but of course that can be altered with the normal #startValue:stopValue: message!

Item was added:
+ ----- Method: ThermometerDialMorph>>buildDial (in category 'dial drawing') -----
+ buildDial
+ 	"start by making a damn big Form, twice the size we want to end up with"
+ 	|outerRadius destForm canvas tickLabel tickLength beginAngle endAngle tickAngle tickLabelSize maxTicks |
+ 	outerRadius := self height  - 1.
+ 	destForm := Form extent: self extent * 2 depth: 32.
+ 	(canvas := destForm getCanvas) fillOval: (0 at 0 extent: self extent * 2) color: Color white.
+ 	"outer ring"
+ 	self drawArcAt: destForm center radius: outerRadius thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	"inner ring"
+ 	self drawArcAt: destForm center radius: outerRadius * 0.97 thickness: 1 color: Color black beginAngle: 0 endAngle: 360 onForm: destForm.
+ 	
+ 	"outer scale for Fahrenheit"
+ 	beginAngle := startAngle -360. "needs cleaning up about this"
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.8 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.73 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	"The Fahrenheit values of our range are 
+ 	startValue -5/ 5 * 9 + 32 ->23
+ 	stopValue 30 / 5 * 9 + 32 -> 86
+ 	which is very conveniently integral but sadly it corresponds to 4.44444 deg per ... degree."
+ 	maxTicks := stopValue - startValue  / 5 * 9 .
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	(startValue / 5 * 9 +32) to: (stopValue / 5 * 9 +32) do: [:tick|
+ 	tickLength := outerRadius * 0.07.
+ 		tickLabel := nil.
+ 		tick \\ 10 = 0 ifTrue: [
+ 			tickLabel := tick asString.
+ 			tickLabelSize := 24
+ 		] ifFalse: [
+ 			tick \\ 2 = 0 ifTrue:[
+ 				tickLabel := (tick \\ 10) asString.
+ 				tickLabelSize := 18
+ 			] ifFalse: [
+ 				tickLength := tickLength * 2
+ 			]
+ 		].
+ 		self drawTickRadius: outerRadius * 0.73 length: tickLength thickness: 2 color: Color black angle:  beginAngle + (tick - (startValue / 5 * 9 +32) * tickAngle) onCanvas: canvas.
+ 		self tickLabel: tickLabel fontSize: tickLabelSize color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) + tickLength angle: beginAngle + (tick - (startValue / 5 * 9 +32) * tickAngle) onCanvas: canvas.
+ 	].
+ 
+ 	self tickInnerLabel: (String with: (Unicode value: 16rB0) with: $C) fontSize: 36 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) angle: 180 onCanvas: canvas.
+ 	
+ 	"inner scale for Celsius"
+ 	beginAngle := startAngle -360. "needs cleaning up about this"
+ 	endAngle := stopAngle.
+ 	
+ 	self drawArcAt: destForm center radius: outerRadius * 0.71 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	self drawArcAt: destForm center radius: outerRadius * 0.63 thickness: 1 color: Color black beginAngle:beginAngle endAngle: stopAngle onForm: destForm.
+ 	maxTicks := stopValue - startValue.
+ 	tickAngle := endAngle - beginAngle / maxTicks.
+ 	tickLength := outerRadius * 0.07.
+ 	startValue to: stopValue do: [ :tick ||tickThickness|
+ 		tickLabel := nil.
+ 		tick \\ 5 = 0 ifTrue: [
+ 			tickLabelSize := 20.
+ 			tickThickness := 3.
+ 			tickLabel :=  tick asString.
+ 		] ifFalse: [
+ 			tickThickness := 2.
+ 		].
+ 		self drawTickRadius: outerRadius * 0.63 length: tickLength thickness: tickThickness color: Color black angle:  beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 		self tickInnerLabel: tickLabel fontSize: tickLabelSize color: Color black centeredAt: dialCenter radius: (outerRadius * 0.63) angle: beginAngle + (tick - startValue * tickAngle) onCanvas: canvas.
+ 
+ 	].
+ 
+ 	self tickLabel: (String with: (Unicode value: 16rB0) with: $F)  fontSize: 36 color: Color black centeredAt: dialCenter radius: (outerRadius * 0.73) angle: 180 onCanvas: canvas.
+ 	
+ 	self addMorph: (destForm magnify: destForm boundingBox by: 0.5 smoothing: 2) asMorph!

Item was added:
+ ----- Method: ThermometerDialMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ 	"Build a thermometer. The background is an ImageMorph showing a dial derived from the same general principles as the BarometerMorph. 
+ 	The temperature scale is fixed for now at -5C to 30C but ought to be parameterised someday. We'll have the Celcius scale as the inner and a conversion to Fahrenheit as the outer"
+ 	| pointerMorph |
+ 	super initialize.
+ 	
+ 	self startAngle: -140 stopAngle: 140;
+ 		startValue: -5 stopValue: 30.
+ 	self extent: 200 at 200; color: Color transparent; borderWidth: 0.
+ 	dialCenter := self center.
+ 	
+ 	self buildDial.
+ 
+ 	"build our fancy needle as an ImageMorph, set the position to horizontal centre and about 2/3 down so that it rotates about that point when inside the TransformationMorph"
+ 	pointerMorph := self fancyNeedleOfLength: (self height * 0.65) rounded.
+  	pointerMorph position: pointerMorph extent * ( -0.5@ -0.65).
+ 
+ 	"we keep track of the TransformationMorph since that is what we have to rotate as the incoming pressure values change"
+ 	needleMorph := TransformationMorph new position: dialCenter; addMorph: pointerMorph.
+ 	self addMorph: needleMorph.
+ 
+ 	"add a central colored dot. Because we just do."
+ 	self addMorph: (CircleMorph new extent: 20 at 20; color: Color black; center: dialCenter)
+ !




More information about the Packages mailing list