[GOODIE] Symbolitry

Markus Gaelli gaelli at emergent.de
Mon Dec 3 22:44:48 UTC 2001


Hi folks,

here comes a new toy called "Symbolitry".

If you could help me with the following known bugs:

- Only the rectangle-symbols are layouted correctly, neither the triangles
nor the hearts are.
This is kind of solved with stepping right now as you can see... :-(
- Further on, when restarting a game the countdown is not updated, as long
as you don''t move the mouse on the board.
- Also there seem to be dangling instances, after quitting symbolitry.
The only class-variables I use should be ok, so any other ideas?

Have fun,

Markus

-------------- next part --------------
'From Squeak3.2alpha of 1 November 2001 [latest update: #4566] on 3 December 2001 at 11:40:39 pm'!
"Change Set:		Symbolitry
Date:			3 December 2001
Author:			Markus Gaelli

Symbolitry v1.0

Goal of the game
Find symetric triples by selecting cards.

Introduction
Just click on a card. Red frames will show your selected cards.
If you choose the third card, the computer will decide, if your selected cards are symetric.

If they are, it will take this cards away and deal three new cards, otherwise the cards will be deselected.

So what does symetric mean here?

We have four different aspects on each card: the kind of the symbol, the number, the color and the fillstyle of each symbol.

We have three different kind of symbols: hearts, rectangles and triangles; a symbolitry-card has one, two, or three symbols, which could be red, blue, or green; the fillstyle of each symbol can be solid, empty, or patternd. 
Three cards are symetric, if each aspect is different on each card or if it is the same on each card.
It is not symetric, if any aspect is equal on exactly two of the cards.

Credits

Credits go to the author of Mindthumps. Mindthumps is a shareware game for the Mac written by Andrew Tomazos for Stairways-Software, which is quite symetric to Symbolitry ;-) , though many features of Mindthumps still have to be implemented here.

Also there is a card game in Germany called ""Set"" from a company named ""Ravensburger"", which does a ""similar job"" as Symbolitry.
And last but not least certainly to the whole squeak community, which is a great pleasure to be part of.

License

Symbolitry is released under the squeak license.

Known bugs

