Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Exercise: construct a launcher window - version 2
Last updated at 11:16 pm UTC on 6 June 2018
Page extracted from page The AlignmentMorph

This is version 2 of Exercise: construct a launcher window with an AlignmentMorph.

You can pick it up here as a changeset: simplelaunch.cs


  SimpleButtonMorph subclass: #LaunchButtonMorph
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Morphic Documentation example'

" Here are the instance side methods "
mouseUp: evt
  | delay |
  " The oldColor is the button's original color saved in mouseDown: evt "
  delay _ Delay forMilliseconds: 50.
 (self containsPoint: evt cursorPoint )
 ifTrue: [
  1 to: 3 do: [ :i |
    self color: oldColor.   " display the original color "
    self refreshWorld.     " paint the button"
    delay wait.
    self color: (oldColor mixed: 1/2 with: Color white). " make it a light color again "
    self refreshWorld.     " paint the button "
    delay wait. ].
   ].
  self color: oldColor.
  self refreshWorld.
  super mouseUp: evt.

initialize
  super initialize.
  self useSquareCorners.
  bounds _ 0 @ 0 extent: 96 @ 20.
  self setDefaultLabel.
  self color: ( Color lightGray ).
  self borderColor: #raised.
  self borderWidth: 1.

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


AlignmentMorph subclass: #LaunchAlignmentMorph
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Morphic Documentation example'

" instance methods"

initialize
  | button |
  super initialize.
  orientation _ #vertical.
  button _ LaunchButtonMorph new
    label: 'Browser' ;
    target: ( World activeHand ) ;
    actionSelector: #openBrowser ;
    actWhen: #buttonUp.
  self addMorph: button.
  button _ LaunchButtonMorph new
    label: 'Workspace' ;
    target: ( World activeHand ) ;
    actionSelector: #openWorkspace ;
    actWhen: #buttonUp.
  self addMorphBack: button.
  button _ LaunchButtonMorph new
    label: 'Transcript' ;
    target: ( World activeHand ) ;
    actionSelector: #openTranscript ;
    actWhen: #buttonUp.
  self addMorphBack: button.
  button _ LaunchButtonMorph new
    label: 'Change Sorter' ;
    target: ( World activeHand ) ;
    actionSelector: #openChangeSorter: ;
    arguments: #( 1 ) ;
    actWhen: #buttonUp.
  self addMorphBack: button.
  button _ LaunchButtonMorph new
    label: 'File List' ;
    target: ( World activeHand ) ;
    actionSelector: #openFileList ;
    actWhen: #buttonUp.
  self addMorphBack: button.
  self color: ( Color gray ).


" here is a class side method"
openLauncher
^ self new openInWindowLabeled: 'Go' inWorld: World.

Read these classes into your image.

OK, with this stuff in our image, let's talk about some of what's going on here.

We can bring up our Window Launcher by executing: LaunchAlignmentMorph openLauncher. Try it out. A window with five buttons is created and placed on the Squeak desktop. Clicking on one of the buttons brings up the corresponding Squeak window.

Let's go through some of the methods. First up, LaunchButtonMorph#initialize. Nothing special here, we just define how the button is going to look and how big it is going to be. #label: is a little trickier. A button consists of a bordered rectangle and a string. #label: is centering the string inside of the rectangle.

Being interface designers, we added a little 'trick' for the mouseUp code. When the user releases the mouse button, the button flashes 3 times. This is to indicate that the user has made a selection, that is, a positive reinforcement of his action. All modern interfaces do this type of thing. Again, the delay is applied so that it appears
as if something important has happened on faster machines.

Which leads us to LaunchAlignmentMorph. The class method #openLauncher is provided for convenience. There is one instance method, #initialization. The code looks ugly, but is pretty simple. First, we set the orientation to #vertical, and then we add the buttons. We also set the color to gray.

So, add 'em up. 5 methods to build our little launcher. That's pretty good, and we have the spiffy part about the flashing buttons too !!!

Except we kind of skipped over that button initialization code stuff. Who is this 'World activeHand' character ? That sounds like the next chapter.

HandMorph

Jim Benson
jb@speed.net

tagBeginner

Exercise: construct a launcher window - version 3