ApplicationModel subclass: #GreedMainGUI instanceVariableNames: 'rankingList roundNumber textCollector score playerName diceValues iterateNumber greedTable parent ' classVariableNames: 'BeepOn ' poolDictionaries: '' category: 'Greed-Boundary'! GreedMainGUI comment: 'Copyright(C) 1998 Masashi Umezawa GreedMainGUI is a main GUI for playing GreedGame. It displays all game process, showing current ranking. Instance Variables: diceValues field for showing current dice values greedTable reference to the GreedTable which is a controller of this game. iterateNumber field for showing current turn iteration times playerName field for showing current player name rankingList list showing current ranking roundNumber field for current round number score field for current player''s score textCollector log for entire game process parent my launcher gui Class Variables: BeepOn switch for beep sound in bunkrupt '! !GreedMainGUI methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" "lazy initialization" greedTable := nil. "list setup" self resetList! release "Copyright(C) 1998 Masashi Umezawa" self unregisterTableEventsOf: self greedTable. super release! resetList "Copyright(C) 1998 Masashi Umezawa" "list setup" rankingList := nil. self rankingList list: (self rankingList list asSortedCollection sortBlock: [:a :b | a totalScore >= b totalScore])! ! !GreedMainGUI methodsFor: 'actions'! confirmPlayWill "Copyright(C) 1998 Masashi Umezawa" ^Dialog confirm: #continue_you_play << #greed >> 'continue to play?'! setPlayers: aPlayerCollection "Copyright(C) 1998 Masashi Umezawa" self resetList. self greedTable resetPlayers. aPlayerCollection do: [:each | self rankingList list add: each. self greedTable addPlayer: each]! start "Copyright(C) 1998 Masashi Umezawa" self configureTableEventsOf: self greedTable. self greedTable start. self unregisterTableEventsOf: self greedTable! ! !GreedMainGUI methodsFor: 'window actions'! back "Copyright(C) 1998 Masashi Umezawa" self closeRequest. self parent isNil ifFalse: [self parent reOpen]! flush "Copyright(C) 1998 Masashi Umezawa" self builder window flush. BeepOn ifTrue: [Screen default ringBell]! ! !GreedMainGUI methodsFor: 'configuring events'! configureTableEventsOf: aGreedTable "Copyright(C) 1998 Masashi Umezawa" aGreedTable when: #cannotPlay send: #cannotPlay to: self. aGreedTable when: #playStarting send: #playStarting to: self. aGreedTable when: #bankrupt send: #bankrupt: to: self. aGreedTable when: #checkFirstPlay send: #checkFirstPlay: to: self. aGreedTable when: #checkContinueToPlay send: #checkContinueToPlay: to: self. aGreedTable when: #checkWinners send: #checkWinners: to: self. aGreedTable when: #newRoundStarting send: #newRoundStarting: to: self. aGreedTable when: #preTurnProcessing send: #preTurnProcessing: to: self. aGreedTable when: #postTurnProcessing send: #postTurnProcessing: to: self. aGreedTable when: #newTurnEnding send: #newTurnEnding: to: self. aGreedTable when: #playEndingWith send: #playEndingWith: to: self! unregisterTableEventsOf: aGreedTable "Copyright(C) 1998 Masashi Umezawa" aGreedTable class eventsTriggered do: [:each | aGreedTable removeActionsWithReceiver: self forEvent: each]! ! !GreedMainGUI methodsFor: 'handling events'! bankrupt: aGreedPlayer "Copyright(C) 1998 Masashi Umezawa" self flush. (self textCollector) cr; show: aGreedPlayer name , (#is_bunkrupt << #greed >> ' is bunkrupt!!!!!!!!') asString! cannotPlay "Copyright(C) 1998 Masashi Umezawa" Dialog warn: #not_enough_player << #greed >> 'Not enough player!!'! checkContinueToPlay: aGreedPlayer "Copyright(C) 1998 Masashi Umezawa" aGreedPlayer hasPlayWill: self confirmPlayWill. aGreedPlayer beDecided! checkFirstPlay: aGreedPlayer "Copyright(C) 1998 Masashi Umezawa" (self textCollector) cr; show: aGreedPlayer name , (#someones_turn << #greed >> ' ''s turn') asString. self playerName value: aGreedPlayer name. aGreedPlayer beDecided! checkWinners: aGreedRound "Copyright(C) 1998 Masashi Umezawa" (self textCollector) cr; show: (#round_ended << #greed >> 'The <1s> round ended' expandMacrosWith: aGreedRound roundNumber printString) asString. self rankingList list: self rankingList list reSort! newRoundStarting: aRound "Copyright(C) 1998 Masashi Umezawa" self roundNumber value: aRound roundNumber! newTurnEnding: aTurn "Copyright(C) 1998 Masashi Umezawa" self playerName value: ''. self score value: 0. self diceValues value: ''. self iterateNumber value: 0! playEndingWith: winners "Copyright(C) 1998 Masashi Umezawa" (self builder componentAt: #back) beVisible. (self builder componentAt: #start) enable. (self textCollector) cr; show: (#game_ended << #greed >> 'The game ended..') asString. (self textCollector) cr; show: (#winner_is << #greed >> '** The Winners **') asString. winners do: [:each | (self textCollector) cr; show: each displayString].! playStarting "Copyright(C) 1998 Masashi Umezawa" (self builder componentAt: #rankingList) widget invalidate. (self builder componentAt: #back) beInvisible. (self builder componentAt: #start) disable. (self textCollector) cr; show: (#greed_started << #greed >> 'GreedGame started!!!!') asString! postTurnProcessing: aGreedTurn "Copyright(C) 1998 Masashi Umezawa" (aGreedTurn player isInFirstTurn or: [aGreedTurn player hasPlayWill]) ifTrue: [(self textCollector) cr; show: aGreedTurn gameField dicePot displayString. (self textCollector) space; show: aGreedTurn score printString. self diceValues value: aGreedTurn gameField dicePot displayString. self score value: aGreedTurn score]! preTurnProcessing: aGreedTurn "Copyright(C) 1998 Masashi Umezawa" | player | player := aGreedTurn player. player isRobot ifTrue: [(self textCollector) cr; show: player name , (#someones_turn << #greed >> ' ''s turn') asString. self playerName value: player name]. (self textCollector) cr; show: aGreedTurn iterateNumber printString , (#nth_try << #greed >> ' try') asString. self iterateNumber value: aGreedTurn iterateNumber! ! !GreedMainGUI methodsFor: 'accessing'! greedTable "Copyright(C) 1998 Masashi Umezawa" ^greedTable isNil ifTrue: [greedTable := self defaultTable. ] ifFalse: [greedTable]! greedTable: aGreedTable "Copyright(C) 1998 Masashi Umezawa" greedTable := aGreedTable! parent "Copyright(C) 1998 Masashi Umezawa" ^parent! parent: aGreedOpeningGUI "Copyright(C) 1998 Masashi Umezawa" parent := aGreedOpeningGUI! ! !GreedMainGUI methodsFor: 'factory'! defaultTable "Copyright(C) 1998 Masashi Umezawa" | tab | tab := GreedTable new. ^tab! ! !GreedMainGUI methodsFor: 'aspects'! diceValues "Copyright(C) 1998 Masashi Umezawa" ^diceValues isNil ifTrue: [diceValues := String new asValue] ifFalse: [diceValues]! iterateNumber "Copyright(C) 1998 Masashi Umezawa" ^iterateNumber isNil ifTrue: [iterateNumber := 0 asValue] ifFalse: [iterateNumber]! playerName "Copyright(C) 1998 Masashi Umezawa" ^playerName isNil ifTrue: [playerName := String new asValue] ifFalse: [playerName]! rankingList "Copyright(C) 1998 Masashi Umezawa" ^rankingList isNil ifTrue: [rankingList := SelectionInList new] ifFalse: [rankingList]! roundNumber "Copyright(C) 1998 Masashi Umezawa" ^roundNumber isNil ifTrue: [roundNumber := 0 asValue] ifFalse: [roundNumber]! score "Copyright(C) 1998 Masashi Umezawa" ^score isNil ifTrue: [score := 0 asValue] ifFalse: [score]! ! !GreedMainGUI methodsFor: 'building transcript'! gameLogView "Copyright(C) 1998 Masashi Umezawa" | tcv | tcv := TextCollectorView new model: self textCollector. tcv controller: TextEditorController new. tcv controller keyboardProcessor: builder keyboardProcessor. ^tcv! textCollector "Copyright(C) 1998 Masashi Umezawa" textCollector isNil ifTrue: [textCollector := TextCollector new]. ^textCollector! ! !GreedMainGUI methodsFor: 'interface opening'! postBuildWith: aBuilder "Copyright(C) 1998 Masashi Umezawa" (aBuilder componentAt: #rankingList) widget displayStringSelector: #displayStringWithScore! ! !GreedMainGUI methodsFor: 'window events'! noticeOfWindowClose: aWindow "Copyright(C) 1998 Masashi Umezawa" self release! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GreedMainGUI class instanceVariableNames: ''! !GreedMainGUI class methodsFor: 'class initialization'! initialize "Copyright(C) 1998 Masashi Umezawa" BeepOn := true! ! !GreedMainGUI class methodsFor: 'interface specs'! windowSpec "Copyright(C) 1998 Masashi Umezawa" "UIPainter new openOnClass: self andSelector: #windowSpec" ^#(#FullSpec #window: #(#WindowSpec #label: #(#UserMessage #key: #GreedGame #defaultString: 'GreedGame') #min: #(#Point 557 480) #max: #(#Point 557 480) #bounds: #(#Rectangle 209 177 766 657) #isEventDriven: true) #component: #(#SpecCollection #collection: #(#(#ActionButtonSpec #layout: #(#Rectangle 11 435 546 467) #name: #start #model: #start #label: #(#UserMessage #key: #start #defaultString: 'start!!!!') #defaultable: true) #(#ArbitraryComponentSpec #layout: #(#Rectangle 290 81 533 255) #flags: 9 #component: #gameLogView) #(#InputFieldSpec #layout: #(#Rectangle 117 20 196 45) #model: #roundNumber #type: #number) #(#LabelSpec #layout: #(#Point 22 19) #label: #(#UserMessage #key: #round #defaultString: 'round')) #(#SequenceViewSpec #layout: #(#Rectangle 19 78 254 258) #name: #rankingList #model: #rankingList #useModifierKeys: true #selectionType: #highlight) #(#LabelSpec #layout: #(#Point 22 52) #label: #(#UserMessage #key: #ranking #defaultString: 'ranking')) #(#LabelSpec #layout: #(#Point 295 55) #label: #(#UserMessage #key: #log #defaultString: 'log')) #(#InputFieldSpec #layout: #(#Rectangle 186 318 359 344) #model: #playerName #isReadOnly: true) #(#InputFieldSpec #layout: #(#Rectangle 210 382 341 406) #model: #diceValues #alignment: #center #isReadOnly: true) #(#GroupBoxSpec #layout: #(#Rectangle 152 367 402 420)) #(#InputFieldSpec #layout: #(#Rectangle 99 318 162 344) #model: #iterateNumber #alignment: #center #isReadOnly: true #type: #number) #(#InputFieldSpec #layout: #(#Rectangle 384 318 447 344) #model: #score #alignment: #center #isReadOnly: true #type: #number) #(#LabelSpec #layout: #(#Point 79 353) #label: #(#UserMessage #key: #turns #defaultString: 'turns')) #(#LabelSpec #layout: #(#Point 442 347) #label: #(#UserMessage #key: #player_sum #defaultString: 'sum')) #(#LabelSpec #layout: #(#Point 168 381) #label: #(#UserMessage #key: #di #defaultString: 'di-')) #(#LabelSpec #layout: #(#Point 344 381) #label: #(#UserMessage #key: #ce #defaultString: '-ce')) #(#ActionButtonSpec #layout: #(#Rectangle 9 272 544 304) #name: #back #flags: 24 #model: #back #label: #(#UserMessage #key: #back #defaultString: 'back!!!!') #defaultable: true))))! ! !GreedMainGUI class methodsFor: 'utilities'! beepOn: aBoolean "Copyright(C) 1998 Masashi Umezawa" BeepOn := aBoolean! ! ApplicationModel subclass: #GreedOpeningGUI instanceVariableNames: 'playerListGUI ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Boundary'! GreedOpeningGUI comment: 'Copyright(C) 1998 Masashi Umezawa GreedOpeningGUI is a launcher GUI for GreedGame. Instance Variables: playerListGUI a child GUI used for players entry '! !GreedOpeningGUI methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" "lazy initialization" playerListGUI := nil.! release "Copyright(C) 1998 Masashi Umezawa" playerListGUI isNil ifFalse:[playerListGUI release; reOpen; closeRequest.]. super release! ! !GreedOpeningGUI methodsFor: 'actions'! end "Copyright(C) 1998 Masashi Umezawa" self closeRequest. self release! start "Copyright(C) 1998 Masashi Umezawa" self openGreedPlayerListGUI. self collapse! ! !GreedOpeningGUI methodsFor: 'window actions'! collapse "Copyright(C) 1998 Masashi Umezawa" | win | win := self builder window. win isOpen ifTrue: [win collapse]! expand "Copyright(C) 1998 Masashi Umezawa" | win | win := self builder window. win isOpen ifTrue: [win expand]! openGreedPlayerListGUI "Copyright(C) 1998 Masashi Umezawa" self playerListGUI open! reOpenGreedPlayerListGUI "Copyright(C) 1998 Masashi Umezawa" self playerListGUI reOpen! ! !GreedOpeningGUI methodsFor: 'factory'! defaultPlayerListGUI "Copyright(C) 1998 Masashi Umezawa" ^GreedPlayerListGUI new parent: self! ! !GreedOpeningGUI methodsFor: 'accessing'! playerListGUI "Copyright(C) 1998 Masashi Umezawa" ^playerListGUI isNil ifTrue: [playerListGUI := self defaultPlayerListGUI] ifFalse: [playerListGUI]! playerListGUI: aGreedPlayerListGUI "Copyright(C) 1998 Masashi Umezawa" playerListGUI := aGreedPlayerListGUI! ! !GreedOpeningGUI methodsFor: 'window events'! noticeOfWindowClose: aWindow "Copyright(C) 1998 Masashi Umezawa" self release! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GreedOpeningGUI class instanceVariableNames: ''! !GreedOpeningGUI class methodsFor: 'interface specs'! windowSpec "Copyright(C) 1998 Masashi Umezawa" "UIPainter new openOnClass: self andSelector: #windowSpec" ^#(#FullSpec #window: #(#WindowSpec #label: #(#UserMessage #key: #GreedGame #defaultString: 'GreedGame') #min: #(#Point 244 169) #max: #(#Point 244 169) #bounds: #(#Rectangle 180 281 424 450) #isEventDriven: true) #component: #(#SpecCollection #collection: #(#(#LabelSpec #layout: #(#Point 75 14) #label: #(#UserMessage #key: #GreedGame #defaultString: 'GreedGame')) #(#ActionButtonSpec #layout: #(#Rectangle 22 58 217 88) #model: #start #label: #(#UserMessage #key: #Start #defaultString: 'Start') #defaultable: true) #(#DividerSpec #layout: #(#Rectangle 22 41 217 45)) #(#LabelSpec #layout: #(#Point 11 134) #label: #(#UserMessage #key: #copyright_m_umezawa #defaultString: 'Copyright(C) 1998 Masashi Umezawa')) #(#DividerSpec #layout: #(#Rectangle 22 11 217 15)) #(#ActionButtonSpec #layout: #(#Rectangle 23 98 218 128) #model: #end #label: #(#UserMessage #key: #End #defaultString: 'End') #defaultable: true))))! ! ApplicationModel subclass: #GreedPlayerListGUI instanceVariableNames: 'entryList participantList mainGUI parent ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Boundary'! GreedPlayerListGUI comment: 'Copyright(C) 1998 Masashi Umezawa GreedPlayerListGUI is a GUI for entering and selectiong GreedGame players. Instance Variables: entryList possible player list of GreedGame participantList acutual player list of GreedGame mainGUI a main GUI for GreedGame parent my launcher gui '! !GreedPlayerListGUI methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" "lazy initialization" mainGUI := nil! release "Copyright(C) 1998 Masashi Umezawa" mainGUI isNil ifFalse: [mainGUI release; closeRequest.]. super release! ! !GreedPlayerListGUI methodsFor: 'actions'! addParticipant "Copyright(C) 1998 Masashi Umezawa" self entryList selections do: [:each | | li | li := self participantList list. (li includes: each) ifFalse: [li add: each]]! removeParticipant "Copyright(C) 1998 Masashi Umezawa" | sels | sels := self participantList selections. sels do: [:each | self participantList list remove: each]! removePlayer "Copyright(C) 1998 Masashi Umezawa" | sels | sels := self entryList selections. sels do: [:each | self entryList list remove: each]! ! !GreedPlayerListGUI methodsFor: 'window actions'! cancel "Copyright(C) 1998 Masashi Umezawa" self closeRequest! hide "Copyright(C) 1998 Masashi Umezawa" self builder isNil ifFalse: [| win | win := self builder window. win isOpen ifTrue: [win unmap]]! openGreedAddPlayerGUI "Copyright(C) 1998 Masashi Umezawa" | dialog | dialog := GreedAddPlayerDialog new. dialog open. dialog accept value ifTrue: [| player | player := dialog returnPlayer. self entryList list add: player. Dialog warn: player name , (#added_player << #greed >> ' added!!!!') asString]! openGreedMainGUI "Copyright(C) 1998 Masashi Umezawa" self hide. self mainGUI setPlayers: self participantList list. self mainGUI open.! reOpen "Copyright(C) 1998 Masashi Umezawa" self builder isNil ifFalse: [| win | win := self builder window. win isOpen ifTrue: [win map]]! ! !GreedPlayerListGUI methodsFor: 'aspects'! entryList "Copyright(C) 1998 Masashi Umezawa" ^entryList isNil ifTrue: [entryList := MultiSelectionInList new] ifFalse: [entryList]! participantList "Copyright(C) 1998 Masashi Umezawa" ^participantList isNil ifTrue: [participantList := MultiSelectionInList new] ifFalse: [participantList]! ! !GreedPlayerListGUI methodsFor: 'accessing'! mainGUI "Copyright(C) 1998 Masashi Umezawa" ^mainGUI isNil ifTrue: [mainGUI := self defaultMainGUI] ifFalse: [mainGUI]! mainGUI: aGreedMainGUI "Copyright(C) 1998 Masashi Umezawa" mainGUI := aGreedMainGUI! parent "Copyright(C) 1998 Masashi Umezawa" ^parent! parent: aGreedOpeningGUI "Copyright(C) 1998 Masashi Umezawa" parent := aGreedOpeningGUI! ! !GreedPlayerListGUI methodsFor: 'factory'! defaultMainGUI "Copyright(C) 1998 Masashi Umezawa" ^GreedMainGUI new parent: self! ! !GreedPlayerListGUI methodsFor: 'window events'! noticeOfWindowClose: aWindow "Copyright(C) 1998 Masashi Umezawa" self parent isNil ifFalse: [self parent expand]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GreedPlayerListGUI class instanceVariableNames: ''! !GreedPlayerListGUI class methodsFor: 'interface specs'! windowSpec "Copyright(C) 1998 Masashi Umezawa" "UIPainter new openOnClass: self andSelector: #windowSpec" ^#(#FullSpec #window: #(#WindowSpec #label: #(#UserMessage #key: #GreedGame #defaultString: 'GreedGame') #min: #(#Point 586 382) #max: #(#Point 586 382) #bounds: #(#Rectangle 112 185 698 567) #isEventDriven: true) #component: #(#SpecCollection #collection: #(#(#LabelSpec #layout: #(#Point 27 19) #label: #(#UserMessage #key: #Please_select_players #defaultString: 'Please select players')) #(#ActionButtonSpec #layout: #(#Rectangle 343 313 447 345) #model: #openGreedMainGUI #label: #(#UserMessage #key: #Okay #defaultString: 'OK') #defaultable: true) #(#ActionButtonSpec #layout: #(#Rectangle 461 313 565 345) #model: #cancel #label: #(#UserMessage #key: #Cancel #defaultString: 'Cancel') #defaultable: true) #(#SequenceViewSpec #layout: #(#Rectangle 27 84 250 286) #model: #entryList #multipleSelections: true #selectionType: #checkMark) #(#SequenceViewSpec #layout: #(#Rectangle 347 83 570 285) #model: #participantList #multipleSelections: true #selectionType: #checkMark) #(#ActionButtonSpec #layout: #(#Rectangle 271 134 323 159) #model: #addParticipant #label: '>>' #defaultable: true) #(#ActionButtonSpec #layout: #(#Rectangle 271 200 323 225) #model: #removeParticipant #label: '<<' #defaultable: true) #(#LabelSpec #layout: #(#Point 31 56) #label: #(#UserMessage #key: #Registered_players #defaultString: 'registered players')) #(#LabelSpec #layout: #(#Point 346 55) #label: #(#UserMessage #key: #Participants #defaultString: 'participants')) #(#ActionButtonSpec #layout: #(#Rectangle 23 313 127 345) #model: #openGreedAddPlayerGUI #label: #(#UserMessage #key: #add_new_player #defaultString: 'add new player') #defaultable: true) #(#ActionButtonSpec #layout: #(#Rectangle 146 313 250 345) #model: #removePlayer #label: #(#UserMessage #key: #delete_player #defaultString: 'delete player') #defaultable: true))))! ! SimpleDialog subclass: #GreedAddPlayerDialog instanceVariableNames: 'playerName isRobot ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Boundary'! GreedAddPlayerDialog comment: 'Copyright(C) 1998 Masashi Umezawa GreedAddPlayerDialog is a Dialog for entering new GreedPlayer. Instance Variables: isRobot check box value holder indicating the player is robot or not playerName player name value holder '! !GreedAddPlayerDialog methodsFor: 'actions'! returnPlayer "Copyright(C) 1998 Masashi Umezawa" | player | player := GreedPlayer new. player name: self playerName value. player isRobot: self isRobot value. ^player! ! !GreedAddPlayerDialog methodsFor: 'aspects'! isRobot "Copyright(C) 1998 Masashi Umezawa" ^isRobot isNil ifTrue: [isRobot := false asValue] ifFalse: [isRobot]! playerName "Copyright(C) 1998 Masashi Umezawa" ^playerName isNil ifTrue: [playerName := String new asValue] ifFalse: [playerName]! ! !GreedAddPlayerDialog methodsFor: 'private'! closeAccept "Copyright(C) 1998 Masashi Umezawa" self accept value ifTrue: [self playerName value isEmpty ifTrue: [self accept value: false. ^Dialog warn: #enter_player_name << #greed >> 'Please enter player''s name!!']]. super closeAccept! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GreedAddPlayerDialog class instanceVariableNames: ''! !GreedAddPlayerDialog class methodsFor: 'interface specs'! windowSpec "Copyright(C) 1998 Masashi Umezawa" "UIPainter new openOnClass: self andSelector: #windowSpec" ^#(#FullSpec #window: #(#WindowSpec #label: #(#UserMessage #key: #GreedGame #defaultString: 'GreedGame') #min: #(#Point 408 165) #max: #(#Point 408 165) #bounds: #(#Rectangle 135 297 543 462) #isEventDriven: true) #component: #(#SpecCollection #collection: #(#(#LabelSpec #layout: #(#Point 24 13) #label: #(#UserMessage #key: #Please_add_new_player #defaultString: 'Please add a new player')) #(#LabelSpec #layout: #(#Point 28 59) #label: #(#UserMessage #key: #Player_name #defaultString: 'name')) #(#InputFieldSpec #layout: #(#Rectangle 127 52 376 84) #model: #playerName) #(#CheckBoxSpec #layout: #(#Point 309 92) #model: #isRobot #label: #(#UserMessage #key: #isRobot #defaultString: 'robot')) #(#ActionButtonSpec #layout: #(#Rectangle 23 124 159 157) #model: #accept #label: #(#UserMessage #key: #accept #defaultString: 'OK') #defaultable: true) #(#ActionButtonSpec #layout: #(#Rectangle 239 125 375 158) #model: #cancel #label: #(#UserMessage #key: #Cancel #defaultString: 'Cancel') #defaultable: true))))! ! GreedMainGUI initialize!