[FIX] Re: Full-text search, performance results.

Scott A Crosby crosby at qwes.math.cmu.edu
Wed Jan 23 05:08:15 UTC 2002


On Tue, 22 Jan 2002, Scott A Crosby wrote:

The changeset for StringRefactor requires manual reordering. The initial
version was so old that I had forgotten about that.

This version succesfully files in to a clean 5446 image. (though, all of
this stuff is strictly for pre-alpha testing/demo.)

I've tested it. StringRefactor.5.cs, FullTextSearch.1.cs, and
MiscEnhancements.2.cs, filein'ed to a clean do pass at least the first
test.

Scott
-------------- next part --------------
'From Squeak3.2alpha of 11 October 2001 [latest update: #4646] on 22 January 2002 at 10:05:37 pm'!

!ChessMoveGenerator methodsFor: 'public' stamp: 'sac 1/22/2002 15:32'!
findAllPossibleMovesFor: player
	"Find all possible moves. This method does not check if the move is legal, e.g., if the king of the player is under attack after the move. If the opponent is check mate (e.g., the king could be taken in the next move) the method returns nil. If the game is stale mate (e.g., the receiver has no move left) this method returns an empty array."
	| piece actions square |
	myPlayer _ player.
	myPieces _ player pieces.
	itsPieces _ player opponent pieces.
	castlingStatus _ player castlingStatus.
	enpassantSquare _ player opponent enpassantSquare.
	firstMoveIndex = lastMoveIndex ifFalse:[self error:'I am confused'].
	kingAttack _ nil.
	myPlayer isWhitePlayer ifTrue:[
		actions _ #(	moveWhitePawnAt: moveKnightAt: moveBishopAt:
					moveRookAt: moveQueenAt: moveWhiteKingAt:).
	] ifFalse:[
		actions _ #(	moveBlackPawnAt: moveKnightAt: moveBishopAt:
					moveRookAt: moveQueenAt: moveBlackKingAt:).
	].
	square _ 0.
	[square < 64] whileTrue:[
		"Note: The following is only to skip empty fields efficiently.
		It could well be replaced by going through each field and test it
		for zero but this is *much* faster."
		square _ myPieces indexOfAnyOf: EmptyPieceMap startingAt: square+1.
		"square _ String findFirstInString: myPieces inSet: EmptyPieceMap startingAt: square+1."
		square = 0 ifTrue:[^self moveList].
		piece _ myPieces at: square.
		self perform: (actions at: piece) with: square.
		kingAttack ifNotNil:[^self moveList].
	].
	^self moveList! !


!InterpreterSupportCode class methodsFor: 'source file exporting' stamp: 'sac 1/22/2002 15:15'!
cCodeForMiscPrimitives
	"Return the contents of the miscellaneous primitives file, which is generated via automatic translation to C."

	^ CCodeGenerator new codeStringForPrimitives: #(
		(Bitmap compress:toByteArray:)
		(Bitmap decompress:fromByteArray:at:)
		(Bitmap encodeBytesOf:in:at:)
		(Bitmap encodeInt:in:at:)
		(String compare:with:collated:)
		(String translate:from:to:table:)	
		(String findFirstInString:inSet:startingAt:endingAt:)
		(String indexOfAscii:inString:startingAt:)
		(String findSubstring:in:startingAt:matchTable:)
		(SampledSound convert8bitSignedFrom:to16Bit:))
! !


!MethodFinder methodsFor: 'initialize' stamp: 'sac 1/22/2002 15:16'!
initialize2
	"The methods we are allowed to use.  (MethodFinder new initialize) "

"Set"
	#("in class" sizeFor:
"testing" "adding" "removing" "enumerating"
"private" array findElementOrNil: 
"accessing" someElement) do: [:sel | Approved add: sel].

"Dictionary, IdentityDictionary, IdentitySet"
	#("accessing" associationAt: associationAt:ifAbsent: at:ifPresent: keyAtIdentityValue: keyAtIdentityValue:ifAbsent: keyAtValue: keyAtValue:ifAbsent: keys
"testing" includesKey: ) do: [:sel | Approved add: sel].
	#(removeKey: removeKey:ifAbsent:
) do: [:sel | AddAndRemove add: sel].

