[BUG] [ENH] [FIX] Misc small features and bugfixes (repost) (fwd)

Scott A Crosby crosby at qwes.math.cmu.edu
Sun Dec 9 13:40:43 UTC 2001


Also, apparently lost in the mail.

Some of my code for helping out searching/scanning strings for substrings
or characters. Plus, a few other small changes.

Scott


---------- Forwarded message ----------
Date: Wed, 3 Oct 2001 16:29:33 -0400 (EDT)
From: Scott A Crosby <crosby at qwes.math.cmu.edu>
Reply-To: squeak-dev at lists.squeakfoundation.org
To: Squeak List <squeak-dev at lists.squeakfoundation.org>
Subject: [BUG] [ENH] [FIX] #2 Misc small features and bugfixes


I've refactored these changes. This is my first VM plugin hacking, so I
can't promose that that part is 'quite right', but eh.

Ok, the files are:

StringRefactor.3.cs:
   Minor refactor of the string character searching routines. This
changeset has been reordered manually.

StringNew.2:
   My attempt to alter the misc plugin for my new primitive, (and also to
try to get it to build a second primitive correctly) It seems to want to
work.

MiscEnhancements.1.cs:
   The misc features below:

>   - Small documentation fixes,
>   - Fixing a buglet in creating ReadWriteStreams with on:.
>   - Giving Writestream an understanding of lf/crlf messages.
>   - Giving Socket a lowlevel try-to-send-data function
>   - Giving SharedQueue the ability to safetly check its size with critical
> sections.
>   - More flexible CharacterSet generation, and more predefined
> charactersets.


-------------- next part --------------
'From Squeak3.2alpha of 3 October 2001 [latest update: #4411] on 3 October 2001 at 12:38:22 pm'!

!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 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 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: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 class removeSelector: #indexOfAscii:inString:startingAt:!
-------------- next part --------------
'From Squeak3.2alpha of 3 October 2001 [latest update: #4411] on 3 October 2001 at 4:09:10 pm'!

!FilePlugin methodsFor: 'file primitives' stamp: 'sac 10/3/2001 14:58'!
primitiveFileTruncate
	| truncatePosition file |
	self var: 'file' declareC: 'SQFile *file'.
	self export: true.
	truncatePosition _ interpreterProxy
				positive32BitValueOf: (interpreterProxy stackValue: 0).
	file _ self
				fileValueOf: (interpreterProxy stackValue: 1).
	interpreterProxy failed
		ifFalse: ["For some reason, this is failing to compile:
			'self sqFile: file Truncate: truncatePosition'"
			truncatePosition.
			file].
	interpreterProxy failed
		ifFalse: [interpreterProxy pop: 2
			"pop position, file; leave rcvr on stack"]! !


