Not a member of Pastebin yet?
Sign Up,
it unlocks many cool features!
- Object subclass: #Insertion
- instanceVariableNames: 'point isHorizontal numberOfOverlaps accidentalPrimes'
- classVariableNames: ''
- poolDictionaries: ''
- category: 'Amos'!
- !Insertion methodsFor: 'initialization' stamp: 'AMC 3/24/2016 15:29'!
- initialize
- super initialize.
- numberOfOverlaps := 0.
- accidentalPrimes := OrderedCollection new! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:55'!
- point: aPoint
- point := aPoint! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:56'!
- numberOfOverlaps: anInteger
- numberOfOverlaps := anInteger! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:29'!
- addAccidentalPrime: aPrime
- accidentalPrimes add: aPrime! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:29'!
- accidentalPrimes
- ^accidentalPrimes! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:56'!
- numberOfOverlaps
- ^numberOfOverlaps! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:55'!
- point
- ^point! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:59'!
- increaseOverlaps
- numberOfOverlaps := numberOfOverlaps + 1! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:55'!
- isHorizontal
- ^isHorizontal! !
- !Insertion methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:55'!
- isHorizontal: aBoolean
- isHorizontal := aBoolean! !
- !Insertion methodsFor: 'printing' stamp: 'AMC 3/24/2016 16:19'!
- printOn: aStream
- aStream
- nextPutAll: 'Insertion at: ';
- nextPutAll: point printString;
- nextPut: Character space;
- nextPut: (isHorizontal ifTrue: [$>] ifFalse: [$v]);
- nextPutAll: ' {';
- nextPutAll: (', ' join: accidentalPrimes);
- nextPut: $}! !
- "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
- Insertion class
- instanceVariableNames: ''!
- !Insertion class methodsFor: 'instance creation' stamp: 'AMC 3/24/2016 15:58'!
- at: aPoint isHorizontal: aBoolean
- ^self new
- point: aPoint;
- isHorizontal: aBoolean;
- yourself! !
- Object subclass: #Stuffer
- instanceVariableNames: 'box width height'
- classVariableNames: 'primeLoadDictionary primes'
- poolDictionaries: ''
- category: 'Amos'!
- !Stuffer methodsFor: 'initialization' stamp: 'AMC 3/24/2016 15:48'!
- initializeBox
- box := Box width: (width min: 5) height: (height min: 5)! !
- !Stuffer methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:49'!
- height: anInteger
- height := anInteger! !
- !Stuffer methodsFor: 'accessing' stamp: 'AMC 3/24/2016 16:07'!
- box
- ^box! !
- !Stuffer methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:49'!
- width: anInteger
- width := anInteger! !
- !Stuffer methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:48'!
- width
- ^width! !
- !Stuffer methodsFor: 'accessing' stamp: 'AMC 3/24/2016 16:07'!
- box: aBox
- box := aBox! !
- !Stuffer methodsFor: 'accessing' stamp: 'AMC 3/24/2016 14:49'!
- height
- ^height! !
- !Stuffer methodsFor: 'testing' stamp: 'AMC 3/24/2016 14:50'!
- canGrow
- ^width > box width or: [height > box height]! !
- !Stuffer methodsFor: 'stuffing' stamp: 'AMC 3/24/2016 13:23'!
- insert: aString at: aPoint horizontalIf: isHorizontal
- | point offset |
- point := aPoint.
- offset := isHorizontal ifTrue: [box rightOffset] ifFalse: [box downOffset].
- Transcript crShow: 'Inserting ', aString, ' at ', point printString.
- aString do: [:eachChar |
- box at: point x at: point y put: eachChar.
- point := point + offset
- ].
- Transcript crShow: box! !
- !Stuffer methodsFor: 'stuffing' stamp: 'AMC 3/24/2016 13:46'!
- stuffBox
- self stuffCurrentBox.
- [self canGrow] whileTrue: [
- box growMatrixByOneUpTo: width @ height.
- self stuffCurrentBox
- ]! !
- !Stuffer methodsFor: 'stuffing' stamp: 'AMC 3/24/2016 13:47'!
- stuffCurrentBox
- self class primes reverseDo: [:eachPrime |
- | string insertion |
- (box primesUsed includes: eachPrime) ifFalse: [
- string := eachPrime asString.
- (insertion := box bestInsertionFor: string)
- ifNotNil: [
- Transcript crShow: insertion printString, ' of ', string.
- box doInsertion: insertion of: eachPrime.
- Transcript crShow: box
- ]
- ]
- ].
- box updatePrimesUsed.! !
- "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
- Stuffer class
- instanceVariableNames: ''!
- !Stuffer class methodsFor: 'primes' stamp: 'AMC 3/24/2016 16:32'!
- primeMaxLength
- "self primeMaxLength"
- ^self primes last asString size! !
- !Stuffer class methodsFor: 'primes' stamp: 'AMC 3/25/2016 18:11'!
- primeLoadDictionary
- "self primeLoadDictionary"
- primeLoadDictionary ifNil: [
- | sum |
- primeLoadDictionary := IdentityDictionary new.
- sum := 0.
- self primes do: [:eachPrime |
- sum := sum + eachPrime asString size.
- primeLoadDictionary at: sum put: eachPrime
- ]
- ].
- ^primeLoadDictionary! !
- !Stuffer class methodsFor: 'primes' stamp: 'AMC 3/25/2016 18:05'!
- maxPrime
- ^20000! !
- !Stuffer class methodsFor: 'primes' stamp: 'AMC 3/24/2016 14:46'!
- resetPrimes
- "self resetPrimes"
- primes := nil.
- primeLoadDictionary := nil! !
- !Stuffer class methodsFor: 'primes' stamp: 'AMC 3/24/2016 14:54'!
- primes
- "self primes"
- primes isNil ifTrue: [
- primes := (Integer primesUpTo: self maxPrime) asOrderedCollection.
- primes removeAll: #(2 3 5 7)
- ].
- ^primes! !
- !Stuffer class methodsFor: 'instance creation' stamp: 'AMC 3/24/2016 13:09'!
- forBox: aBox
- ^self new
- box: aBox;
- yourself! !
- !Stuffer class methodsFor: 'instance creation' stamp: 'AMC 3/24/2016 13:54'!
- forDimensions: aPoint
- ^self new
- width: aPoint x;
- height: aPoint y;
- initializeBox;
- yourself! !
- Object subclass: #Box
- instanceVariableNames: 'matrix primesUsed'
- classVariableNames: ''
- poolDictionaries: ''
- category: 'Amos'!
- !Box methodsFor: 'convenience' stamp: 'AMC 3/24/2016 14:32'!
- rightOffset
- ^1@0! !
- !Box methodsFor: 'convenience' stamp: 'AMC 3/24/2016 14:18'!
- width
- ^matrix numberOfColumns! !
- !Box methodsFor: 'convenience' stamp: 'AMC 3/24/2016 14:20'!
- pointsDo: aBlock
- 1 to: self height do: [:eachY |
- 1 to: self width do: [:eachX |
- aBlock value: eachX @ eachY
- ]
- ]! !
- !Box methodsFor: 'convenience' stamp: 'AMC 3/24/2016 14:02'!
- offset: isHorizontal
- ^isHorizontal
- ifTrue: [self rightOffset]
- ifFalse: [self downOffset]! !
- !Box methodsFor: 'convenience' stamp: 'AMC 3/24/2016 13:32'!
- downOffset
- ^0@1! !
- !Box methodsFor: 'convenience' stamp: 'AMC 3/24/2016 13:17'!
- height
- ^matrix numberOfRows! !
- !Box methodsFor: 'initialization' stamp: 'AMC 3/24/2016 14:33'!
- initialize
- super initialize.
- primesUsed := OrderedCollection new! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:47'!
- matrix
- ^matrix! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 16:24'!
- primesUsed
- ^primesUsed! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 13:54'!
- from: aPoint rightBy: aNumber
- ^(matrix atRow: aPoint y)
- copyFrom: aPoint x to: (aPoint x + aNumber min: self width)! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 16:25'!
- primesUsed: somePrimes
- primesUsed := somePrimes! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 13:30'!
- at: aRowIndex at: aColumnIndex
- ^self at: aColumnIndex @ aRowIndex! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 13:09'!
- primesInColumn: aColumnIndex
- ^self class primesIn: (matrix atColumn: aColumnIndex)! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 13:07'!
- primesInRow: aRowIndex
- ^self class primesIn: (matrix atRow: aRowIndex)! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 16:02'!
- at: aRowIndex at: aColumnIndex put: aCharacter
- ^matrix at: aRowIndex at: aColumnIndex put: aCharacter! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 15:47'!
- matrix: aMatrix
- matrix := aMatrix! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 13:42'!
- at: aPoint
- ^matrix at: aPoint y at: aPoint x ifInvalid: nil! !
- !Box methodsFor: 'accessing' stamp: 'AMC 3/24/2016 13:53'!
- from: aPoint downBy: aNumber
- ^(matrix atColumn: aPoint x)
- copyFrom: aPoint y to: (aPoint y + aNumber min: self height)! !
- !Box methodsFor: 'evaluating' stamp: 'AMC 3/24/2016 17:16'!
- updatePrimesUsed
- Transcript crShow: primesUsed size printString, ' old primes: ', (', ' join: primesUsed).
- primesUsed := OrderedCollection new.
- 1 to: self height do: [:each |
- primesUsed addAll: (self primesInRow: each)
- ].
- 1 to: self width do: [:each |
- primesUsed addAll: (self primesInColumn: each)
- ].
- primesUsed asBag sortedCounts first key > 1
- ifTrue: [self error: 'Damn dirty duplicates!!'].
- Transcript crShow: primesUsed size printString, ' new primes: ', (', ' join: primesUsed)! !
- !Box methodsFor: 'evaluating' stamp: 'AMC 3/24/2016 15:05'!
- load
- ^((matrix size - (matrix occurrencesOf: Character space)) / matrix size) * 100! !
- !Box methodsFor: 'inserting' stamp: 'AMC 3/24/2016 12:59'!
- doInsertion: anInsertion of: aPrime
- self
- insert: aPrime printString
- at: anInsertion point
- horizontalIf: anInsertion isHorizontal.
- primesUsed
- add: aPrime;
- addAll: anInsertion accidentalPrimes! !
- !Box methodsFor: 'inserting' stamp: 'AMC 3/24/2016 11:21'!
- growMatrixByOneUpTo: aDimension
- | smallMatrix rowOffset columnOffset |
- smallMatrix := matrix copy.
- matrix := Matrix
- rows: (self height + 2 min: aDimension y)
- columns: (self width + 2 min: aDimension x)
- element: Character space.
- rowOffset := (self height - smallMatrix numberOfRows) min: 1.
- columnOffset := (self width - smallMatrix numberOfColumns) min: 1.
- self copy: smallMatrix to: (1 + columnOffset) @ (1 + rowOffset)! !
- !Box methodsFor: 'inserting' stamp: 'AMC 3/25/2016 17:46'!
- bestInsertionFor: aString
- | insertions |
- insertions := OrderedCollection new.
- self pointsDo: [:eachPoint |
- insertions
- addIfNotNil: (self insertionOf: aString at: eachPoint isHorizontal: true);
- addIfNotNil: (self insertionOf: aString at: eachPoint isHorizontal: false)
- ].
- insertions removeAllSuchThat: [:each |
- self isInsertion: each invalidWith: aString asInteger
- ].
- ^insertions detectMax: [:each |
- (each accidentalPrimes size * 1) + (each numberOfOverlaps * 2)
- ]! !
- !Box methodsFor: 'inserting' stamp: 'AMC 3/24/2016 11:08'!
- copy: aMatrix to: aPoint
- matrix
- atRows: aPoint y
- to: aPoint y + aMatrix numberOfRows - 1
- columns: aPoint x
- to: aPoint x + aMatrix numberOfColumns - 1
- put: aMatrix! !
- !Box methodsFor: 'inserting' stamp: 'AMC 3/24/2016 12:51'!
- insertionOf: aString at: aPoint isHorizontal: isHorizontal
- | point insertion |
- point := aPoint.
- (self canFitEndsAt: point length: aString size isHorizontal: isHorizontal)
- ifFalse: [^nil].
- (self isAlreadyThere: aString at: aPoint isHorizontal: isHorizontal)
- ifTrue: [^nil].
- insertion := Insertion at: point isHorizontal: isHorizontal.
- 1 to: aString size do: [:eachIndex |
- | eachCharacter |
- eachCharacter := aString at: eachIndex.
- (self canDoInsertion: insertion of: eachCharacter at: point)
- ifTrue: [
- (self at: point) == eachCharacter
- ifTrue: [insertion increaseOverlaps].
- point := point + (self offset: isHorizontal)
- ]
- ifFalse: [^nil]
- ].
- ^insertion! !
- !Box methodsFor: 'inserting' stamp: 'AMC 3/24/2016 14:19'!
- insert: aString at: aPoint horizontalIf: isHorizontal
- | point offset |
- point := aPoint.
- offset := isHorizontal ifTrue: [self rightOffset] ifFalse: [self downOffset].
- aString do: [:eachChar |
- self at: point y at: point x put: eachChar.
- point := point + offset
- ]! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/25/2016 16:11'!
- isInsertion: anInsertion invalidWith: aPrime
- | otherPrimes |
- otherPrimes := anInsertion accidentalPrimes.
- ^(primesUsed includesAny: otherPrimes)
- or: [(otherPrimes includes: aPrime)
- or: [otherPrimes copy removeDuplicates size < otherPrimes size]]! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/24/2016 15:39'!
- canFitEndsAt: aPoint length: aLength isHorizontal: isHorizontal
- | before after |
- before := isHorizontal
- ifTrue: [aPoint - self rightOffset]
- ifFalse: [aPoint - self downOffset].
- after := isHorizontal
- ifTrue: [(aPoint x + aLength) @ aPoint y]
- ifFalse: [aPoint x @ (aPoint y + aLength)].
- ^(self isFreeOrBorder: before) and: [self isFreeOrBorder: after]! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/24/2016 14:49'!
- isFreeOrBorder: aPoint
- ^(self isBorder: aPoint)
- or: [self isFreeAt: aPoint]! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/24/2016 16:24'!
- canDoInsertion: anInsertion of: aCharacter at: aPoint
- "Answer whether anInsertion of aCharacter is valid at aPoint. If so,
- also update anInsertion with any accidental insertions."
- | perpendicularSequence offset front back |
- (self at: aPoint) == aCharacter
- ifTrue: [^true].
- (self isFreeAt: aPoint)
- ifFalse: [^false].
- perpendicularSequence := OrderedCollection with: aCharacter.
- offset := self offset: anInsertion isHorizontal not.
- front := aPoint - offset.
- back := aPoint + offset.
- [self isFreeOrBorder: front] whileFalse: [
- perpendicularSequence addFirst: (self at: front).
- front := front - offset
- ].
- [self isFreeOrBorder: back] whileFalse: [
- perpendicularSequence addLast: (self at: back).
- back := back + offset
- ].
- ^perpendicularSequence size == 1
- or: [
- | string number |
- string := String withAll: perpendicularSequence.
- number := string asInteger.
- (string first ~~ $0 and: [number isPrime])
- ifTrue: [anInsertion addAccidentalPrime: number. true]
- ifFalse: [false]
- ]! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/24/2016 14:50'!
- isBorder: aPoint
- ^(aPoint x == 0)
- or: [aPoint x == (self width + 1)
- or: [aPoint y == 0
- or: [aPoint y == (self height + 1)]]]! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/25/2016 16:46'!
- isFreeAt: aPoint
- ^(self at: aPoint) == Character space! !
- !Box methodsFor: 'testing' stamp: 'AMC 3/24/2016 16:08'!
- isAlreadyThere: aString at: aPoint isHorizontal: isHorizontal
- | currentString |
- currentString := isHorizontal
- ifTrue: [self from: aPoint rightBy: aString size]
- ifFalse: [self from: aPoint downBy: aString size].
- ^aString = currentString! !
- !Box methodsFor: 'printing' stamp: 'AMC 3/24/2016 14:46'!
- primesUsedPrintString
- ^primesUsed size printString, (' prime' asPluralBasedOn: primesUsed)! !
- !Box methodsFor: 'printing' stamp: 'AMC 3/24/2016 14:45'!
- loadPrintString
- ^'load: ', self load asInteger printString, '%'! !
- !Box methodsFor: 'printing' stamp: 'AMC 3/24/2016 14:44'!
- sizePrintString
- ^self height printString, 'x', self width printString! !
- !Box methodsFor: 'printing' stamp: 'AMC 3/25/2016 17:18'!
- printOn: aStream
- aStream
- nextPutAll: 'Box ';
- nextPutAll: self sizePrintString;
- nextPutAll: ' (';
- nextPutAll: self primesUsedPrintString;
- nextPutAll: ', ';
- nextPutAll: self loadPrintString;
- nextPutAll: '):';
- nextPut: Character cr.
- 1 to: self height do: [ :eachY |
- aStream nextPut: $|.
- 1 to: self width do: [ :eachX |
- aStream nextPut: (self at: eachX @ eachY)
- ].
- aStream nextPut: $|.
- aStream nextPut: Character cr
- ]
- ! !
- "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
- Box class
- instanceVariableNames: ''!
- !Box class methodsFor: 'instance creation' stamp: 'AMC 3/24/2016 15:48'!
- width: aWidth height: aHeight
- | matrix |
- matrix := Matrix rows: aHeight columns: aWidth element: Character space.
- ^self newWith: matrix! !
- !Box class methodsFor: 'instance creation' stamp: 'AMC 3/24/2016 15:47'!
- newWith: aMatrix
- ^self new
- matrix: aMatrix;
- yourself! !
- !Box class methodsFor: 'primes' stamp: 'AMC 3/24/2016 14:33'!
- primesIn: aString
- ^((aString splitOn: Character space)
- collect: [:each | (String withAll: each) asInteger])
- select: [:each |
- each notNil and: [
- (each > 9 and: [each isPrime not])
- ifTrue: [self error: 'Caught unexpected non-prime: ', each printString].
- each > 9
- ]
- ]! !
- 'From Pharo4.0 of 18 March 2013 [Latest update: #40626] on 25 March 2016 at 10:19:38.616703 pm'!
- !Collection methodsFor: '*Amos' stamp: 'AMC 3/24/2016 14:52'!
- addIfNotNil: anElement
- anElement ifNotNil: [self add: anElement]! !
Add Comment
Please, Sign In to add comment