"LinkedList, Interval, MappedCollection"
	#("in class"  from:to: from:to:by:
"accessing" contents) do: [:sel | Approved add: sel].
	#(
"adding" addFirst: addLast:) do: [:sel | AddAndRemove add: sel].

"OrderedCollection, SortedCollection"
	#("accessing" after: before:
"copying" copyEmpty
"adding"  growSize
"removing" "enumerating" "private" 
"accessing" sortBlock) do: [:sel | Approved add: sel].
	#("adding" add:after: add:afterIndex: add:before: addAllFirst: addAllLast: addFirst: addLast:
"removing" removeAt: removeFirst removeLast
"accessing" sortBlock:) do: [:sel | AddAndRemove add: sel].

"Character"
	#("in class, instance creation" allCharacters digitValue: new separators
	"accessing untypeable characters" backspace cr enter lf linefeed nbsp newPage space tab
	"constants" alphabet characterTable
"accessing" asciiValue digitValue
"comparing"
"testing" isAlphaNumeric isDigit isLetter isLowercase isSafeForHTTP isSeparator isSpecial isUppercase isVowel tokenish
"copying"
"converting" asIRCLowercase asLowercase asUppercase
	) do: [:sel | Approved add: sel].

"String"
	#("in class, instance creation" crlf fromPacked:
	"primitives" findFirstInString:inSet:startingAt:endingAt: indexOfAscii:inString:startingAt:endingAt:	"internet" valueOfHtmlEntity:
"accessing" byteAt: endsWithDigit findAnySubStr:startingAt: findBetweenSubStrs: findDelimiters:startingAt: findString:startingAt: findString:startingAt:caseSensitive: findTokens: findTokens:includes: findTokens:keep: includesSubString: includesSubstring:caseSensitive: indexOf:startingAt: indexOfAnyOf: indexOfAnyOf:ifAbsent: indexOfAnyOf:startingAt: indexOfAnyOf:startingAt:ifAbsent: lineCorrespondingToIndex: lineCount lineNumber: skipAnySubStr:startingAt: skipDelimiters:startingAt: startsWithDigit
"comparing" alike: beginsWith: caseSensitiveLessOrEqual: charactersExactlyMatching: compare: crc16 endsWith: endsWithAnyOf: sameAs: startingAt:match:startingAt:
"copying" copyReplaceTokens:with: padded:to:with:
"converting" asByteArray asDate asDisplayText asFileName asHtml asLegalSelector asPacked asParagraph asText asTime asUnHtml asUrl asUrlRelativeTo: capitalized compressWithTable: contractTo: correctAgainst: encodeForHTTP initialIntegerOrNil keywords quoted sansPeriodSuffix splitInteger stemAndNumericSuffix substrings surroundedBySingleQuotes truncateWithElipsisTo: withBlanksTrimmed withFirstCharacterDownshifted withNoLineLongerThan: withSeparatorsCompacted withoutLeadingDigits withoutTrailingBlanks
"displaying" "printing"
"system primitives" compare:with:collated: 
"Celeste" withCRs
"internet" decodeMimeHeader decodeQuotedPrintable replaceHtmlCharRefs unescapePercents withInternetLineEndings withSqueakLineEndings withoutQuoting
"testing" isAllSeparators lastSpacePosition
"paragraph support" indentationIfBlank:
"arithmetic" ) do: [:sel | Approved add: sel].
	#(byteAt:put: translateToLowercase match:) do: [:sel | AddAndRemove add: sel].

"Symbol"
	#("in class, private" hasInterned:ifTrue:
	"access" morePossibleSelectorsFor: possibleSelectorsFor: selectorsContaining: thatStarts:skipping:
"accessing" "comparing" "copying" "converting" "printing" 
"testing" isInfix isKeyword isPvtSelector isUnary) do: [:sel | Approved add: sel].

"Array"
	#("comparing" "converting" evalStrings 
"printing" "private" hasLiteralSuchThat:) do: [:sel | Approved add: sel].

