Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Jim Bungles Check Box
Last updated at 1:06 pm UTC on 16 January 2006
So, here's a lesson I learned. I threw some code up against a wall and looked to see if it stuck. My first implementation of the CheckBoxMorph didn't stick. I originally thought that I would just have this big transparent composite Morph that contained the check box and label.

However, the check box rectangle gets its raised borders from the color of its owner, in this case the CheckBoxMorph. So I colored the CheckBoxMorph with the color of the check box, and figured I'd set the CheckBoxMorph to be transparent only when I was drawing the CheckBoxMorph itself.

Here's the suspicious characters in the play:

drawOn: aCanvas
	| savedColor |
	" The check box rectangle gets its border color from us, so we keep our color instance var set to the appropriate color. However, we want to appear to be transparent, so we 'hide' by becoming the color transparent when we draw ourselves. " 
	savedColor _ color.
	color _ Color transparent.
	super drawOn: aCanvas.
	color _ savedColor.

drawSubmorphsOn: aCanvas
	"Display submorphs back to front"
	| rect |
	submorphs
		reverseDo: [:morph | (morph isKindOf: RectangleMorph)
				ifTrue: 
					[" This is the checkbox "
					rect _ morph bounds.
					" frame the check box with a black rectangle "
					aCanvas frameRectangle: (rect insetBy: -1 @ -1)
						color: Color black.
					aCanvas fullDrawMorph: morph]
				ifFalse: [aCanvas fullDrawMorph: morph]]

extent: aPoint

	bounds extent = aPoint ifFalse: [
		self changed.
		bounds _ bounds topLeft extent: aPoint.
		self layoutChanged.
		self changed].

In retrospect, the drawSubmorphsOn: method looked pretty fishy

Here's what I originally wrote.

There is a tricky part in the drawOn: method. I muck about with the color, set it to transparent, draw the Morph, and then restore the color. This is a composite Morph, so I'm not really interested in displaying it. I want the color to be transparent. I draw in a transparent color to make sure that any underlying Morphs are drawn correctly. The reason that the CheckButtonMorph has a color in the first place is because that is where the RectangleMorph that represents the check box gets its color from for drawing the 'raised' border. Nasty and not obvious, but now it's out in the open.

Here's where I got busted:

Err, that's an ugly hack, and it doesn't work. Try moving your button with the brown handle, or enlarge it and grab ...
  1. Drawing should only be done in drawOn:. So delete drawSubmorphsOn: and change drawOn: to
    aCanvas fillRectangle: (self xBox bounds expandBy: 1@1) color: Color black.
    That way you don't need to muck with the color at all. If you don't want something get drawn, don't draw it.
  2. The bounds should enclose all drawing a morph does. So change the line in extent: to
    bounds := bounds topLeft extent: (aPoint max: self xBox extent + (2@2)).
  3. A morph must tell what areas still need to get drawn. So implement areasRemainingToFill: aRectangle like
    ^ aRectangle areasOutside: (self xBox bounds expandBy: 1@1).
You also have to move the #setDefaultLabel send to the bottom of initialize so the xBox gets initialized first. (Vanessa Freudenberg)


Right then. Here's what I learned. First, don't mess with your submorphs drawing. Draw only in drawOn: I also learned about the #areasRemainingToFill: message, which handles that 'transparent' idea I was thinking about. In retrospect, the only thing that the CheckBoxMorph itself does is draw a rectangle around the check box, so that is what it is responsible for. Thanks Bert for going thru and fixing the code.



Jim Benson
jb@speed.net