Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Eye Candy
Last updated at 12:56 pm UTC on 10 November 2015
Dude, a topic known as Eye Candy demands screenshots.



So there I was,

Lions on the left of me. Tigers on the right. Bears straight ahead. All I had was with my trusty laptop, with Morphic painting my screen. Lions, Tiger, Bears, pretty much sums it up.

A minute passed. Then two more, but I wasn't afraid. I had the power of Morphic at my fingertips.

I heard a voice. "The zoo will be closing in five minutes." I packed up my things and went home.

Groan. So after hearing the worst story in worst story history, you're saying to yourself, "What does that have to do with anything?"

Things are not always as they seem. So it is with our friend the Morph.

A few chapters ago I was talking about how Morphs look, and that the entire interface of Morphic being a collection of Morphs. I'm also sure that you've noticed that these collections of Morphs look nothing like the user interfaces that you are used to seeing, like say post 1984. You bring your friends over telling them how great Morphic is, you show them the screen... and they look at each other with quizzical looks. They're thinking to themselves, "I really hate to have an intervention for a person who used to be so mentally sharp, a person with their whole lives in front of them, but this demands it".

It's OK, many people have had the same reaction. Let me tell you another secret. Morphic can change looks and colors faster than a chameleon under the neon lights of Las Vegas! I'll give you a quick history of the 3D look. This dude, Leon Battista Alberti, writes a book called "On Painting" in 1436. The father of Renaissance perspective, Alberti laid out the system for creating pictures that assumed one point of observation. Just like any time you look at a picture on a piece of paper or computer screen. This system has formed the basis for every painting, drawing, or picture done since.

This development basically sets the world on its ear and effects everything from painting, to architecture, to the way wars are fought, even gardening! The theory was as mind expanding to the time as was Einstein's theory of relativity to ours. Anyway, some time passes. A couple of good bits, like Michelangelo lies on his back and paints the Sistine Chapel ceiling using the power of perspective to stress the relationships of all of the characters. Van Gogh cuts off his ear. Picasso uses perspective in a disturbing manner. Then the folks who brought you Smalltalk at PARC invent the overlapping display windows which are so widely imitated today. These windows appear to be different documents lying on top of each other, giving the perspective that your desktop is 3 dimensional. I hope I didn't go to far into depth on this subject. I just hate when history drags on like that.

After Steve Jobs sneaks in and steals the WIMP display from Xerox (in a version of what I call letting the rabbits guard the lettuce), some marketing guy decides he needs to differentiate his product from others on the market [We won't make fun of marketing guys here, that's to easy of a target. So easy in fact it has spawned a whole industry, see Dilbert et. al. ]. He tells the engineers, "Can't you make these screen thingies better looking?", and runs off to his three martini lunch. When he returns from lunch three days later, some engineer has figured out that if you put white, gray and black together just right, it makes a rectangle on the screen look just like a "3D" button. People throw some color on it, and BAM! we're into some UI nightmare the likes the world has never seen before. [ Jecel Assumpcao Jr. remembers it differently. Jecel is smart, you should probably believe that story: Eye Candy. After reading that, you can probably see that the 3D look is Morphics birthright! ]

You're thinking, "My, what is he off on now?" I'm telling you all of these things that make the interfaces different from what Morphic presents to you are cosmetic, and that you can easily have Morphic imitate them. Let's go over an example right now.

Remember our LaunchButtonMorph? If you look at one closely, you'll see that the borders of the button are of a different color than the field, which gives the illusion that light is hitting the button from the upper left hand corner of the window. This particular version of "3D" button is used for things like toolbar icons, and palette icons. Buttons with text in them now usually have a "warmer" look.

When folks started using color in the interface, someone came up with the idea of using color to make the button look like it was three dimensional on the screen. So how do they do that?

The trick is to use a gradient. A gradient is a ramp of colors, which appears to smear and blend the colors between one point to the next. In or example, the gradient is vertically oriented going from a light color to a darker color. Some folks just draw the gradient directly to the screen. Other folks store the gradient as a bitmap then replicate it as needed. It's the age old computer trade off, speed versus storage. We're going to draw it straight to the screen, because we trust that Mr. Moore is right.

Time to whip out our Morphic bag of tricks. We know that we need a gradient of some sort. We also notice there is something called a "GradientFillMorph" in the image, a natural combination right?