!MethodFinder methodsFor: 'initialize' stamp: 'sac 10/3/2001 12:30'!
initialize2
	"The methods we are allowed to use. (MethodFinder new initialize)"
	"Set"
	"in class"
	"testing"
	"adding"
	"removing"
	"enumerating"
	"private"
	"accessing"
	#(#sizeFor: #array #findElementOrNil: #someElement )
		do: [:sel | Approved add: sel].
	"Dictionary, IdentityDictionary, IdentitySet"
	"accessing"
	"testing"
	#(#associationAt: #associationAt:ifAbsent: #at:ifPresent: #keyAtIdentityValue: #keyAtIdentityValue:ifAbsent: #keyAtValue: #keyAtValue:ifAbsent: #keys #includesKey: )
		do: [:sel | Approved add: sel].
	#(#removeKey: #removeKey:ifAbsent: )
		do: [:sel | AddAndRemove add: sel].
	"LinkedList, Interval, MappedCollection"
	"in class"
	"accessing"
	#(#from:to: #from:to:by: #contents )
		do: [:sel | Approved add: sel].
	"adding"
	#(#addFirst: #addLast: )
		do: [:sel | AddAndRemove add: sel].
	"OrderedCollection, SortedCollection"
	"accessing"
	"copying"
	"adding"
	"removing"
	"enumerating"
	"private"
	"accessing"
	#(#after: #before: #copyEmpty #growSize #sortBlock )
		do: [:sel | Approved add: sel].
	"adding"
	"removing"
	"accessing"
	#(#add:after: #add:afterIndex: #add:before: #addAllFirst: #addAllLast: #addFirst: #addLast: #removeAt: #removeFirst #removeLast #sortBlock: )
		do: [:sel | AddAndRemove add: sel].
	"Character"
	"in class, instance creation"
	"accessing untypeable characters"
	"constants"
	"accessing"
	"comparing"
	"testing"
	"copying"
	"converting"
	#(#allCharacters #digitValue: #new #separators #backspace #cr #enter #lf #linefeed #nbsp #newPage #space #tab #alphabet #characterTable #asciiValue #digitValue #isAlphaNumeric #isDigit #isLetter #isLowercase #isSafeForHTTP #isSeparator #isSpecial #isUppercase #isVowel #tokenish #asIRCLowercase #asLowercase #asUppercase )
		do: [:sel | Approved add: sel].
	"String"
	"in class, instance creation"
	"primitives"
	"internet"
	"accessing"
	"comparing"
	"copying"
	"converting"
	"displaying"
	"printing"
	"system primitives"
	"Celeste"
	"internet"
	"testing"
	"paragraph support"
	"arithmetic"
	#(#crlf #fromPacked: #findFirstInString:inSet:startingAt: #indexOfAscii:inString:startingAt:endingAt: #valueOfHtmlEntity: #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 #alike: #beginsWith: #caseSensitiveLessOrEqual: #charactersExactlyMatching: #compare: #crc16 #endsWith: #endsWithAnyOf: #sameAs: #startingAt:match:startingAt: #copyReplaceTokens:with: #padded:to:with: #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 #compare:with:collated: #withCRs #decodeMimeHeader #decodeQuotedPrintable #replaceHtmlCharRefs #unescapePercents #withInternetLineEndings #withSqueakLineEndings #withoutQuoting #isAllSeparators #lastSpacePosition #indentationIfBlank: )
		do: [:sel | Approved add: sel].
	#(#byteAt:put: #translateToLowercase #match: )
		do: [:sel | AddAndRemove add: sel].
	"Symbol"
	"in class, private"
	"access"
	"accessing"
	"comparing"
	"copying"
	"converting"
	"printing"
	"testing"
	#(#hasInterned:ifTrue: #morePossibleSelectorsFor: #possibleSelectorsFor: #selectorsContaining: #thatStarts:skipping: #isInfix #isKeyword #isPvtSelector #isUnary )
		do: [:sel | Approved add: sel].
	"Array"
	"comparing"
	"converting"
	"printing"
	"private"
	#(#evalStrings #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"
	"platform independent access"
	"converting"
	#(#doubleWordAt: #wordAt: #longAt:bigEndian: #shortAt:bigEndian: #unsignedLongAt:bigEndian: #unsignedShortAt:bigEndian: )
		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"
			"primitives-translated"
			"converting"
			"private"
			"user interface"
			#(#*= #+= #-= #/= #primAddArray: #primAddScalar: #primDivArray: #primDivScalar: #primMulArray: #primMulScalar: #primSubArray: #primSubScalar: #primAddArray:withArray:from:to: #primMulArray:withArray:from:to: #primSubArray:withArray:from:to: )
				do: [:sel | Approved add: sel]].
	"IntegerArray, WordArray"
	"RunArray"
	"in class, instance creation"
	"accessing"
	"adding"
	"copying"
	"private"
	#(#runs:values: #scanFrom: #runLengthAt: #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"
	"printing"
	#(#next: #nextMatchAll: #nextMatchFor: #upToEnd #next:put: #nextPut: #nextPutAll: #print: #printHtml: )
		do: [:sel | AddAndRemove add: sel].
	"PositionableStream"
	"accessing"
	"testing"
	"positioning"
	#(#contentsOfEntireFile #originalContents #peek #peekFor: #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"
	"character writing"
	#(#resetToStart #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"
	"accessing"
	"comparing"
	"arithmetic"
	"truncation and round off"
	"polar coordinates"
	"point functions"
	"converting"
	"transforming"
	"copying"
	"interpolating"
	#(#r:degrees: #x:y: #x #y #degrees #r #theta #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 #asFloatPoint #asIntegerPoint #corner: #extent: #rect: #adhereTo: #rotateBy:about: #scaleBy: #scaleFrom:to: #translateBy: #interpolateTo:at: )
		do: [:sel | Approved add: sel].
	"Rectangle"
	"in class, instance creation"
	"accessing"
	"comparing"
	"rectangle functions"
	"testing"
	"truncation and round off"
	"transforming"
	"copying"
	#(#center:extent: #encompassing: #left:right:top:bottom: #merging: #origin:corner: #origin:extent: #area #bottom #bottomCenter #bottomLeft #bottomRight #boundingBox #center #corner #corners #innerCorners #left #leftCenter #origin #right #rightCenter #top #topCenter #topLeft #topRight #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: #containsPoint: #containsRect: #hasPositiveExtent #intersects: #isTall #isWide #align:with: #centeredBeneath: #newRectFrom: #squishedWithin: )
		do: [:sel | Approved add: sel].
	"Color"
	"in class, instance creation"
	"named colors"
	"other"
	"access"
	"equality"
	"queries"
	"transformations"
	"groups of shades"
	"printing"
	"other"
	"conversions"
	"private"
	"copying"
	#(#colorFrom: #colorFromPixelValue:depth: #fromRgbTriplet: #gray: #h:s:v: #r:g:b: #r:g:b:alpha: #r:g:b:range: #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 #colorNames #indexedColors #pixelScreenForDepth: #quickHighLight: #alpha #blue #brightness #green #hue #luminance #red #saturation #isBitmapFill #isBlack #isGray #isSolidFill #isTranslucent #isTranslucentColor #alpha: #dansDarker #darker #lighter #mixed:with: #muchLighter #slightlyDarker #slightlyLighter #veryMuchLighter #alphaMixed:with: #darkShades: #lightShades: #mix:shades: #wheel: #shortPrintString #colorForInsets #rgbTriplet #asB3DColor #asColor #balancedPatternForDepth: #bitPatternForDepth: #closestPixelValue1 #closestPixelValue2 #closestPixelValue4 #closestPixelValue8 #dominantColor #halfTonePattern1 #halfTonePattern2 #indexInMap: #pixelValueForDepth: #pixelWordFor:filledWith: #pixelWordForDepth: #scaledPixelValue32 #privateAlpha #privateBlue #privateGreen #privateRGB #privateRed )
		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! !