"Array2D"
	#("access" at:at: atCol: atCol:put: atRow: extent extent:fromArray: height width width:height:type:) do: [:sel | Approved add: sel].
	#(at:at:add: at:at:put: atRow:put: ) do: [:sel | AddAndRemove add: sel].

"ByteArray"
	#("accessing" doubleWordAt: wordAt: 
"platform independent access" longAt:bigEndian: shortAt:bigEndian: unsignedLongAt:bigEndian: unsignedShortAt:bigEndian: 
"converting") do: [:sel | Approved add: sel].
	#(doubleWordAt:put: wordAt:put: longAt:put:bigEndian: shortAt:put:bigEndian: unsignedLongAt:put:bigEndian: unsignedShortAt:put:bigEndian:
	) do: [:sel | AddAndRemove add: sel].

"FloatArray"		"Dont know what happens when prims not here"
	false ifTrue: [#("accessing" "arithmetic" *= += -= /=
"comparing"
"primitives-plugin" primAddArray: primAddScalar: primDivArray: primDivScalar: primMulArray: primMulScalar: primSubArray: primSubScalar:
"primitives-translated" primAddArray:withArray:from:to: primMulArray:withArray:from:to: primSubArray:withArray:from:to:
"converting" "private" "user interface") do: [:sel | Approved add: sel].
	].

"IntegerArray, WordArray"
"RunArray"
	#("in class, instance creation" runs:values: scanFrom:
"accessing" runLengthAt: 
"adding" "copying"
"private" runs values) do: [:sel | Approved add: sel].
	#(coalesce addLast:times: repeatLast:ifEmpty: repeatLastIfEmpty:
		) do: [:sel | AddAndRemove add: sel].

"Stream  -- many operations change its state"
	#("testing" atEnd) do: [:sel | Approved add: sel].
	#("accessing" next: nextMatchAll: nextMatchFor: upToEnd
next:put: nextPut: nextPutAll: "printing" print: printHtml:
	) do: [:sel | AddAndRemove add: sel].

"PositionableStream"
	#("accessing" contentsOfEntireFile originalContents peek peekFor: "testing"
"positioning" position ) do: [:sel | Approved add: sel].
	#(nextDelimited: nextLine upTo: position: reset resetContents setToEnd skip: skipTo: upToAll: ) do: [:sel | AddAndRemove add: sel].
	"Because it is so difficult to test the result of an operation on a Stream (you have to supply another Stream in the same state), we don't support Streams beyond the basics.  We want to find the messages that convert Streams to other things."

"ReadWriteStream"
	#("file status" closed) do: [:sel | Approved add: sel].
	#("accessing" next: on: ) do: [:sel | AddAndRemove add: sel].

"WriteStream"
	#("in class, instance creation" on:from:to: with: with:from:to:
		) do: [:sel | Approved add: sel].
	#("positioning" resetToStart
"character writing" crtab crtab:) do: [:sel | AddAndRemove add: sel].

"LookupKey, Association, Link"
	#("accessing" key nextLink) do: [:sel | Approved add: sel].
	#(key: key:value: nextLink:) do: [:sel | AddAndRemove add: sel].

"Point"
	#("in class, instance creation" r:degrees: x:y:
"accessing" x y "comparing" "arithmetic" "truncation and round off"
"polar coordinates" degrees r theta
"point functions" bearingToPoint: crossProduct: dist: dotProduct: eightNeighbors flipBy:centerAt: fourNeighbors grid: nearestPointAlongLineFrom:to: nearestPointOnLineFrom:to: normal normalized octantOf: onLineFrom:to: onLineFrom:to:within: quadrantOf: rotateBy:centerAt: transposed unitVector
"converting" asFloatPoint asIntegerPoint corner: extent: rect:
"transforming" adhereTo: rotateBy:about: scaleBy: scaleFrom:to: translateBy: "copying"
"interpolating" interpolateTo:at:) do: [:sel | Approved add: sel].

"Rectangle"
	#("in class, instance creation" center:extent: encompassing: left:right:top:bottom: 
	merging: origin:corner: origin:extent: 