Not exactly. When I was bungling trying to put this material together, I added a GradientFillMorph to the LaunchButtonMorph. It looked right, but it seemed to draw slowly. That was a problem, because we are going to use this in a user interface object, an application which demands speed. Stumped, I asked the gurus on the Squeak list for some help.

BobArning and Vanessa Freudenberg pointed out some of the things that slowed the GradientFillMorph code down. More importantly, they steered me towards the righteous path. These men are Morphic gods, and should be worshipped as such.

It turns out, a basic Morph has something called fillStyles. This might surprise you, but these fillStyles determine which style a Morph is filled in. We already know about a SolidFillStyle, which is a color. The other fill styles are OrientedFillStyles. OrientedFillStyles is the abstract class from which BitmapFillStyle and GradientFillStyle are derived. A BitmapFillStyle is used to fill a Morph with a bitmap (Form). A GradientFillStyle comes in a couple of flavors. You can have a radial fill or a gradient fill. We're interested in the gradient fill for our purposes.

File in the changeset: gradientbuttonmorph.st this needs some changes for 3.6, see bottom of page

SimpleButtonMorph subclass: #GradientButtonMorph
	instanceVariableNames: 'topColor bottomColor reverseFillStyle saveFill '
	classVariableNames: 'DelayTime '
	poolDictionaries: ''
	category: 'Morphic Documentation example'


cacheFillStyle
	| fill |
	"Make receiver use a solid fill style (e.g., a simple color)"
	fill _ GradientFillStyle ramp: {0.0 -> topColor. 1.0 -> bottomColor}.
	fill	origin: self topLeft ;
		direction: 0 @ self bounds extent y ;
		normal: self bounds extent x @ 0 ;
		radial: false.
	self fillStyle: fill.
	" reverse ramps the colors in the opposite direction "
	reverseFillStyle _ fill copy.
	reverseFillStyle colorRamp: {0.0 -> bottomColor. 1.0 -> topColor}.

gradientColor: theColor

	topColor _ theColor.
	bottomColor _  (theColor mixed: 0.5 with: Color black).
	self cacheFillStyle.
	self changed.


gradientColor: color1 bottomColor: color2

	topColor _ color1.
	bottomColor _ color2.
	self cacheFillStyle.
	self changed.! !


labelColor: theColor
	| sm |
	(sm _ self findA: StringMorph)
		ifNotNil: [sm color: theColor.].

mouseDown: evt
	self cacheFillStyle.
	saveFill _ self fillStyle.
	self fillStyle: reverseFillStyle.
	self changed.
	self refreshWorld.