!MiscPrimitivePlugin class methodsFor: 'translation' stamp: 'sac 10/3/2001 12:32'!
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:) 

#(#String #indexOfAscii:inString:startingAt:endingAt:)
#(#String #scanWhileMatching:forLast:inString:startingAt:endingAt:)


 #(#String #findSubstring:in:startingAt:matchTable:) #(#String #stringHash:initialHash:) #(#SampledSound #convert8bitSignedFrom:to16Bit:) )! !


!String methodsFor: 'accessing' stamp: 'sac 10/3/2001 12:08'!
matchWhileIn: aCharacterSet1 forLastMatching: aCharacterSet2 startingAt: start 
	^ self
		matchWhileIn: aCharacterSet1
		forLastMatching: aCharacterSet2
		startingAt: start
		endingAt: self size! !

!String methodsFor: 'accessing' stamp: 'sac 10/3/2001 12:08'!
matchWhileIn: aCharacterSet1 forLastMatching: aCharacterSet2 startingAt: start endingAt: end 

	^ String
		scanWhileMatching: aCharacterSet1 byteArrayMap
		forLast: aCharacterSet2 byteArrayMap
		inString: self
		startingAt: start
		endingAt: (end min: self size)!
]style[(14 14 18 14 13 5 11 3 6 6 22 14 25 14 26 4 15 5 14 3 6 4 6)f1b,f1cblue;b,f1b,f1cblue;b,f1b,f1cblue;b,f1b,f1cblue;b,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cblue;i,f1,f1cmagenta;,f1! !

!String methodsFor: 'accessing' stamp: 'sac 10/3/2001 12:09'!
matchWhileIn: aCharacterSet startingAt: start endingAt: end 
	^ self
		matchWhileIn: aCharacterSet 
		forLastMatching: aCharacterSet 
		startingAt: start
		endingAt: end! !


!String class methodsFor: 'primitives' stamp: 'sac 10/3/2001 14:40'!
indexOfAscii: anInteger inString: aString startingAt: start endingAt: end 
	<primitive: 'primitiveIndexOfAsciiInSubString' module: 'MiscPrimitivePlugin'>

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 class methodsFor: 'primitives' stamp: 'sac 10/3/2001 15:12'!
scanWhileMatching: inclusionMap1 forLast: inclusionMap2 inString: aString 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."
	| matchloc |
	<primitive: 'primitiveMatchInSubString' module: 'MiscPrimitivePlugin'>
	self var: #aString declareC: 'unsigned char *aString'.
	self var: #inclusionMap1 declareC: 'char *inclusionMap1'.
	self var: #inclusionMap2 declareC: 'char *inclusionMap2'.
	matchloc _ 0.
	start
		to: end
		do: [:pos | (inclusionMap1 at: (aString at: pos) asciiValue + 1)
					= 1
				ifTrue: [(inclusionMap2 at: (aString at: pos) asciiValue + 1)
							= 1
						ifTrue: [matchloc _ pos]]
				ifFalse: [^ matchloc]].
	^ matchloc! !

String class removeSelector: #scanWhileIn:indexOfLast:inString:startingAt:endingAt:!
Smalltalk removeClassNamed: #InterpreterSupportCode!
-------------- next part --------------
'From Squeak3.2alpha of 3 October 2001 [latest update: #4411] on 3 October 2001 at 4:08:54 pm'!

!CharacterSet class methodsFor: 'instance creation' stamp: 'sac 9/22/2001 02:25'!
allAlphabetic
	"return a set containing only alphabetic characters"
	^self allMatching: [ :char | char isLetter].

 ! !

!CharacterSet class methodsFor: 'instance creation' stamp: 'sac 9/22/2001 02:23'!
allCharacters
	"return a set containing all characters"
	^self allMatching: [ :unused | true ]! !

!CharacterSet class methodsFor: 'instance creation' stamp: 'sac 9/22/2001 02:25'!
allMatching: aBlock 
	"return a set containing all characters matching some predicate."
	| set character |
	set _ self empty.
	0
		to: 255
		do: [:ascii | 
			character _ Character value: ascii.
			(aBlock value: character)
				ifTrue: [set add: character]].
	^ set! !

!CharacterSet class methodsFor: 'instance creation' stamp: 'sac 9/22/2001 02:30'!
allNumerical
	"return a set containing only alphabetic characters"
	^ self
		allMatching: [:char | char isDigit]! !

!CharacterSet class methodsFor: 'instance creation' stamp: 'sac 10/1/2001 17:24'!
allSeperator
	"return a set containing only alphabetic characters"
	^ self
		allMatching: [:char | char isSeparator]! !


!SharedQueue methodsFor: 'testing' stamp: 'sac 8/9/2001 13:22'!
critical: aBlock
	"Evaluate aBlock with the accessProtect semaphore held. Do NOT mutate the queue during aBlock."
	"This is to allow variable operation based on the sharedqueue length, for example,
	 disabling writers when the queue gets too long

		queue critical: [queue size > 10. ifTrue: self writerDisable wait]

	And the writer runs
		self wait.
		self signal."

	accessProtect critical: aBlock.

! !


!Socket methodsFor: 'sending-receiving' stamp: 'sac 9/24/2001 01:41'!
getData
	"Get some data"
	| buf bytesRead |
	(self waitForDataUntil: Socket standardDeadline)
		ifFalse: [self error: 'getData timeout'].
	buf _ String new: 4096.
	bytesRead _ self
				primSocket: socketHandle
				receiveDataInto: buf
				startingAt: 1
				count: buf size.
	^ buf copyFrom: 1 to: bytesRead! !

!Socket methodsFor: 'sending-receiving' stamp: 'sac 9/24/2001 03:17'!
receiveDataInto: aStringOrByteArray at: starting
	"Receive data into the given buffer and return the number of bytes 
	received. Note the given buffer may be only partially filled by the 
	received data."
	^ self
		primSocket: socketHandle
		receiveDataInto: aStringOrByteArray
		startingAt: starting
		count: (aStringOrByteArray size - starting) + 1! !

!Socket methodsFor: 'sending-receiving' stamp: 'sac 9/29/2001 05:31'!
trySendSomeData: aStringOrByteArray startIndex: startIndex count: count 
	"Send up to count bytes of the given data starting at the given index.  
	Answer the number of bytes actually sent. Do not do any timeouts for data not sent."
	"Note: This operation may have to be repeated multiple times to send a  
	large amount of data."
	^ self
		primSocket: socketHandle
		sendData: aStringOrByteArray
		startIndex: startIndex
		count: count! !


!UndefinedObject methodsFor: 'testing' stamp: 'sac 9/24/2001 07:12'!
isNil
	"Refer to the comment in ProtoObject|isNil."
	^ true! !


!WriteStream methodsFor: 'character writing' stamp: 'sac 8/10/2001 15:01'!
crlf
	"Append a return character to the receiver."

	self nextPut: Character cr.
	self nextPut: Character lf.! !

!WriteStream methodsFor: 'character writing' stamp: 'sac 8/10/2001 15:00'!
lf
	"Append a return character to the receiver."

	self nextPut: Character lf! !


!ReadWriteStream methodsFor: 'accessing' stamp: 'sac 9/24/2001 03:47'!
on: aCollection 
	super on: aCollection.
	readLimit _ aCollection size.
! !



More information about the Squeak-dev mailing list