v 1.0: Only the rectangle-symbols are layouted correctly, neither the triangles nor the hearts are.
This is kind of solved with stepping right now as you can see... :-(
Further on, when restarting a game the countdown is not updated, as long as you don''t move the mouse on the board.
Also there seem to be dangling instances. The only class-variables I use should be ok, maybe it is somewhere in the event-handling?

Also missing are highscores, sounds, options, different game-modes and maybe, sometime, it should be ported to Nebraska, so that we could play games against each other.

I would really be very happy about bugfixes or enhancements.

Have fun...

Markus Gaelli 
gaelli at emergent.de
December 2001"!

BorderedMorph subclass: #CellMorph
	instanceVariableNames: 'sheetPosition '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!
TextMorph subclass: #CountdownMorph
	instanceVariableNames: 'endtime '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!
BorderedMorph subclass: #SheetMorph
	instanceVariableNames: 'cells '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!
BorderedMorph subclass: #Symbolitry
	instanceVariableNames: 'board countdown score '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Games'!
Symbolitry class
	instanceVariableNames: ''!
SheetMorph subclass: #SymbolitryBoard
	instanceVariableNames: 'stack selectedCards '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Games'!
SymbolitryBoard class
	instanceVariableNames: ''!
BorderedMorph subclass: #SymbolitryCard
	instanceVariableNames: 'indices '
	classVariableNames: 'FillColors '
	poolDictionaries: ''
	category: 'Morphic-Games'!
SymbolitryCard class
	instanceVariableNames: ''!

!Array2D methodsFor: 'accessing' stamp: 'mga 11/1/2001 20:00'!
atPoint: aPoint
	^self at: aPoint x at: aPoint y! !

!Array2D methodsFor: 'accessing' stamp: 'mga 11/1/2001 21:31'!
atPoint: aPoint put: anObject
	self at: aPoint x at: aPoint y put: anObject! !


!CellMorph methodsFor: 'accessing' stamp: 'mga 11/27/2001 21:37'!
directNeighbours 
	^self directNeighbourIndices
			collect: [:each | self sheet pointAt: each]! !

!CellMorph methodsFor: 'accessing' stamp: 'mga 11/27/2001 21:39'!
neighbours 
	^self neighbourIndices
			collect: [:each | self sheet pointAt: each]! !

!CellMorph methodsFor: 'accessing' stamp: 'mga 11/6/2001 23:56'!
sheet
	^self owner! !

!CellMorph methodsFor: 'accessing' stamp: 'mga 11/12/2001 09:19'!
sheetPosition
	^sheetPosition! !

!CellMorph methodsFor: 'initialization' stamp: 'mga 11/23/2001 00:57'!
initialize
	super initialize.	
	self 
		borderWidth: 1;
		color: Color transparent;
		borderColor: Color white;
		layoutPolicy: ProportionalLayout new;
		hResizing: #spaceFill; 
		vResizing: #spaceFill.! !

!CellMorph methodsFor: 'initialization' stamp: 'mga 11/6/2001 01:45'!
initializeFor: aPoint
	sheetPosition:= aPoint! !

!CellMorph methodsFor: 'testing' stamp: 'mga 11/16/2001 00:02'!
isCell
	^true! !


!CellMorph class methodsFor: 'instance creation' stamp: 'mga 11/6/2001 01:33'!
for: aPoint
	^self new initializeFor: aPoint! !


!CountdownMorph methodsFor: 'stepping and presenter' stamp: 'mga 11/3/2001 14:45'!
step
	self contents: self secondsLeft printString.
	self secondsLeft <= 0 ifTrue: [
		self stopStepping.
		self owner countdownFinished]! !

!CountdownMorph methodsFor: 'stepping and presenter' stamp: 'mga 11/16/2001 22:58'!
stepTime
	^50
! !

!CountdownMorph methodsFor: 'accessing' stamp: 'mga 11/13/2001 20:51'!
increment: someSeconds
	self secondsLeft: self secondsLeft + someSeconds! !

!CountdownMorph methodsFor: 'accessing' stamp: 'mga 11/3/2001 14:45'!
secondsLeft
	^(endtime - Time primMillisecondClock) // 1000! !

!CountdownMorph methodsFor: 'accessing' stamp: 'mga 11/23/2001 01:53'!
secondsLeft: someSeconds
	endtime := (Time primMillisecondClock + (someSeconds * 1000)) max: 0
	! !


!Point methodsFor: 'truncation and round off' stamp: 'mga 11/10/2001 13:04'!
ceiling
	(x isInteger and: [y isInteger]) ifTrue: [^ self].
	 ^x ceiling at y ceiling! !

!Point methodsFor: 'truncation and round off' stamp: 'mga 11/10/2001 13:04'!
floor
	(x isInteger and: [y isInteger]) ifTrue: [^ self].
	 ^(x floor)@(y floor)! !

!Point methodsFor: 'intervals' stamp: 'mga 11/1/2001 20:11'!
to: aPoint
	^self to: aPoint by: (1 at 1)! !

!Point methodsFor: 'intervals' stamp: 'mga 11/1/2001 20:11'!
to: aPoint by: anIndexPoint
	|aCollection|
	aCollection := OrderedCollection new.
	self y to: aPoint y by: anIndexPoint y do: [:anY |
		self x to: aPoint x by: anIndexPoint x do: [:anX |
			aCollection add: (anX at anY)]].
	^aCollection! !

!Point methodsFor: 'enumerating' stamp: 'mga 11/1/2001 20:01'!
to: aPoint do: aBlock
	(self to: aPoint) do: aBlock! !


!SheetMorph methodsFor: 'initialization' stamp: 'mga 11/15/2001 23:43'!
initialize
	super initialize.
	self 
		color: Color black;
		extent: 300 at 300;
		layoutPolicy: ProportionalLayout new! !

!SheetMorph methodsFor: 'initialization' stamp: 'mga 11/23/2001 01:16'!
initializeCells
	(1 at 1 to: self sheetExtent) do: [:anIndexPoint | 
		self addCell: (self cellClass for: anIndexPoint)]
	! !

!SheetMorph methodsFor: 'initialization' stamp: 'mga 11/23/2001 01:10'!
initializeFor: aPoint
	cells:=Array2D extent: aPoint.
	self 
		initializeCells;
		layoutEqualDistance! !

!SheetMorph methodsFor: 'initialization' stamp: 'mga 11/23/2001 01:05'!
layoutEqualDistance
	cells do: [:aCell | 
		aCell 
			layoutFrame:
				(LayoutFrame
					fractions: (((aCell sheetPosition-(1 at 1))/self sheetExtent) extent: ((1 at 1)/self sheetExtent))
					offsets: nil)]! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/23/2001 01:15'!
addCell: aCell
	cells 
		atPoint: aCell sheetPosition 
		put: aCell.
	self addMorph: aCell! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/23/2001 01:15'!
addCells: someCells
	someCells do: [:aCell | self addCell: aCell]
	! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/23/2001 01:31'!
addColumnLast
	
	|aNewArray|
	aNewArray := Array2D extent: (self sheetExtent + (1 at 0)).
	cells do: [:aCell | 
		 aNewArray atPoint: aCell sheetPosition put: aCell].
	cells := aNewArray.
	((self sheetExtent x at 1) to: self sheetExtent) do: [:anIndexPoint |
		self addCell: (self cellClass for: anIndexPoint)].
	self layoutEqualDistance
	! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/17/2001 17:24'!
addMorphsCentered: someMorphs toCellPositions: somePositions

	somePositions with: someMorphs do: [:aPoint :aMorph| (self atPoint: aPoint) addMorphCentered: aMorph]! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/10/2001 17:17'!
atPoint: aPoint
	^cells atPoint: (aPoint - (1 at 1)) \\ self sheetExtent + (1 at 1)! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/7/2001 00:26'!
cellClass
	^CellMorph! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/18/2001 22:50'!
cellEntries
	|anOrderedCollection|
	anOrderedCollection:=OrderedCollection new.
	self cells do: [:aCellMorph | 
		anOrderedCollection addAll: aCellMorph submorphs].
	^anOrderedCollection! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/1/2001 19:54'!
cells
	^cells! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/19/2001 01:42'!
deleteCellEntries
	self cellEntries do: [:each | each delete]! !

!SheetMorph methodsFor: 'accessing' stamp: 'mga 11/6/2001 23:58'!
sheetExtent
	^cells extent! !


!SheetMorph class methodsFor: 'instance creation' stamp: 'mga 11/1/2001 20:20'!
for: aPoint
	^self new initializeFor: aPoint! !

!SheetMorph class methodsFor: 'instance creation' stamp: 'mga 11/7/2001 00:11'!
openFor: aPoint
	"self openFor: (20 at 20)"
	
	^(self for: aPoint) openInWorld! !


!Symbolitry methodsFor: 'constants' stamp: 'mga 11/19/2001 02:04'!
bonusSeconds
	^15! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 11/30/2001 01:12'!
defaultBoardExtent
	^4 @ 3! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 12/3/2001 22:30'!
defaultExtent
	^400 at 400! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 12/3/2001 23:10'!
helpText
	^'Symbolitry v1.0

Goal of the game
Find symetric triples by selecting cards.

Introduction
Just click on a card. Red frames will show your selected cards.
If you choose the third card, the computer will decide, if your selected cards are symetric.

If they are, it will take this cards away and deal three new cards, otherwise the cards will be deselected.

So what does symetric mean here?

We have four different aspects on each card: the kind of the symbol, the number, the color and the fillstyle of each symbol.

We have three different kind of symbols: hearts, rectangles and triangles; a symbolitry-card has one, two, or three symbols, which could be red, blue, or green; the fillstyle of each symbol can be solid, empty, or patternd. 
Three cards are symetric, if each aspect is different on each card or if it is the same on each card.
It is not symetric, if any aspect is equal on exactly two of the cards.

Credits

Credits go to the author of Mindthumps. Mindthumps is a shareware game for the Mac written by Andrew Tomazos for Stairways-Software, which is quite symetric to Symbolitry ;-) , though many features of Mindthumps still have to be implemented here.