"accessing" area bottom bottomCenter bottomLeft bottomRight boundingBox center corner corners innerCorners left leftCenter origin right rightCenter top topCenter topLeft topRight
"comparing"
"rectangle functions" adjustTo:along: amountToTranslateWithin: areasOutside: bordersOn:along: encompass: expandBy: extendBy: forPoint:closestSideDistLen: insetBy: insetOriginBy:cornerBy: intersect: merge: pointNearestTo: quickMerge: rectanglesAt:height: sideNearestTo: translatedToBeWithin: withBottom: withHeight: withLeft: withRight: withSide:setTo: withTop: withWidth:
"testing" containsPoint: containsRect: hasPositiveExtent intersects: isTall isWide
"truncation and round off"
"transforming" align:with: centeredBeneath: newRectFrom: squishedWithin: "copying"
	) do: [:sel | Approved add: sel].

"Color"
	#("in class, instance creation" colorFrom: colorFromPixelValue:depth: fromRgbTriplet: gray: h:s:v: r:g:b: r:g:b:alpha: r:g:b:range:
	"named colors" black blue brown cyan darkGray gray green lightBlue lightBrown lightCyan lightGray lightGreen lightMagenta lightOrange lightRed lightYellow magenta orange red transparent veryDarkGray veryLightGray veryVeryDarkGray veryVeryLightGray white yellow
	"other" colorNames indexedColors pixelScreenForDepth: quickHighLight:
"access" alpha blue brightness green hue luminance red saturation
"equality"
"queries" isBitmapFill isBlack isGray isSolidFill isTranslucent isTranslucentColor
"transformations" alpha: dansDarker darker lighter mixed:with: muchLighter slightlyDarker slightlyLighter veryMuchLighter alphaMixed:with:
"groups of shades" darkShades: lightShades: mix:shades: wheel:
"printing" shortPrintString
"other" colorForInsets rgbTriplet
"conversions" asB3DColor asColor balancedPatternForDepth: bitPatternForDepth: closestPixelValue1 closestPixelValue2 closestPixelValue4 closestPixelValue8 dominantColor halfTonePattern1 halfTonePattern2 indexInMap: pixelValueForDepth: pixelWordFor:filledWith: pixelWordForDepth: scaledPixelValue32
"private" privateAlpha privateBlue privateGreen privateRGB privateRed "copying"
	) do: [:sel | Approved add: sel].

"	For each selector that requires a block argument, add (selector argNum) 
		to the set Blocks."
"ourClasses _ #(Object Boolean True False UndefinedObject Behavior ClassDescription Class Metaclass MethodContext BlockContext Message Magnitude Date Time Number Integer SmallInteger LargeNegativeInteger LargePositiveInteger Float Fraction Random Collection SequenceableCollection ArrayedCollection Bag Set Dictionary IdentityDictionary IdentitySet LinkedList Interval MappedCollection OrderedCollection SortedCollection Character String Symbol Array Array2D ByteArray FloatArray IntegerArray WordArray RunArray Stream PositionableStream ReadWriteStream WriteStream LookupKey Association Link Point Rectangle Color).
ourClasses do: [:clsName | cls _ Smalltalk at: clsName.
	(cls selectors) do: [:aSel |
		((Approved includes: aSel) or: [AddAndRemove includes: aSel]) ifTrue: [
			(cls formalParametersAt: aSel) withIndexDo: [:tName :ind |
				(tName endsWith: 'Block') ifTrue: [
					Blocks add: (Array with: aSel with: ind)]]]]].
