[SUBMISSION] The Quinto Game.

Edmund Ronald eronald at cmapx.polytechnique.fr
Wed Aug 14 06:37:07 UTC 2002


Here is the obligatory newbie game-with-squares contribution.

BTW. I have trouble with non-refreshing thumbnails in parts, and with the
thing showing up in the right bins. Please educate me about this and other
obvious shortcomings. 


BTW I would be willing to write a tutorial  for layout myself, if someone
would just tell me what the keywords etc are supposed to do. A couple of
one-line comments in the code would be appropriate here.

 Edmund

-------------- next part --------------
AlignmentMorph subclass: #Quinto
	instanceVariableNames: 'board minesDisplay timeDisplay helpText '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Quinto'!

!Quinto methodsFor: 'access' stamp: 'er 8/2/2002 23:18'!
board

	board ifNil:
		[board _ QuintoBoard new initialize].
	^ board! !

!Quinto methodsFor: 'access' stamp: 'er 8/2/2002 23:21'!
buildButton: aButton target: aTarget label: aLabel selector: aSelector
	"wrap a button or switch in an alignmentMorph to allow a row of buttons to fill space"

	| a |
	aButton 
		target: aTarget;
		label: aLabel;
		actionSelector: aSelector;
		borderColor: #raised;
		borderWidth: 2;
		color: color.
	a _ AlignmentMorph newColumn
		wrapCentering: #center; cellPositioning: #topCenter;
		hResizing: #spaceFill;
		vResizing: #shrinkWrap;
		color: color.
	a addMorph: aButton.
	^ a

! !

!Quinto methodsFor: 'access' stamp: 'er 8/14/2002 15:22'!
helpString

^ '
You win this game by highlighting all the buttons. My friend John Horton Conway who is rather better than me at mathematics solved the whole thing explicitly in an afternoon a long time ago in Cambridge. Morphic Quinto is a quick hack by a Squeak newbie and contains lots of orphan DNA from its ancestors. Some borrowed code comes from the Squeak Minesweeper by David Smith, which is itself an offspring of the Same game. 

Morphic *REALLY* needs more documentation.

Edmund Ronald
eronald at barbes.polytechnique.fr

'

! !

!Quinto methodsFor: 'access' stamp: 'er 7/9/2002 19:20'!
helpText

	helpText ifNil:
		[helpText _ PluggableTextMorph new
			width: self width; "board width;"
			editString: self helpString].
	^ helpText! !


!Quinto methodsFor: 'actions' stamp: 'er 8/2/2002 22:00'!
newGame
	self board resetBoard.! !


!Quinto methodsFor: 'initialize' stamp: 'er 8/2/2002 23:38'!
initialize
	super initialize.
	self listDirection: #topToBottom.
	self wrapCentering: #center; cellPositioning: #topCenter.
	self vResizing: #spaceFill.
	self hResizing: #spaceFill.
	self layoutInset: 3.
	color _ Color lightGray.
	self borderColor: #raised.
	self borderWidth: 2.
	self addMorph: self board.
	self addMorph: self makeControls.
	helpText _ nil.
	self extent:350 at 400.
"	self newGame."! !