Also there is a card game in Germany called "Set" from a company named "Ravensburger", which does a "similar job" as Symbolitry.
And last but not least certainly to the whole squeak community, which is a great pleasure to be part of.

License

Symbolitry is released under the squeak license.

Known bugs

v 1.0: Only the rectangle-symbols are layouted correctly, neither the triangles nor the hearts are.
This is kind of solved with stepping right now as you can see... :-(
Further on, when restarting a game the countdown is not updated, as long as you don''t move the mouse on the board.
Also there seem to be dangling instances. The only class-variables I use should be ok, maybe it is somewhere in the event-handling?

Also missing are highscores, sounds, options, different game-modes and maybe, sometime, it should be ported to Nebraska, so that we could play games against each other.

I would really be very happy about bugfixes or enhancements.

Have fun...

Markus Gaelli 
gaelli at emergent.de
December 2001'


	! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 11/23/2001 00:24'!
malusSeconds
	^3! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 11/22/2001 23:39'!
playingTime
	^40! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 11/23/2001 11:51'!
pointsForSuccessfullImpossible
	^5! !

!Symbolitry methodsFor: 'constants' stamp: 'mga 11/23/2001 11:51'!
pointsForSuccessfullSelection
	^1! !

!Symbolitry methodsFor: 'initialization' stamp: 'mga 12/3/2001 22:53'!
addBoard
	|aLayoutFrame|
	board:=SymbolitryBoard for: self defaultBoardExtent.
	aLayoutFrame := LayoutFrame new.
	aLayoutFrame
		bottomFraction: 1 offset: -50;
		leftFraction: 0 offset: 0;
		rightFraction: 1 offset: 0;
		topFraction: 0 offset: 0.
	self addMorph: board fullFrame: aLayoutFrame.
	board 
		initializeStack;
		dialNewCards;
		when: #successfullSelection send: #successfullSelection to: self;
		when: #unsuccessfullSelection send: #unsuccessfullSelection to: self.
	! !

!Symbolitry methodsFor: 'initialization' stamp: 'mga 11/23/2001 01:46'!
initialize
	super initialize.
	self 
		addBoard;
		initializeOuterBoard;
		initializeScoreRow;
		setCountdown;
		extent: self defaultExtent;
		center: Display center! !

!Symbolitry methodsFor: 'initialization' stamp: 'mga 11/19/2001 01:04'!
initializeOuterBoard
	self
		layoutPolicy: ProportionalLayout new;
		useRoundedCorners;
		color: Color blue muchLighter;
		position: Display center - self center.
	! !

!Symbolitry methodsFor: 'initialization' stamp: 'mga 11/23/2001 00:26'!
initializeScoreRow
	countdown:= CountdownMorph new.
	self 
		addMorph: (StringMorph contents: 'Time left: ') 
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -20;
				leftFraction: 0 offset: 20;
				yourself);
		addMorph: countdown			
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -18;
				leftFraction: 0 offset: 80;
				yourself);
		addMorph: (StringMorph contents: 'Score: ')
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -20;
				leftFraction: 0 offset: 100;
				yourself).
	score := StringMorph contents: '000'.
	self		
		addMorph: score
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -20;
				leftFraction: 0 offset: 145;
				yourself);	
		addMorph: self boardImpossibleButton
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -18;
				leftFraction: 0 offset: 180;
				yourself);
		addMorph: self helpButton
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -18;
				leftFraction: 0 offset: 295;
				yourself);
		addMorph: self quitButton
		fullFrame: 
			((LayoutFrame new)
				bottomFraction: 1 offset: -18;
				leftFraction: 0 offset: 340;
				yourself)! !