"
#((timesRepeat: 1 ) (indexOf:ifAbsent: 2 ) (pairsCollect: 1 ) (mergeSortFrom:to:by: 3 ) (ifNotNil:ifNil: 1 ) (ifNotNil:ifNil: 2 ) (ifNil: 1 ) (at:ifAbsent: 2 ) (ifNil:ifNotNil: 1 ) (ifNil:ifNotNil: 2 ) (ifNotNil: 1 ) (at:modify: 2 ) (identityIndexOf:ifAbsent: 2 ) (sort: 1 ) (sortBlock: 1 ) (detectMax: 1 ) (repeatLastIfEmpty: 1 ) (allSubclassesWithLevelDo:startingLevel: 1 ) (keyAtValue:ifAbsent: 2 ) (in: 1 ) (ifTrue: 1 ) (or: 1 ) (select: 1 ) (inject:into: 2 ) (ifKindOf:thenDo: 2 ) (forPoint:closestSideDistLen: 2 ) (value:ifError: 2 ) (selectorsDo: 1 ) (removeAllSuchThat: 1 ) (keyAtIdentityValue:ifAbsent: 2 ) (detectMin: 1 ) (detect:ifNone: 1 ) (ifTrue:ifFalse: 1 ) (ifTrue:ifFalse: 2 ) (detect:ifNone: 2 ) (hasLiteralSuchThat: 1 ) (indexOfAnyOf:ifAbsent: 2 ) (reject: 1 ) (newRectFrom: 1 ) (removeKey:ifAbsent: 2 ) (at:ifPresent: 2 ) (associationAt:ifAbsent: 2 ) (withIndexCollect: 1 ) (repeatLast:ifEmpty: 2 ) (findLast: 1 ) (indexOf:startingAt:ifAbsent: 3 ) (remove:ifAbsent: 2 ) (ifFalse:ifTrue: 1 ) (ifFalse:ifTrue: 2 ) (caseOf:otherwise: 2 ) (count: 1 ) (collect: 1 ) (sortBy: 1 ) (and: 1 ) (asSortedCollection: 1 ) (with:collect: 2 ) (sourceCodeAt:ifAbsent: 2 ) (detect: 1 ) (scopeHas:ifTrue: 2 ) (collectWithIndex: 1 ) (compiledMethodAt:ifAbsent: 2 ) (bindWithTemp: 1 ) (detectSum: 1 ) (indexOfSubCollection:startingAt:ifAbsent: 3 ) (findFirst: 1 ) (sourceMethodAt:ifAbsent: 2 ) (collect:thenSelect: 1 ) (collect:thenSelect: 2 ) (select:thenCollect: 1 ) (select:thenCollect: 2 ) (ifFalse: 1 ) (indexOfAnyOf:startingAt:ifAbsent: 3 ) (indentationIfBlank: 1 ) ) do: [:anArray |
	Blocks add: anArray].

self initialize3.

"
MethodFinder new initialize.
MethodFinder new organizationFiltered: TranslucentColor class 
"
"Do not forget class messages for each of these classes"
! !


!MiscPrimitivePlugin class methodsFor: 'translation' stamp: 'sac 1/22/2002 15:16'!
translatedPrimitives
	"an assorted list of various primitives"
	^#(
		(Bitmap compress:toByteArray:)
		(Bitmap decompress:fromByteArray:at:)
		(Bitmap encodeBytesOf:in:at:)
		(Bitmap encodeInt:in:at:)
		(String compare:with:collated:)
		(String translate:from:to:table:)	
		(String findFirstInString:inSet:startingAt:endingAt:)
		(String indexOfAscii:inString:startingAt:endingAt:)
		(String findSubstring:in:startingAt:matchTable:)
		(String stringHash:initialHash:)
		(SampledSound convert8bitSignedFrom:to16Bit:)
	)
! !


!String class methodsFor: 'primitives' stamp: 'sac 1/22/2002 15:14'!
findFirstInString: aString  inSet: inclusionMap  startingAt: start endingAt: end

	"Scan a string for from the start to the end as long as the characters  
	are in the first character set. Return the index of the last character  
	that is also in the second character set.  
	 
	For example, if you want ot identify the end of a whitespace  
	deliminated alpha string, make the first set alphabetic+whitespace, and  
	the second set be alphabetic."
	| |
	<primitive: 'primitiveMatchInSubString' module:'MiscPrimitivePlugin'> "primitiveExternalCall" 
	self var: #aString declareC: 'unsigned char *aString'.
	self var: #inclusionMap declareC: 'char *inclusionMap'.

	start
		to: end
		do: [:pos | (inclusionMap at: (aString at: pos) asciiValue + 1)
					= 1
				ifTrue: [^ pos]].
	^ 0! !

