[Squeak-fr] Quelqu'un pour lire mon code ?

stéphane ducasse ducasse at iam.unibe.ch
Mar 7 Sep 14:28:44 CEST 2004


C'est bien.

pour ton random
tu peux faire (a verifier)
	5 atRandom + 1
pour obtenir un nombre entre 1 et 6.

sinon tu as aussi max:

Moi je formatterai differemment  ;)

> minValue: aValue maxValue: aHigherValue
> 	(aValue < aHigherValue) ifTrue: [minValue:=aValue. maxValue := 
> aHigherValue]
> 	ifFalse: [self error: 'aHigherValue is an integer higher than 
> aValue'].! !

=>

> minValue: aValue maxValue: aHigherValue
> 	(aValue < aHigherValue)
>            ifTrue: [minValue:=aValue.
>                      maxValue := aHigherValue]
> 	      ifFalse: [self error: 'aHigherValue is an integer higher than 
> aValue'].! !


Bon tres bien j'espere que l'on verra la registration de RMLL en 
seaside bientot :)

Stef


On 7 sept. 04, at 12:56, Damien Cassou wrote:

> Bonjour,
>
> je viens juste d'écrire une petite classe pour jouer aux dès. Est-ce 
> que vous pourriez regarder mon code et me dire ce que vous en pensez ? 
> Toutes les critiques sont acceptées, car je souhaite écrire du beau 
> code smalltalk. :-) Dites moi tout ce que vous pensez de ces deux 
> classes.
>
> Merci beaucoup
>
> Damien
> Object subclass: #Dice
> 	instanceVariableNames: 'value minValue maxValue selected'
> 	classVariableNames: ''
> 	poolDictionaries: ''
> 	category: 'Games-Yatzee'!
> !Dice commentStamp: '<historical>' prior: 0!
> A class to make games with dice.
> Default dice is a 6 faced dice (1 to 6).
> Use the "run" method to throw the dice.
> You can select or unselect the dice (in the game, it means the player 
> takes the dice in his hands or not)!
>
>
> !Dice methodsFor: 'accessing' stamp: 'dc 9/7/2004 07:23'!
> maxValue
> 	^ maxValue! !
>
> !Dice methodsFor: 'accessing' stamp: 'dc 9/7/2004 07:20'!
> minValue
> ^minValue! !
>
> !Dice methodsFor: 'accessing' stamp: 'dc 9/7/2004 12:17'!
> minValue: aValue maxValue: aHigherValue
> 	(aValue < aHigherValue) ifTrue: [minValue:=aValue. maxValue := 
> aHigherValue]
> 	ifFalse: [self error: 'aHigherValue is an integer higher than 
> aValue'].! !
>
> !Dice methodsFor: 'accessing' stamp: 'dc 9/7/2004 08:17'!
> myValue: aValue
> 	(aValue between: minValue and: maxValue) ifTrue:	[value:= aValue] 
> ifFalse: [self halt]! !
>
> !Dice methodsFor: 'accessing' stamp: 'dc 9/7/2004 07:01'!
> value
> ^ value! !
>
>
> !Dice methodsFor: 'selection' stamp: 'dc 9/7/2004 12:37'!
> isSelected
> 	^selected! !
>
> !Dice methodsFor: 'selection' stamp: 'dc 9/7/2004 12:37'!
> select
> 	selected := true! !
>
> !Dice methodsFor: 'selection' stamp: 'dc 9/7/2004 12:36'!
> unselect
> selected := false! !
>
>
> !Dice methodsFor: 'modification' stamp: 'dc 9/7/2004 08:14'!
> run
> 	"Choose a random number between minValue and maxValue, store it and
> 	return it"
> 	self myValue: (self minValue to: self maxValue) atRandom.
> 	^ self value! !
>
>
> !Dice methodsFor: 'initialization' stamp: 'dc 9/7/2004 12:36'!
> initialize
> 	self minValue: 1 maxValue: 6;
> 		run;
> 		unselect.! !
>
> 
> TestCase subclass: #DiceTest
> 	instanceVariableNames: 'sixthDice1 sixthDice2 twelvethDice'
> 	classVariableNames: ''
> 	poolDictionaries: ''
> 	category: 'Games-Yatzee'!
> !DiceTest commentStamp: '<historical>' prior: 0!
> Test class to class Dice!
>
>
> !DiceTest methodsFor: 'as yet unclassified' stamp: 'dc 9/7/2004 07:40'!
> setUp
> 	sixthDice1 := Dice new.
> 	sixthDice2 := Dice new.
> 	twelvethDice := Dice new.
> 	twelvethDice minValue: 1 maxValue:12.! !
>
> !DiceTest methodsFor: 'as yet unclassified' stamp: 'dc 9/7/2004 08:18'!
> testRunBetween
> 	"Throw 100 times a dice and test if the value is between minValue and 
> maxValue"
> 	100 timesRepeat: [self assert: ((twelvethDice run) between: 1 and: 
> 12)]! !
>
> !DiceTest methodsFor: 'as yet unclassified' stamp: 'dc 9/7/2004 08:03'!
> testRunRandom
> 	"Try to run maxTimes throw of two dices. If the two dices are always
> 	equal, it's a problem"
> 	| maxTimes curTime finished |
> 	maxTimes := 100.
> 	curTime := 1.
> 	finished := false.
> 	[finished not
> 		and: [curTime < maxTimes]]
> 		whileTrue: [curTime := curTime + 1.
> 			sixthDice1 run ~= sixthDice2 run
> 				ifTrue: [finished := true]].
> 	self assert: finished! !
>
> !DiceTest methodsFor: 'as yet unclassified' stamp: 'dc 9/7/2004 12:42'!
> testSelection
> 	self deny: sixthDice1 isSelected.
> 	sixthDice1 select.
> 	self assert: sixthDice1 isSelected.
> 	sixthDice1 unselect.
> 	self deny: sixthDice1 isSelected.! !
> _______________________________________________
> Squeak-fr mailing list
> Squeak-fr at lists.squeakfoundation.org
> http://lists.squeakfoundation.org/listinfo/squeak-fr



Plus d'informations sur la liste de diffusion Squeak-fr