!Symbolitry methodsFor: 'initialization' stamp: 'mga 11/22/2001 01:02'!
setCountdown
	countdown secondsLeft: self playingTime! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/23/2001 11:48'!
boardImpossible
	|someMatches|
	someMatches:=board allMatches.	
	someMatches isEmpty 
		ifTrue: [
			board stack size < 3 ifTrue: [^self newGame].
			^self successfullImpossible].
	board deselectAllCards.
	self 
		showMatches: someMatches;
		unsuccessfullSelection! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/19/2001 01:49'!
countdownFinished
	self newGame! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/22/2001 00:40'!
help
	| window helpMorph |

	window _ SystemWindow labelled: 'Symbolitry Help'.
	window model: self.
	helpMorph _ (PluggableTextMorph new editString: self helpText)
				 lock.
	window addMorph: helpMorph frame: (0 at 0 extent: 1 at 1).
	window openInWorld.
! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/23/2001 11:50'!
incrementScore: anInteger
	score contents: ((score contents asNumber + 1000 + anInteger) asString copyFrom: 2 to: 4)! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/23/2001 01:45'!
newGame
	self showAllMatches.
	score contents: '000'.
	board delete.
	self 
		addBoard; 
		setCountdown;
		startCountdown
	! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/22/2001 01:14'!