!String class methodsFor: 'primitives' stamp: 'sac 10/1/2001 17:05'!
indexOfAscii: anInteger inString: aString startingAt: start endingAt: end 
	| |
	self var: #aCharacter declareC: 'int anInteger'.
	self var: #aString declareC: 'unsigned char *aString'.
	
	start
		to: end
		do: [:pos | (aString at: pos) asciiValue = anInteger
				ifTrue: [^ pos]].
	^ 0! !

!String methodsFor: 'accessing' stamp: 'sac 9/24/2001 05:31'!
indexOf: aCharacter startingAt: start endingAt: end
	aCharacter class == Character
		ifFalse: [^ 0].
	^ String
		indexOfAscii: aCharacter asciiValue
		inString: self
		startingAt: start
		endingAt: (end min: self size)! !

!String methodsFor: 'accessing' stamp: 'sac 10/1/2001 17:03'!
indexOf: aCharacter 
	aCharacter class == Character
		ifFalse: [^ 0].
	^ String
		indexOfAscii: aCharacter asciiValue
		inString: self
		startingAt: 1
		endingAt: self size.! !

!String methodsFor: 'accessing' stamp: 'sac 10/3/2001 11:52'!
indexOf: aCharacter startingAt: start 
	^self
		indexOf: aCharacter
		startingAt: start
		endingAt: self size! !

!String methodsFor: 'accessing' stamp: 'sac 10/1/2001 17:04'!
indexOf: aCharacter startingAt: start ifAbsent: aBlock 
	| ans |
	aCharacter class == Character
		ifFalse: [^ aBlock value].
	ans _ String
				indexOfAscii: aCharacter asciiValue
				inString: self
				startingAt: start
				endingAt: self size.
	ans = 0
		ifTrue: [^ aBlock value]
		ifFalse: [^ ans]! !

!String methodsFor: 'accessing' stamp: 'sac 1/22/2002 15:32'!
indexOfAnyOf: aCharacterSet  startingAt: start endingAt: end
	"returns the index of the first character in the given set, starting from start.  Returns 0 if none are found"
	end > self size ifTrue: [self error: 'Access beyond the bounds'].
	^String findFirstInString: self  inSet: aCharacterSet byteArrayMap startingAt: start endingAt: end.
! !

!String methodsFor: 'accessing' stamp: 'sac 1/22/2002 15:26'!
indexOfAnyOf: aCharacterSet  startingAt: start
	"returns the index of the first character in the given set, starting from start.  Returns 0 if none are found"
	^String findFirstInString: self  inSet: aCharacterSet byteArrayMap startingAt: start endingAt: self size.
! !

!String methodsFor: 'accessing' stamp: 'sac 1/22/2002 15:26'!
indexOfAnyOf: aCharacterSet  startingAt: start ifAbsent: aBlock
	"returns the index of the first character in the given set, starting from start"

	| ans |
	ans _ self indexOfAnyOf: aCharacterSet startingAt: start.
	ans = 0 
		ifTrue: [ ^aBlock value ]
		ifFalse: [ ^ans ]! !

!String methodsFor: 'converting' stamp: 'sac 1/22/2002 16:03'!
substrings
	"Answer an array of the substrings that compose the receiver."
	self substrings: CSNonSeparators.! !

!String methodsFor: 'converting' stamp: 'sac 1/22/2002 15:29'!
substrings: aCharacterSet
	"Answer an array of the substrings containing only charactes in aCharacterSet that compose the receiver."
	| result end beginning seperators |

	result _ WriteStream on: (Array new: 10).
	seperators _ aCharacterSet complement.


	end _ 0.
	"find one substring each time through this loop"
	[ 
		"find the beginning of the next substring"
		beginning _ self indexOfAnyOf: aCharacterSet startingAt: end+1 ifAbsent: [ nil ].
		beginning ~~ nil ] 
	whileTrue: [
		"find the end"
		end _ self indexOfAnyOf: seperators startingAt: beginning ifAbsent: [ self size + 1 ].
		end _ end - 1.

		result nextPut: (self copyFrom: beginning to: end).

	].


	^result contents! !


String class removeSelector: #findFirstInString:inSet:startingAt:!
String class removeSelector: #indexOfAscii:inString:startingAt:!


More information about the Squeak-dev mailing list