Exercise: construct a launcher window - version 3
Last updated at 10:37 pm UTC on 4 December 2021
On this page it is explained how a Launcher is done. A number of buttons is presented stacked in a column.
Upon pressing a button a method call on a class object is executed.
Two basic ToolBuilderSpecs (GUI specification) objects are used to set up the launcher.
The buttons are specified with triplets:
- class object
- method call
- button color
The Launcher is started with
Launcher open

Description of the Launcher code
Button definitions
The buttons have been defined as follows in a method called #buttonDefinitions
:
buttonDefinitions
^ #(
( 'SystemBrowser' #openBrowser #lightBrown )
( 'Help browser' #openHelpBrowser #lightGray )
( 'Workspace' #openWorkspace #green )
( 'Transcript' #openTranscript #red )
( 'Monticello' #openMonticello #lightBlue )
( 'FileList' #openFileList #yellow )
)
The method #extent gives the size of the launcher.
These buttonDefinitions are used to build the launcher (Launcher is a subclass of Model) are built with the following method
buildButtonsWith: aBuilder
^ aBuilder pluggablePanelSpec new
model: self;
layout: #vertical;
children: (self buttonDefinitions collect: [ :each |
aBuilder pluggableButtonSpec new
model: self;
label: each first;
action: each second;
color: (Color perform: each third);
"enabled: each fourth;"
yourself ]);
Note that #enabled is not used. All buttons are enabled by default. If an #enabled method is give it is possible to enable the button depending on a condition.
Full code for the Launcher
Copy the code below and paste it into a Workspace. Then file it in.
Then open it as described above
Launcher open
There is also comment in the class 'Launcher'.
'From Squeak6.0alpha of 15 November 2017 [latest update: #17506] on 25 November 2017 at 11:45:42 pm'!
Model subclass: #Launcher
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'ToolBuilder documentation example'!
!Launcher commentStamp: 'hjh 11/25/2017 23:42' prior: 0!
A Launcher presents a list of button to lauch tools.
Change the method #buttonDefinitions in category 'definitions' to adapt it to your needs.
It is a simple demo how to use the ToolBuilder to construct a tool.
Usage:
Launcher open
!
!Launcher methodsFor: 'actions' stamp: 'hjh 11/25/2017 23:31'!
openBrowser
SystemBrowser defaultOpenBrowser
! !
!Launcher methodsFor: 'actions' stamp: 'hjh 11/25/2017 23:37'!
openFileList
FileList open
! !
!Launcher methodsFor: 'actions' stamp: 'hjh 11/23/2017 10:49'!
openHelpBrowser
HelpBrowser open! !
!Launcher methodsFor: 'actions' stamp: 'hjh 11/25/2017 23:36'!
openMonticello
MCWorkingCopyBrowser open
! !
!Launcher methodsFor: 'actions' stamp: 'hjh 11/25/2017 23:33'!
openTranscript
ToolBuilder open: TranscriptStream
! !
!Launcher methodsFor: 'actions' stamp: 'hjh 11/25/2017 23:33'!
openWorkspace
Workspace open! !
!Launcher methodsFor: 'definitions' stamp: 'hjh 11/25/2017 23:44'!
buttonDefinitions
^ #(
( 'SystemBrowser' #openBrowser #lightBrown )
( 'Help browser' #openHelpBrowser #lightGray )
( 'Workspace' #openWorkspace #green )
( 'Transcript' #openTranscript #red )
( 'Monticello' #openMonticello #lightBlue )
( 'FileList' #openFileList #yellow )
)! !
!Launcher methodsFor: 'definitions' stamp: 'hjh 11/23/2017 18:49'!
extent
^ 140 @ 180! !
!Launcher methodsFor: 'definitions' stamp: 'hjh 11/23/2017 13:11'!
label
^ 'Launcher' ! !
!Launcher methodsFor: 'toolbuilder' stamp: 'hjh 11/23/2017 18:58'!
buildButtonsWith: aBuilder
^ aBuilder pluggablePanelSpec new
model: self;
layout: #vertical;
children: (self buttonDefinitions collect: [ :each |
aBuilder pluggableButtonSpec new
model: self;
label: each first;
action: each second;
color: (Color perform: each third);
"enabled: each third;"
yourself ]);
yourself.! !
!Launcher methodsFor: 'toolbuilder' stamp: 'hjh 11/23/2017 18:47'!
buildWith: aBuilder
| window |
window := aBuilder pluggableWindowSpec new
model: self; label: self label; extent: self extent;
children: (OrderedCollection new
add: ((self buildButtonsWith: aBuilder)
frame: self buttonsFrame;
yourself);
yourself);
yourself.
^ aBuilder build: window.! !
!Launcher methodsFor: 'toolbuilder' stamp: 'hjh 11/23/2017 07:28'!
buttonsFrame
^LayoutFrame fractions: (0@0 corner: 1@1)
"
^LayoutFrame new
leftFraction: 0 offset: 0;
topFraction: 1 offset: self buttonHeight negated;
rightFraction: 1 offset: 0;
bottomFraction: 1 offset: 0
" ! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Launcher class
instanceVariableNames: ''!
!Launcher class methodsFor: 'as yet unclassified' stamp: 'hjh 11/23/2017 07:38'!
open
^ ToolBuilder open: self new.! !
tagBeginner