Object subclass: #GamePlayer instanceVariableNames: 'name gameField isRobot isPlayable ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Entity'! GamePlayer comment: 'Copyright(C) 1998 Masashi Umezawa GamePlayer is an abstract class for a general game player. Instance Variables: gameField the field on which the player play isPlayable shows the player can play isRobot shows he player is robot name the name of the player '! !GamePlayer methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" name := ''. isPlayable := true. isRobot := false! ! !GamePlayer methodsFor: 'actions'! play "Copyright(C) 1998 Masashi Umezawa" "default do nothing"! ! !GamePlayer methodsFor: 'accessing'! gameField "Copyright(C) 1998 Masashi Umezawa" ^gameField! gameField: aGameField "Copyright(C) 1998 Masashi Umezawa" gameField := aGameField! isPlayable "Copyright(C) 1998 Masashi Umezawa" ^isPlayable! isPlayable: aBoolean "Copyright(C) 1998 Masashi Umezawa" isPlayable := aBoolean! isRobot "Copyright(C) 1998 Masashi Umezawa" ^isRobot! isRobot: aBoolean "Copyright(C) 1998 Masashi Umezawa" isRobot := aBoolean! name "Copyright(C) 1998 Masashi Umezawa" ^name! name: aString "Copyright(C) 1998 Masashi Umezawa" name := aString! ! !GamePlayer methodsFor: 'displaying'! displayString "Copyright(C) 1998 Masashi Umezawa" ^self isRobot ifFalse: [self name] ifTrue: [self name , ' (ROBOT)']! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GamePlayer class instanceVariableNames: ''! !GamePlayer class methodsFor: 'instance creation'! name: nameString "Copyright(C) 1998 Masashi Umezawa" ^self new name: nameString! name: nameString gameField: aGame "Copyright(C) 1998 Masashi Umezawa" ^(self new) name: nameString; gameField: aGame! new "Copyright(C) 1998 Masashi Umezawa" ^super new initialize! ! Object subclass: #DicePot instanceVariableNames: 'diceCollection shakenDice ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Entity'! DicePot comment: 'Copyright(C) 1998 Masashi Umezawa DicePot holds many dice Instance Variables: diceCollection a collection of dice to be rolled shakenDice shaken dice values '! !DicePot methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" diceCollection := OrderedCollection new. shakenDice := OrderedCollection new! ! !DicePot methodsFor: 'actions'! add: aDice "Copyright(C) 1998 Masashi Umezawa" self diceCollection add: aDice! addAll: aDiceCollection "Copyright(C) 1998 Masashi Umezawa" self diceCollection addAll: aDiceCollection! setDiceCollection: aDiceCollection "Copyright(C) 1998 Masashi Umezawa" self diceCollection: aDiceCollection! shake "Copyright(C) 1998 Masashi Umezawa" self shakenDice: (self diceCollection collect: [:each | self randomDelay wait. each roll. each]). ^self shakenDice! ! !DicePot methodsFor: 'accessing'! diceCollection "Copyright(C) 1998 Masashi Umezawa" ^diceCollection! diceCollection: aCollectionOfDie "Copyright(C) 1998 Masashi Umezawa" diceCollection := aCollectionOfDie! shakenDice "Copyright(C) 1998 Masashi Umezawa" ^shakenDice! shakenDice: aCollectionOfDice "Copyright(C) 1998 Masashi Umezawa" ^shakenDice := aCollectionOfDice! ! !DicePot methodsFor: 'displaying'! displayString "Copyright(C) 1998 Masashi Umezawa" | str | str := '{ '. self shakenDice do: [:each | str := str , each displayString , ' ']. str := str , '}'. ^str! ! !DicePot methodsFor: 'private'! randomDelay "Copyright(C) 1998 Masashi Umezawa" "to create better(more exciting) random number" | delay rand | rand := Random new next * 10 + 10. delay := Delay forMilliseconds: rand. ^delay! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DicePot class instanceVariableNames: ''! !DicePot class methodsFor: 'instance creation'! fromDiceCollection: diceCollection "Copyright(C) 1998 Masashi Umezawa" | inst | inst := self new. inst setDiceCollection: diceCollection. ^inst! fromNumber: numberOfDices "Copyright(C) 1998 Masashi Umezawa" ^self fromNumber: numberOfDices maxValue: 6! fromNumber: numberOfDices maxValue: maxValue "Copyright(C) 1998 Masashi Umezawa" | inst | inst := self new. 1 to: numberOfDices do: [:n | inst add: (self defaultDieClass new maxValue: maxValue)]. ^inst! new "Copyright(C) 1998 Masashi Umezawa" ^super new initialize! ! !DicePot class methodsFor: 'factory'! defaultDieClass "Copyright(C) 1998 Masashi Umezawa" ^Die! ! DicePot subclass: #GreedDiePot instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Greed-Entity'! GreedDiePot comment: 'Copyright(C) 1998 Masashi Umezawa GreedDiePot is a special DicePot which holds GreedDice'! !GreedDiePot methodsFor: 'actions'! shake "Copyright(C) 1998 Masashi Umezawa" self diceCollection: (self diceCollection select: [:each | each isDisposed not]). ^super shake! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GreedDiePot class instanceVariableNames: ''! !GreedDiePot class methodsFor: 'factory'! defaultDieClass "Copyright(C) 1998 Masashi Umezawa" ^GreedDie! ! Object subclass: #Die instanceVariableNames: 'number maxValue ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Entity'! Die comment: 'Copyright(C) 1998 Masashi Umezawa Die represents a die. Instance Variables: maxValue max value of die number current value of die '! !Die methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" number := 0. maxValue := 6! ! !Die methodsFor: 'accessing'! maxValue "Copyright(C) 1998 Masashi Umezawa" ^maxValue! maxValue: maxValueOfDie "Copyright(C) 1998 Masashi Umezawa" maxValue := maxValueOfDie! number "Copyright(C) 1998 Masashi Umezawa" ^number! number: anInteger "Copyright(C) 1998 Masashi Umezawa" ^number := anInteger! ! !Die methodsFor: 'actions'! roll "Copyright(C) 1998 Masashi Umezawa" ^number := (Random new next * self maxValue) truncated + 1! ! !Die methodsFor: 'displaying'! displayString "Copyright(C) 1998 Masashi Umezawa" ^self number printString! printString "Copyright(C) 1998 Masashi Umezawa" ^self number printString , ' isDisposed: ' , self isDisposed printString! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Die class instanceVariableNames: ''! !Die class methodsFor: 'instance creation'! maxValue: maxValue "Copyright(C) 1998 Masashi Umezawa" ^self new maxValue: maxValue! new "Copyright(C) 1998 Masashi Umezawa" ^super new initialize! ! GamePlayer subclass: #GreedPlayer instanceVariableNames: 'dicePot totalScore turn hasPlayWill isBankrupt isDecided playWillBlock ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Entity'! GreedPlayer comment: 'Copyright(C) 1998 Masashi Umezawa GreedPlayer is a player of GreedGame. Instance Variables: dicePot the dicePot the player has hasPlayWill indicates that s/he has a will to play isBankrupt indicates that s/he is bunkrupt isDecided indicates that s/he has decided to play playWillBlock < BlockClosure> will be used by a custom robot player to decide to play totalScore total score of GreedGame turn the turn in which the player plays '! !GreedPlayer methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" super initialize. playWillBlock := nil. self resetAll! reset "Copyright(C) 1998 Masashi Umezawa" self isBankrupt: false. self hasPlayWill: true. self isDecided: false! resetAll "Copyright(C) 1998 Masashi Umezawa" totalScore := 0. self reset! ! !GreedPlayer methodsFor: 'actions'! autoHasPlayWill "Copyright(C) 1998 Masashi Umezawa" | will | will := self isInFirstTurn or: [self playWillBlock isNil ifTrue: [Random new next < 0.3] ifFalse: [self playWillBlock value: self]]. self hasPlayWill: will! beDecided "Copyright(C) 1998 Masashi Umezawa" self isDecided: true! caluculateTotalScore "Copyright(C) 1998 Masashi Umezawa" self isBankrupt ifFalse: [totalScore := totalScore + self turn score]. ^totalScore! checkContinueToPlay "Copyright(C) 1998 Masashi Umezawa" ^self triggerEvent: #checkContinueToPlay withArguments: (Array with: self) ifNotHandled: [self beDecided]! decideToPlay "Copyright(C) 1998 Masashi Umezawa" self isRobot ifTrue: [self beDecided] ifFalse: [self checkContinueToPlay]! giveUp "Copyright(C) 1998 Masashi Umezawa" self hasPlayWill: false! play "Copyright(C) 1998 Masashi Umezawa" | i diceCollection sc | i := 0. [self isDecided] whileFalse: [self decideToPlay. i := i + 1. i > 100 ifTrue: [self beDecided. "about infinite loop" self error: '#checkContinueToPlay event is not hanlded correctly']]. self willContinueToPlay ifTrue: [diceCollection := self dicePot shake. sc := self gameField calculateScoreOf: diceCollection. self turn addScore: sc. (self gameField checkBunkruptOf: self with: sc) ifTrue: [self becomeBankrupt]]. self isDecided: false! willContinueToPlay "Copyright(C) 1998 Masashi Umezawa" self isRobot ifTrue: [self autoHasPlayWill]. ^self hasPlayWill! ! !GreedPlayer methodsFor: 'testing'! isInFirstTurn "Copyright(C) 1998 Masashi Umezawa" ^self turn iterateNumber == 1! isPlayable "Copyright(C) 1998 Masashi Umezawa" ^self isBankrupt not and: [self hasPlayWill]! ! !GreedPlayer methodsFor: 'accessing'! dicePot "Copyright(C) 1998 Masashi Umezawa" ^dicePot! dicePot: aDicePot "Copyright(C) 1998 Masashi Umezawa" dicePot := aDicePot! hasPlayWill "Copyright(C) 1998 Masashi Umezawa" ^hasPlayWill! hasPlayWill: aBoolean "Copyright(C) 1998 Masashi Umezawa" hasPlayWill := aBoolean! isBankrupt "Copyright(C) 1998 Masashi Umezawa" ^isBankrupt! isBankrupt: aBoolean "Copyright(C) 1998 Masashi Umezawa" isBankrupt := aBoolean! isDecided "Copyright(C) 1998 Masashi Umezawa" ^isDecided! isDecided: aBoolean "Copyright(C) 1998 Masashi Umezawa" isDecided := aBoolean! playWillBlock "Copyright(C) 1998 Masashi Umezawa" ^playWillBlock! playWillBlock: aBlockClosure "Copyright(C) 1998 Masashi Umezawa" playWillBlock := aBlockClosure! totalScore "Copyright(C) 1998 Masashi Umezawa" ^totalScore! totalScore: anInteger "Copyright(C) 1998 Masashi Umezawa" totalScore := anInteger! turn "Copyright(C) 1998 Masashi Umezawa" ^turn! turn: aGreedTurn "Copyright(C) 1998 Masashi Umezawa" turn := aGreedTurn! ! !GreedPlayer methodsFor: 'private'! becomeBankrupt "Copyright(C) 1998 Masashi Umezawa" self triggerEvent: #bankrupt with: self. self isBankrupt: true! ! !GreedPlayer methodsFor: 'displaying'! displayStringWithScore "Copyright(C) 1998 Masashi Umezawa" ^super displayString , ' total:' , self totalScore printString! ! !GreedPlayer methodsFor: 'comparing'! <= aGreedPlayer "Copyright(C) 1998 Masashi Umezawa" ^self totalScore <= aGreedPlayer totalScore! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! GreedPlayer class instanceVariableNames: ''! !GreedPlayer class methodsFor: 'private-events'! constructEventsTriggered "Copyright(C) 1998 Masashi Umezawa" "Private - answer the collection of events that instances of the receiver can trigger." ^#(#checkContinueToPlay #bankrupt)! ! Die subclass: #GreedDie instanceVariableNames: 'isDisposed ' classVariableNames: '' poolDictionaries: '' category: 'Greed-Entity'! GreedDie comment: 'Copyright(C) 1998 Masashi Umezawa GreedDie is a special die which knows it should be rolled. Instance Variables: isDisposed indicates that it should be disposed (should not be rolled) '! !GreedDie methodsFor: 'initialize-release'! initialize "Copyright(C) 1998 Masashi Umezawa" super initialize. isDisposed := false! ! !GreedDie methodsFor: 'accessing'! isDisposed "Copyright(C) 1998 Masashi Umezawa" ^isDisposed! isDisposed: aBoolean "Copyright(C) 1998 Masashi Umezawa" isDisposed := aBoolean! !