showAllMatches
	self showMatches: board allMatches! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/22/2001 01:12'!
showMatches: someMatches
	self stopCountdown.
	someMatches do: [:someCards |
			3 timesRepeat: [
				someCards do: [:aCard | aCard beSelected].
				self refreshWorld.
				(Delay forMilliseconds: 200) wait.
				someCards do: [:aCard | aCard beDeselected ].
				self refreshWorld.
				(Delay forMilliseconds: 200) wait]].
	self startCountdown! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/22/2001 01:07'!
startCountdown
	countdown startStepping! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/22/2001 01:12'!
stopCountdown
	countdown stopStepping! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/23/2001 11:51'!
successfullImpossible
	board addColumnLast.
	1 to: board sheetExtent y do: [:anY | board dialNewCardAtPoint: (board sheetExtent x at anY)].
	countdown increment: self bonusSeconds.
	self incrementScore: self pointsForSuccessfullImpossible! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/23/2001 11:50'!
successfullSelection
	countdown increment: self bonusSeconds.
	self incrementScore: self pointsForSuccessfullSelection! !

!Symbolitry methodsFor: 'action' stamp: 'mga 11/23/2001 01:51'!
unsuccessfullSelection
	countdown increment: (0 - self malusSeconds)! !

!Symbolitry methodsFor: 'accessing' stamp: 'mga 9/30/2001 16:31'!
board
	^board! !

!Symbolitry methodsFor: 'accessing' stamp: 'mga 11/23/2001 00:22'!
boardImpossibleButton
	^SimpleButtonMorph new 
		target: self;
		borderColor: #raised; 
		borderWidth: 2; 
		color: self color;
		label: 'Board impossible';		
		actionSelector: #boardImpossible;
		setBalloonText: 'Press this, if you think there are no symetric triples.';
		yourself! !

!Symbolitry methodsFor: 'accessing' stamp: 'mga 11/22/2001 00:41'!
helpButton
	^SimpleButtonMorph new 
		target: self;
		borderColor: #raised; 
		borderWidth: 2; 
		color: self color;
		label: 'Help';		
		actionSelector: #help;
		setBalloonText: 'Opens a help window';
		yourself! !

!Symbolitry methodsFor: 'accessing' stamp: 'mga 11/23/2001 00:27'!
quitButton
	^SimpleButtonMorph new 
		target: self;
		borderColor: #raised; 
		borderWidth: 2; 
		color: self color;
		label: 'Quit';		
		actionSelector: #delete;
		setBalloonText: 'Quits Symbolitry';
		yourself! !


!Symbolitry class methodsFor: 'parts bin' stamp: 'mga 12/3/2001 22:29'!
descriptionForPartsBin
	^ self partName:	'Symbolitry'
		categories:		#('Games')
		documentation:	'Symbolitry v1.0 
A game for agile minds'! !


!SymbolitryBoard methodsFor: 'accessing' stamp: 'mga 8/13/2001 22:13'!
allMatches
	|someMatches|
	someMatches := OrderedCollection new.
	self displayedCards combinations: 3 atATimeDo: [:each | 
		(self isSymetric: each) ifTrue: [	someMatches add: each copy]].
	^someMatches! !

!SymbolitryBoard methodsFor: 'accessing' stamp: 'mga 11/18/2001 22:51'!
displayedCards
	^self cellEntries! !

!SymbolitryBoard methodsFor: 'accessing' stamp: 'mga 8/11/2001 17:08'!
selectedCards
	^selectedCards! !

!SymbolitryBoard methodsFor: 'accessing' stamp: 'mga 11/22/2001 23:56'!
stack
	^stack! !

!SymbolitryBoard methodsFor: 'initialization' stamp: 'mga 11/21/2001 01:33'!
initializeBoard
	self 
		color: Color transparent;
		borderWidth: 0;
		layoutPolicy: ProportionalLayout new.
	stack:= OrderedCollection new.
	selectedCards := OrderedCollection new.! !