!Quinto methodsFor: 'initialize' stamp: 'er 8/2/2002 22:02'!
makeControls
	| row |
	row _ AlignmentMorph newRow color: color;
				 borderWidth: 2;
				 layoutInset: 3.
		row borderColor: #inset.	
		row hResizing: #spaceFill;
		 vResizing: #shrinkWrap;
		 wrapCentering: #center;
		 cellPositioning: #leftCenter;
		 extent: 5 @ 5.
	row
		addMorph: (self
				buildButton: SimpleSwitchMorph new
				target: self
				label: '  Help  '
				selector: #help:).
	row
		addMorph: (self
				buildButton: SimpleButtonMorph new
				target: self
				label: '  Quit  '
				selector: #delete).
	row
		addMorph: (self
				buildButton: SimpleButtonMorph new
				target: self
				label: '  New game  '
				selector: #newGame).
	^ row! !


!Quinto methodsFor: 'as yet unclassified' stamp: 'er 7/9/2002 19:20'!
help: helpState

	helpState
		ifTrue: [self addMorphBack: self helpText]
		ifFalse: [helpText delete]! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Quinto class
	instanceVariableNames: ''!

!Quinto class methodsFor: 'new-morph participation' stamp: 'er 7/9/2002 19:29'!
descriptionForPartsBin
	^ self partName: 	'Quinto'
		categories:		#('Games')
		documentation:	'Hilite All Buttons'! !


AlignmentMorph subclass: #QuintoBoard
	instanceVariableNames: 'xSwitch '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Quinto'!

!QuintoBoard methodsFor: 'initialization' stamp: 'er 8/3/2002 16:15'!
initialize
	|b xRow  xrr tmp r ablock |
super initialize boardLayout.
self extent:(300 at 300).
xSwitch_Array new:25.
1 to: 25 do:[:i| xSwitch at:i put:QuintoSwitch new.
				ablock_([self quintoButtonPressed:i]fixTemps).
				((xSwitch at:i) onAction:ablock) 								    								offAction:ablock].

b_0.
xRow_Array new:5.
1 to: 5 do: [:i| 
	r_RectangleMorph new.
	self rowLayout:r.
	xrr_Array new:5.

	1 to: 5 do: [:n| 
		"The Cells, with their inset buttons"
		xrr at:n put:(RectangleMorph new).
		self cellLayout:(xrr at:n).

		b_b+1.
		tmp_PluggableButtonMorph on:(xSwitch at:b).
		self buttonLayout:tmp.
		(xrr at:n) addMorph: tmp.
			].

	r addAllMorphs:xrr.
	xRow at:i put:r.
].

self addAllMorphs:xRow.
self resetBoard.
! !

!QuintoBoard methodsFor: 'initialization' stamp: 'er 8/3/2002 16:19'!
resetBoard
	"clear all switches"
1 to: 25 do:[:i| (xSwitch at:i) clear].
! !


!QuintoBoard methodsFor: 'actions' stamp: 'er 7/27/2002 13:23'!
quintoButtonPressed:b
|c x y|
c_b-1.
x_c\\5.
y_c//5.
Transcript cr.
(x>0)ifTrue:[(xSwitch at:(b-1)) toggle].
(x<4)ifTrue:[(xSwitch at:(b+1)) toggle].
(y>0)ifTrue:[(xSwitch at:(b-5)) toggle].
(y<4)ifTrue:[(xSwitch at:(b+5)) toggle].! !


!QuintoBoard methodsFor: 'layout' stamp: 'er 7/24/2002 16:39'!
boardLayout

	"I set the layout parameters for the Quinto Board.
	 which is an AlignmentMorph"

self layoutPolicy: TableLayout new.
self cellPositioning: #topLeft.
self rubberBandCells: true.
self listDirection: #topToBottom.
self layoutInset: 20. "content inset in frame by this amount"
self useRoundedCorners.
^self! !

!QuintoBoard methodsFor: 'layout' stamp: 'er 7/28/2002 01:55'!
buttonLayout:b.
	"b is a PluggableButtonMorph"
		b hResizing: #spaceFill .
		b vResizing: #spaceFill .
		b useRoundedCorners.	
		b borderWidth:0.	
		b onColor:(Color white) offColor:(Color black).
	^self
! !

!QuintoBoard methodsFor: 'layout' stamp: 'er 7/24/2002 16:22'!
cellLayout:c.
	"c is a cell-inset"
	c borderWidth:0.
	c layoutPolicy: TableLayout new.
	c cellPositioning: #topLeft.
	c rubberBandCells: true.
	c listDirection: #leftToRight.
	c hResizing: #spaceFill .
	c vResizing: #spaceFill .
	c layoutInset: 2.
	^self
! !

!QuintoBoard methodsFor: 'layout' stamp: 'er 7/24/2002 16:38'!
rowLayout:r.
	"r is a RectangleMorph row of cell-insets"
	r layoutPolicy: TableLayout new.
	r cellPositioning: #topLeft.
	r rubberBandCells: true.
	r listDirection: #leftToRight.
	r borderWidth:0.
	r layoutInset: 0.
	r hResizing: #spaceFill .
	r vResizing: #spaceFill .

	^self
! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

QuintoBoard class
	instanceVariableNames: ''!

!QuintoBoard class methodsFor: 'as yet unclassified' stamp: 'er 7/28/2002 23:43'!
includeInNewMorphMenu

	^true! !


Switch subclass: #QuintoSwitch
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Quinto'!

!QuintoSwitch methodsFor: 'as yet unclassified' stamp: 'er 7/27/2002 13:28'!
toggle
	"Toggle the state of the receiver.  'self change' is sent. The receiver's off action is NOT executed."

	self isOn
		ifTrue: 
			[on _ false.
			self changed]
		ifFalse: 
			[on _ true.
			self changed]! !


More information about the Squeak-dev mailing list