mouseMove: evt
	actWhen == #buttonDown ifTrue: [^ self].
	(self containsPoint: evt cursorPoint)
		ifTrue: 
			[self fillStyle = reverseFillStyle
				ifFalse: 
					[self fillStyle: reverseFillStyle.
					self changed.
					self world displayWorld].
			(actWhen == #whilePressed and: [evt anyButtonPressed])
				ifTrue: 
					[self doButtonAction.
					evt hand noteSignificantEvent: evt]]
		ifFalse: [self fillStyle = saveFill
				ifFalse: 
					[self fillStyle: saveFill.
					self changed.
					self world displayWorld]]! !

mouseUp: evt
	" flash the button three times when the button is released"
	| delay time elapsed |

	(self containsPoint: evt cursorPoint)
		ifTrue: [1 to: 3 do: 
				[:i | 
				time _ Time millisecondClockValue.
				self fillStyle: saveFill.
				self changed.
				self refreshWorld.
				elapsed _ Time millisecondClockValue - time.
				elapsed > 0
					ifTrue: 
						[delay _ Delay forMilliseconds: (elapsed min: DelayTime).
						delay wait].
				self fillStyle: reverseFillStyle.
				self changed.
				self refreshWorld.
				elapsed > 0
					ifTrue: 
						[delay wait]]].
	self fillStyle: saveFill.
	self changed.
	self refreshWorld.
	(actWhen == #buttonUp and: [self containsPoint: evt cursorPoint])
		ifTrue: [self doButtonAction]

layoutChanged
	| sm |

	super layoutChanged.
	( sm _ self findA: StringMorph )
		ifNotNil: [ 	sm position: self center - (sm extent // 2). ].

	self cacheFillStyle.

position: thePoint
	super position: thePoint.
	self cacheFillStyle.

setDefaultLabel
	self label: 'Untitled'.

initialize

	super initialize.
	self useSquareCorners.
	bounds _ 0 @ 0 extent: 96 @ ( self class buttonHeight) .
	self setDefaultLabel.
	self borderColor: #raised.
	self borderWidth: 1.
	self useGradientFill.
	topColor _ Color lightGray.
	bottomColor _ Color black.
	self cacheFillStyle.


label: aString

	| oldLabel m |
	(oldLabel _ self findA: StringMorph)
		ifNotNil: [oldLabel delete].
	m _ StringMorph contents: aString font: TextStyle defaultFont.
	m position: self center - (m extent // 2).
	self addMorph: m.
	m lock

"– – – – – – – – – – – – – – – – – – "

GradientButtonMorph class
instanceVariableNames: ''

initialize
	DelayTime _ 60.

buttonHeight
	^ 22


GradientButtonMorph initialize



Boy, that seems like a lot of code. A couple of notes, GradientButtonMorph is a subclass of SimpleButtonMorph, so we know it behaves like a simple button. We notice in the instance #initialize a line that reads

self useGradientFill.

That line tells the Morph to use a gradient fill style. The rest of the code basically mucks about trying to make sure that the button looks right. Especially when you press it. Execute this in a Workspace:

bo := GradientButtonMorph new openInWorld.

A kinder, warmer, gentler looking button pops up on the screen. Press it, the colors do a little dance. Doesn't that make you feel warm and fuzzy inside? It shouldn't, it's just some bits on the display for heavens sake. But it seems a little hard to read the button title. Let's change that:

bo labelColor: ( Color white ).

Notice how much the look of the button changes just by changing the color of the label. Try it also with a very lightGray color. It appears as though the label is etched into the button. Just a little optical illusion, and part of the interface look bag of tricks.

You can also:

bo useRoundedCorners

to get the softer feel of the rounded button. Also, we can change to color of the gradient fill:

bo gradientColor: ( Color yellow ).

This uses the color that you send it as the top color of the button, and uses a darker version of the same color as the bottom. You can also set the top and bottom colors of the gradient:

bo gradientColor: ( Color blue ) bottomColor: ( Color black )

Play around with those a little until you do something really annoying like:

bo gradientColor: ( Color green ) bottomColor: ( Color yellow ).

Now you too are ready to be an interface designer.

Notice that when you press the button, the gradient reverses direction. That's our friend visual feedback cue trying to help us along. This effect is done by creating a gradient ramp in the opposite direction of the original, and displaying it on the screen. Also, when we release the button, we get that same 3 times flash that we did with the LaunchButtonMorph to tell the user that something significant has happened.




I awoke early one cold February day and decided to go ice fishing. Usually I don't go for that kind of thing, but it makes for a great intro to this story. I bundled up, put my gloves on and went down to the local pond. I settled down on my stool, with my hot thermos bottle to spend a relaxing day with nature. I started cutting a hole in the ice, and threw my line in. I sat back with my hot drink and started relaxing. Suddenly I heard a deep voice say, "There are no fish under the ice."

Now it hand been a long night before, and maybe I wasn't at my sharpest. I looked around, but I thought I must be hearing things. The morning passed uneventfully, not even one nibble. I broke out my lunch, and the middle of my baloney sandwich I heard, "There are no fish under the ice". Hmm, maybe this is a message from God, divine intervention. Either that or very clever fish.

Another hour passes, not one bite. How strange I thought, I've been sitting out on this ice for 6 hours and not one single bite. On top of this I keep hearing strange voices. Then it happens again!

"There are no fish under the ice"

I'm starting to worry at this point. I've been out here almost 8 hours, I'm cold and I MUST be hearing things. Another 20 minutes pass.

I heard a voice say, "The skating rink will be closing in five minutes." I packed up my things and went home.

And you thought the first story was bad.





Jim Benson
jb@speed.net

In 3.6 (and I guess upwards) GradientButtonMorph new results in an error.

As far as I figured out, super initialize in the initialize method does not like topColor and bottomColor to be nil.

So moving the two lines "topColor := lightGray" and "bottomColor := light gray" to the beginning of the initialize method solves the problem.

The same applies to the changeset in Eye Candy III.

Herbert König
herbertkoenig@gmx.net


The button is supposed to flash three times on #mouseUp:
but this doesn't happen. Changing the #min: to #max: in
   [delay _ Delay forMilliseconds: 
      (elapsed min: DelayTime). delay wait].

appears to fix it.

Michael Ross
kmr1642@yahoo.com