!SymbolitryBoard methodsFor: 'initialization' stamp: 'mga 11/21/2001 01:23'!
initializeFor: aPoint
	super initializeFor: aPoint.
	self initializeBoard.
	! !

!SymbolitryBoard methodsFor: 'initialization' stamp: 'mga 10/20/2001 17:28'!
initializeStack
	stack _ OrderedCollection new.
	(1 to: 3)
		asDigitsToPower: 4
		do: [:each | stack add: each copy].
	stack _ stack shuffled! !

!SymbolitryBoard methodsFor: 'testing' stamp: 'mga 11/18/2001 21:38'!
isSelected: aCard 
	^selectedCards includes: aCard! !

!SymbolitryBoard methodsFor: 'testing' stamp: 'mga 8/13/2001 21:31'!
isSymetric: someCards
	| aSet |
	^((1 to: 4) detect: [:anIndex | 
		aSet := (someCards collect: [:aCard | aCard indices at: anIndex]) asSet.
		aSet size = 2] ifNone: [nil]) isNil! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/22/2001 00:16'!
deselectAllCards
	selectedCards do: [:each | each beDeselected].
	selectedCards:=OrderedCollection new.! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/23/2001 00:02'!
dialCard: aCard atPoint: aPosition
	(self atPoint: aPosition) addMorphCentered: aCard! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/21/2001 01:10'!
dialNewCardAtPoint: aPoint 
	self 
		dialCard: (SymbolitryCard for: stack removeLast)
		atPoint: aPoint! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/21/2001 01:29'!
dialNewCards
	(1 at 1 to: self sheetExtent) do: [:aPoint | self dialNewCardAtPoint: aPoint]! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/22/2001 00:15'!
removeCard: aCard
	selectedCards  remove: aCard! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/23/2001 00:05'!
