An implementation of the EightQueensProblem in SmalltalkLanguage
I've gone for maximum Brownie points in that my solution does:
you can see
Quite a lot of the code is to do with only counting solutions that are unique through reflection and rotation. Some of it is a little bit repetitive (see method rotationsAndReflections and its friends), but I can't think of a way of slickening it up.
Also, I wrote the code before the tests thinking that with such a simple problem I didn't need to bother. Then when I started writing the tests I saw how foolish I had been. Perhaps I'll learn one day.
Like the Ruby version, the code also allows the generation of a solution from a partially completed board.
As for performance, I don't make any great claims, but I did manage to count the solutions for the 14*14 board without it taking a ridiculously long time.
Sample output
(1 to: 16) inject: '' into: [ :string :i | string, i printString, ': ', (Board new: i) solutions size printString, '
']
((Board new: 8) solutions asSortedCollection: [ :a :b | a hash <= b hash]) inject: '' into: [ :sum :each | sum, '
', each printString]
The Code
Object subclass: #Board
instanceVariableNames: 'size queenXcoords '
classVariableNames:
poolDictionaries: !
!Board class publicMethods !
new: anInteger
^self new initializeWithSize: anInteger! !
!Board publicMethods !
= aBoard
self class = aBoard class ifFalse: [^false].
^aBoard hasQueenXcoords: queenXcoords!
addAllQueensAt: aCollection
aCollection do: [ :each | self addQueenAt: each]!
addQueenAt: aPoint
queenXcoords at: aPoint y put: aPoint x!
cardinalForm
^(self rotationsAndReflections asSortedCollection: [ :a :b | a hash <= b hash]) first!
copy
^(self class new: size)
queenXcoords: queenXcoords copy!
hash
| result |
result := 0.
queenXcoords do:
[ :y | result := result * size.
y notNil ifTrue: [ result := result + y]].
^result!
hasQueenXcoords: aCollection
^queenXcoords = aCollection!
initializeWithSize: anInteger
size := anInteger.
queenXcoords :=Array new: size.!
nextUnoccupiedRow
queenXcoords doWithIndex: [ :x :y | x isNil ifTrue: [^y]].
^nil!
printCharForPosition: aPoint
^(queenXcoords at: aPoint y) = aPoint x
ifTrue: [ $Q]
ifFalse: [ $_].!
printOn: aStream
[ :y |
aStream nextPutAll: y printString;
nextPutAll: ': |'.
nextPut: $| ].
aStream cr.]!
queenAt: aPoint threatens: bPoint
^(aPoint x = bPoint x)
or: [(aPoint y = bPoint y)
or: [(aPoint x - bPoint x) abs = (aPoint y - bPoint y) abs]]!
queenPositions
| result |
result := OrderedCollection new.
queenXcoords doWithIndex: [ :x :y | x notNil ifTrue: [result add: x@y]].
^result!
queenXcoords: aCollection
queenXcoords := aCollection!
reflectedInHorizontallAxis: aPoint
^aPoint x @ (size + 1 - aPoint y)!
reflectedInNegativeDiagonal: aPoint
^ (size + 1 - aPoint y) @ (size + 1 - aPoint x)!
reflectedInPositiveDiagonal: aPoint
^aPoint y @ aPoint x!
reflectedInVerticalAxis: aPoint
^(size + 1 - aPoint x) @ aPoint y!
rotated180: aPoint
^(size + 1 - aPoint x) @ (size + 1 - aPoint y)!
rotated270: aPoint
^aPoint y @ (size + 1 - aPoint x)!
rotated90: aPoint
^(size + 1 - aPoint y) @ aPoint x!
rotationsAndReflections
^OrderedCollection new
add: self;
add: (self transformedUsingBlock: [ :each |self rotated90: each]);
add: (self transformedUsingBlock: [ :each |self rotated180: each]);
add: (self transformedUsingBlock: [ :each |self rotated270: each]);
add: (self transformedUsingBlock: [ :each |self reflectedInHorizontallAxis: each]);
add: (self transformedUsingBlock: [ :each |self reflectedInVerticalAxis: each]);
add: (self transformedUsingBlock: [ :each |self reflectedInPositiveDiagonal: each]);
add: (self transformedUsingBlock: [ :each |self reflectedInNegativeDiagonal: each]);
yourself!
solutions
self nextUnoccupiedRow isNil ifTrue: [^Set with: self cardinalForm].
^(self unthreatenedSquaresInRow: self nextUnoccupiedRow)
inject: Set new
into: [ :collection :each | collection
addAll: (self copy addQueenAt: each) solutions;
yourself]!
transformedUsingBlock: aBlock
^(self class new: size)
addAllQueensAt: (self queenPositions collect: aBlock)!
unthreatenedSquaresInRow: anInteger
| queenPositions |
queenPositions := self queenPositions.
^((1 to: size) collect: [ :x | x@anInteger])
select: [ :eachSquare | queenPositions
allSatisfy: [ :eachQueen | (self queenAt: eachQueen threatens: eachSquare) not]]! !
Tests
TestCase subclass: #EightTestCase
instanceVariableNames:
classVariableNames:
poolDictionaries: !
!EightTestCase publicMethods !
testAddQueen
| board |
board := Board new: 4.
board addQueenAt: 1@2.
self should: [ board printString = '1: |_|_|_|_|
']!
testBoardDifferent
| board1 board2 |
board1 := Board new: 4.
board1 addQueenAt: 1@2;
addQueenAt: 2@1.
board2 := Board new: 4.
board2 addQueenAt: 1@1;
addQueenAt: 1@2.
self shouldnt: [ board1 = board2]!
testBoardEquals
| board1 board2 |
board1 := Board new: 4.
board1 addQueenAt: 1@2;
addQueenAt: 2@1.
board2 := Board new: 4.
board2 addQueenAt: 2@1;
addQueenAt: 1@2.
self should: [ board1 = board2]!
testNew1
| board |
board := Board new: 1.
self should: [ board printString = '1: |_|
']!
testNew4
| board |
board := Board new: 4.
self should: [ board printString = '1: |_|_|_|_|
']!
testReflectionsAndRotations
| board boardH boardV boardPd boardNd board90 board180 board270 rnr |
board := (Board new: 4) addQueenAt: 1@2.
rnr := board rotationsAndReflections.
boardH := (Board new: 4) addQueenAt: 4@2.
boardV := (Board new: 4) addQueenAt: 1@3.
boardPd := (Board new: 4) addQueenAt: 2@1.
boardNd := (Board new: 4) addQueenAt: 3@4.
board90 := (Board new: 4) addQueenAt: 3@1.
board180 := (Board new: 4) addQueenAt: 4@3.
board270 := (Board new: 4) addQueenAt: 2@4.
self should: [rnr includes: board].
self should: [rnr includes: boardH].
self should: [rnr includes: boardV].
self should: [rnr includes: boardPd].
self should: [rnr includes: boardNd].
self should: [rnr includes: board90].
self should: [rnr includes: board180].
self should: [rnr includes: board270].!
testSolutions1
| board solutions solution1|
board := Board new: 1.
solution1 := Board new: 1.
solution1 addQueenAt: 1@1.
solutions := board solutions.
self should: [solutions size = 1].
self should: [solutions includes: solution1 ].!
testSolutions4
| board solutions solution1|
board := Board new: 4.
solution1 := Board new: 4.
solution1
addQueenAt: 1@3;
addQueenAt: 2@1;
addQueenAt: 3@4;
addQueenAt: 4@2.
solutions := board solutions.
self should: [solutions size = 1].
self should: [solutions includes: solution1 ].!
testSolutions8
| board solutions |
board := Board new: 8.
solutions := board solutions.
self should: [solutions size = 12].! !