selectCard: aCard
	aCard beSelected.
	self selectedCards add: aCard.
	self selectedCards size < 3 ifTrue: [^ self].
	(self isSymetric: self selectedCards)
		ifTrue: [
			self 
				takeAwaySymetricSelection;
				trigger: #successfullSelection]
		ifFalse: [self trigger: #unsuccessfullSelection].
	self deselectAllCards! !

!SymbolitryBoard methodsFor: 'action' stamp: 'mga 11/21/2001 02:00'!
takeAwaySymetricSelection
	stack size >= 3 ifTrue: [
		| somePositions | 
		somePositions _ self selectedCards collect: [:e | e sheetPosition].
		somePositions do: [:aPoint | self dialNewCardAtPoint: aPoint]].
	self selectedCards do: [:each | each delete].
	
	! !


!SymbolitryBoard class methodsFor: 'examples' stamp: 'mga 11/21/2001 02:05'!
example
	"self example openInWorld"

	|anInstance|
	anInstance := 
		(self for: 3 at 4) 
			extent: 400 at 400;
			initializeStack;
			borderWidth: 2;
			borderColor: Color black;
			dialNewCards;
			yourself.
	anInstance cells do: [:e | e borderColor: Color gray].
	^anInstance

	! !

!SymbolitryBoard class methodsFor: 'examples' stamp: 'mga 11/21/2001 01:16'!
exampleAllDifferent
	"self exampleAllDifferent openInWorld"

	^(self for: 3 at 1) 
		extent: 300 at 300;
		dialCard: (SymbolitryCard for: #(3 2 1 3)) atPoint: 1 at 1;
		dialCard: (SymbolitryCard for: #(2 1 2 1)) atPoint: 2 at 1;
		dialCard: (SymbolitryCard for: #(1 3 3 2)) atPoint: 3 at 1;
		openInWorld



	! !

!SymbolitryBoard class methodsFor: 'examples' stamp: 'mga 11/21/2001 01:18'!
exampleAsymetric
	"self exampleAsymetric openInWorld"

	^(self for: 3 at 1) 
		extent: 300 at 300;
		dialCard: (SymbolitryCard for: #(3 2 1 3)) atPoint: 1 at 1;
		dialCard: (SymbolitryCard for: #(2 2 2 1)) atPoint: 2 at 1;
		dialCard: (SymbolitryCard for: #(1 3 3 2)) atPoint: 3 at 1;
		openInWorld



	! !

!SymbolitryBoard class methodsFor: 'examples' stamp: 'mga 11/21/2001 01:16'!
exampleFullRedForms
	"self exampleFullRedForms openInWorld"

	^(self for: 3 at 1) 
		extent: 300 at 300;
		dialCard: (SymbolitryCard for: #(3 1 1 1)) atPoint: 1 at 1;
		dialCard: (SymbolitryCard for: #(2 2 1 1)) atPoint: 2 at 1;
		dialCard: (SymbolitryCard for: #(1 3 1 1)) atPoint: 3 at 1;
		openInWorld



	! !

!SymbolitryBoard class methodsFor: 'examples' stamp: 'mga 11/21/2001 01:15'!
exampleFullRedRectangles
	"self exampleFullRedRectangles openInWorld"

	^(self for: 3 at 1) 
		extent: 300 at 300;
		dialCard: (SymbolitryCard for: #(1 1 1 1)) atPoint: 1 at 1;
		dialCard: (SymbolitryCard for: #(1 2 1 1)) atPoint: 2 at 1;
		dialCard: (SymbolitryCard for: #(1 3 1 1)) atPoint: 3 at 1;
		openInWorld



	! !

!SymbolitryBoard class methodsFor: 'instance creation' stamp: 'mga 1/1/1904 13:21'!
for: anExtent
	^self new initializeFor: anExtent! !


!SymbolitryCard methodsFor: 'initialization' stamp: 'mga 11/18/2001 22:58'!
initialize
	super initialize.
	self 
		useRoundedCorners;
		color: self emptyColor;
		borderWidth: 1;
		beDeselected;
		layoutPolicy: ProportionalLayout new;
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		layoutFrame:
			(LayoutFrame
				fractions: (0.1 at 0.1 extent: (0.8 at 0.8)) 
				offsets: nil)! !

!SymbolitryCard methodsFor: 'initialization' stamp: 'mga 11/18/2001 22:14'!
initializeFor: someIndices 
	| anY |
	indices _ someIndices.
	1
		to: someIndices second
		do: [:aNumberIndex | 
			| aSymbol aRectangle| 
			aSymbol _ self symbolFor: someIndices first.
			aSymbol
				borderColor: (self class colors at: someIndices third);
				color: ((FillColors at: someIndices third)
						at: someIndices last).	
			anY:=  (0.5*(2*aNumberIndex-someIndices second+1)*(self spaceSize+self symbolSize))+(0.5*self spaceSize).
			aRectangle _ 0.1 at anY extent: (0.8 @ self symbolSize).
		self 
			addMorph: aSymbol 
			fullFrame: (LayoutFrame fractions: aRectangle offsets: nil)]! !

!SymbolitryCard methodsFor: 'event handling' stamp: 'mga 8/11/2001 16:53'!
handlesMouseDown: evt
	^true! !

!SymbolitryCard methodsFor: 'event handling' stamp: 'mga 11/22/2001 00:17'!
mouseDown: evt
	(self board isSelected: self)
		ifTrue: [
			self board removeCard: self.
			self beDeselected]
		ifFalse: [self board selectCard: self]! !

!SymbolitryCard methodsFor: 'action' stamp: 'mga 11/13/2001 19:55'!
beDeselected
	self 
		borderColor: self deselectedBorderColor;
		borderWidth: self deselectedBorderWidth! !

!SymbolitryCard methodsFor: 'action' stamp: 'mga 11/18/2001 21:39'!
beSelected
	self 
		borderWidth: self selectedBorderWidth;
		borderColor: Color red! !

!SymbolitryCard methodsFor: 'action' stamp: 'mga 11/23/2001 11:36'!
step
	self layoutChanged! !

!SymbolitryCard methodsFor: 'accessing' stamp: 'mga 11/18/2001 22:52'!
board
	^self cell sheet! !

!SymbolitryCard methodsFor: 'accessing' stamp: 'mga 11/18/2001 22:52'!
cell
	^self owner! !

!SymbolitryCard methodsFor: 'accessing' stamp: 'mga 8/11/2001 17:30'!
indices
	^indices! !

!SymbolitryCard methodsFor: 'accessing' stamp: 'mga 11/18/2001 22:53'!
sheetPosition
	^self cell sheetPosition! !

!SymbolitryCard methodsFor: 'accessing' stamp: 'mga 9/18/2001 16:16'!
spaceSize
	^ self spaceSymbolRatio*self symbolSize! !

!SymbolitryCard methodsFor: 'accessing' stamp: 'mga 9/18/2001 16:16'!
symbolSize
	^1 / (((self symbolsPerCard+1)*self spaceSymbolRatio)+(self symbolsPerCard))! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:50'!
deselectedBorderColor
	
	^Color blue lighter! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:55'!
deselectedBorderWidth
	^1! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:47'!
emptyColor
	^self class emptyColor! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:28'!
heartMorph
	^(CurveMorph vertices: {25 at 46. 0 at 0. 18 at 0. 25 at 11. 30 at 0. 49 at 0} color: self emptyColor borderWidth: 2 borderColor: self emptyColor)
		beSmoothCurve;	
		borderWidth: self symbolBorderWidth;
		yourself! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:28'!
rectangleMorph
	^RectangleMorph new
		borderWidth: self symbolBorderWidth;
		yourself! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:54'!
selectedBorderWidth
	^4! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 9/18/2001 16:14'!
spaceSymbolRatio
	^1/2! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:44'!
symbolBorderWidth
	^2! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:35'!
symbolFor: anInteger
	^self perform: (self symbolSymbols at: anInteger)! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:36'!
symbolSymbols
	^#(#rectangleMorph #triangleMorph #heartMorph)! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:37'!
symbolsPerCard
	^3! !

!SymbolitryCard methodsFor: 'constants' stamp: 'mga 11/13/2001 19:59'!
triangleMorph
	^(PolygonMorph 
		vertices: {0 at 40 . 35@((40 *(1- (3 sqrt) / 2)) rounded) .70 at 40. 0 at 40} 
		color: self emptyColor 
		borderWidth: 2 
		borderColor: self emptyColor)
			borderWidth: self symbolBorderWidth;
			yourself! !


!SymbolitryCard class methodsFor: 'instance creation' stamp: 'mga 11/6/2001 01:29'!
for: someIndices
	^self new initializeFor: someIndices! !

!SymbolitryCard class methodsFor: 'constants' stamp: 'mga 8/11/2001 12:47'!
colors
	^{Color red. Color blue. Color green}! !

!SymbolitryCard class methodsFor: 'constants' stamp: 'mga 8/11/2001 13:49'!
emptyColor
	^Color white! !

!SymbolitryCard class methodsFor: 'constants' stamp: 'mga 8/11/2001 15:58'!
numberOfFillSymbols
	^3! !

!SymbolitryCard class methodsFor: 'class initialization' stamp: 'mga 11/13/2001 19:43'!
initialize
	"self initialize"
	
	self initializeFillColors! !

!SymbolitryCard class methodsFor: 'class initialization' stamp: 'mga 11/13/2001 20:06'!
initializeFillColors
	FillColors := Array new: self colors size.
	1 to: self colors size do: [:aColorIndex | 
		|aColor|
		aColor:=self colors at: aColorIndex.
		FillColors at:aColorIndex put: (Array new: self numberOfFillSymbols).
		(FillColors at: aColorIndex) 
			at: 1 put: aColor;
			at: 2 put: self emptyColor;
			at: 3 put: (self patternColorFor: aColor)].
	 ! !

!SymbolitryCard class methodsFor: 'class initialization' stamp: 'mga 9/10/2001 21:33'!
patternColorFor: aColor
	| aForm aLinedDistance|
	aLinedDistance:=3.
	aForm :=Form extent: aLinedDistance at aLinedDistance depth: Display depth.
	aForm fillColor: self emptyColor.
	0 to: (aLinedDistance - 1) do: [:anY | 
		0 to: (aLinedDistance - 1) do: [:anX |
			(((anX + anY) \\ aLinedDistance) = 0) ifTrue: [
				aForm colorAt: (anX at anY) put: aColor]]].
	^InfiniteForm with: aForm
	! !

SymbolitryCard initialize!

!SheetMorph reorganize!
('initialization' initialize initializeCells initializeFor: layoutEqualDistance)
('accessing' addCell: addCells: addColumnLast addMorphsCentered:toCellPositions: atPoint: cellClass cellEntries cells deleteCellEntries sheetExtent)
!



More information about the Squeak-dev mailing list