[Pkg] The Trunk: EToys-ul.298.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 27 11:07:18 UTC 2017


Levente Uzonyi uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-ul.298.mcz

==================== Summary ====================

Name: EToys-ul.298
Author: ul
Time: 27 April 2017, 1:02:38.02162 pm
UUID: d4ecbed2-60da-4651-b11b-b6ecd27bee67
Ancestors: EToys-nice.297

- removed some of the extension methods, mostly those which have already been removed from the Trunk
- removed #fixTemps sends
- use the generic quicksort implementation in ChessMoveList

=============== Diff against EToys-nice.297 ===============

Item was removed:
- ----- Method: Behavior>>indexIfCompact (in category '*Etoys-Squeakland-private') -----
- indexIfCompact
- 	"If these 5 bits are non-zero, then instances of this class
- 	will be compact.  It is crucial that there be an entry in
- 	Smalltalk compactClassesArray for any class so optimized.
- 	See the msgs becomeCompact and becomeUncompact."
- 	^ (format bitShift: -11) bitAnd: 16r1F
- "
- Smalltalk compactClassesArray doWithIndex: 
- 	[:c :i | c == nil ifFalse:
- 		[c indexIfCompact = i ifFalse: [self halt]]]
- "!

Item was changed:
  ----- Method: BroomMorph>>filter: (in category 'accessing') -----
  filter: aBlock
  	"Set my acceptance filter. aBlock should return true for all Morphs to be moved"
+ 	filter := aBlock!
- 	filter := aBlock fixTemps!

Item was removed:
- ----- Method: ByteString>>primitiveFindSubstring:in:startingAt:matchTable: (in category '*Etoys-Squeakland-comparing') -----
- primitiveFindSubstring: key in: body startingAt: start matchTable: matchTable
- 	"Answer the index in the string body at which the substring key first occurs, at or beyond start.  The match is determined using matchTable, which can be used to effect, eg, case-insensitive matches.  If no match is found, zero will be returned.
- 
- 	The algorithm below is not optimum -- it is intended to be translated to C which will go so fast that it wont matter."
- 	| index |
- 	<primitive: 'primitiveFindSubstring' module: 'MiscPrimitivePlugin'>
- 	<var: #key declareC: 'unsigned char *key'>
- 	<var: #body declareC: 'unsigned char *body'>
- 	<var: #matchTable declareC: 'unsigned char *matchTable'>
- 
- 	key size = 0 ifTrue: [^ 0].
- 	start to: body size - key size + 1 do:
- 		[:startIndex |
- 		index := 1.
- 			[(matchTable at: (body at: startIndex+index-1) asciiValue + 1)
- 				= (matchTable at: (key at: index) asciiValue + 1)]
- 				whileTrue:
- 				[index = key size ifTrue: [^ startIndex].
- 				index := index+1]].
- 	^ 0
- "
- ' ' findSubstring: 'abc' in: 'abcdefabcd' startingAt: 1 matchTable: CaseSensitiveOrder 1
- ' ' findSubstring: 'abc' in: 'abcdefabcd' startingAt: 2 matchTable: CaseSensitiveOrder 7
- ' ' findSubstring: 'abc' in: 'abcdefabcd' startingAt: 8 matchTable: CaseSensitiveOrder 0
- ' ' findSubstring: 'abc' in: 'abcdefABcd' startingAt: 2 matchTable: CaseSensitiveOrder 0
- ' ' findSubstring: 'abc' in: 'abcdefABcd' startingAt: 2 matchTable: CaseInsensitiveOrder 7
- "!

Item was removed:
- ----- Method: Character>>asUnicodeChar (in category '*Etoys-Squeakland-converting') -----
- asUnicodeChar
- 	"@@@ FIXME: Make this use asUnicode and move it to its lonely sender @@@"
- 	| table charset v |
- 	self leadingChar = 0 ifTrue: [^ self asInteger].
- 	charset := EncodedCharSet charsetAt: self leadingChar.
- 	charset isCharset ifFalse: [^ self].
- 	table := charset ucsTable.
- 	table isNil ifTrue: [^ Character value: 16rFFFD].
- 
- 	v := table at: self charCode + 1.
- 	v = -1 ifTrue: [^ Character value: 16rFFFD].
- 
- 	^ Character leadingChar: charset unicodeLeadingChar code: v.!

Item was removed:
- ----- Method: ChessMoveList>>sort:to:using: (in category 'sorting') -----
- sort: i to: j using: sorter
- 	"Sort elements i through j of self to be nondescending according to sorter."
- 
- 	| di dij dj tt ij k l n |
- 	"The prefix d means the data at that index."
- 	(n := j + 1  - i) <= 1 ifTrue: [^self].	"Nothing to sort." 
- 	 "Sort di,dj."
- 	di := collection at: i.
- 	dj := collection at: j.
- 	(sorter sorts: di before: dj) ifFalse:["i.e., should di precede dj?"
- 		collection swap: i with: j.
- 		tt := di. di := dj. dj := tt].
- 	n > 2 ifTrue:["More than two elements."
- 		ij := (i + j) // 2.  "ij is the midpoint of i and j."
- 		 dij := collection at: ij.  "Sort di,dij,dj.  Make dij be their median."
- 		 (sorter sorts: di before: dij) ifTrue:["i.e. should di precede dij?"
- 			(sorter sorts: dij before: dj) "i.e., should dij precede dj?"
- 				ifFalse:[collection swap: j with: ij.
- 					 	dij := dj].
- 		] ifFalse:[  "i.e. di should come after dij"
- 			collection swap: i with: ij.
- 			 dij := di
- 		].
- 		n > 3 ifTrue:["More than three elements."
- 			"Find k>i and l<j such that dk,dij,dl are in reverse order.
- 			Swap k and l.  Repeat this procedure until k and l pass each other."
- 			 k := i.  l := j.
- 			[
- 				[l := l - 1.  k <= l and: [sorter sorts: dij before: (collection at: l)]]
- 					whileTrue.  "i.e. while dl succeeds dij"
- 				[k := k + 1.  k <= l and: [sorter sorts: (collection at: k) before: dij]]
- 					whileTrue.  "i.e. while dij succeeds dk"
- 				k <= l
- 			] whileTrue:[collection swap: k with: l]. 
- 			"Now l<k (either 1 or 2 less), and di through dl are all less than 
- 			or equal to dk through dj.  Sort those two segments."
- 			self sort: i to: l using: sorter.
- 			self sort: k to: j using: sorter]].
- !

Item was changed:
  ----- Method: ChessMoveList>>sortUsing: (in category 'sorting') -----
  sortUsing: historyTable
+ 	
+ 	^collection 
+ 		quickSortFrom: startIndex
+ 		to: readLimit
+ 		by: [ :a :b | historyTable sorts: a before: b ]!
- 	^self sort: startIndex to: readLimit using: historyTable!

Item was removed:
- ----- Method: Delay>>scheduleEvent (in category '*Etoys-Squeakland-private') -----
- scheduleEvent
- 	"Schedule this delay"
- 	resumptionTime := Time millisecondClockValue + delayDuration.
- 	AccessProtect critical:[
- 		ScheduledDelay := self.
- 		TimingSemaphore signal.
- 	].!

Item was removed:
- ----- Method: Dictionary>>errorKeyNotFound (in category '*Etoys-Squeakland-private') -----
- errorKeyNotFound
- 
- 	self error: 'key not found'!

Item was removed:
- ----- Method: Dictionary>>keyAt: (in category '*Etoys-Squeakland-private') -----
- keyAt: index
- 	"May be overridden by subclasses so that fixCollisions will work"
- 	| assn |
- 	assn := array at: index.
- 	assn == nil ifTrue: [^ nil]
- 				ifFalse: [^ assn key]!

Item was removed:
- ----- Method: Dictionary>>noCheckAdd: (in category '*Etoys-Squeakland-private') -----
- noCheckAdd: anObject
- 	"Must be defined separately for Dictionary because (self findElementOrNil:) expects a key, not an association.  9/7/96 tk"
- 
- 	array at: (self findElementOrNil: anObject key) put: anObject.
- 	tally := tally + 1!

Item was changed:
  ----- Method: FileList2 class>>buildFileTypeButtons:actionRow:fileList: (in category '*Etoys-Squeakland-blue ui') -----
  buildFileTypeButtons: window actionRow: actionRow fileList: aFileList 
  	| fileTypeInfo fileTypeButtons fileTypeRow aButton |
  	fileTypeInfo := self endingSpecs.
  	fileTypeRow := window addARowCentered: #().
  	fileTypeRow color: ScriptingSystem paneColor.
  	fileTypeRow layoutInset: 3 @ 3.
  	fileTypeRow cellInset: 2 @ 0.
  	fileTypeRow hResizing: #spaceFill.
  	fileTypeButtons := fileTypeInfo
  				collect: [:each | 
  					aButton := self
  								buildButtonText: each first
  								balloonText: nil
  								receiver: aFileList
  								selector: #update:fileTypeRow:morphUp:.
  					aButton arguments: {actionRow. fileTypeRow. aButton}.
  					aButton setProperty: #enabled toValue: true.
  					aButton setProperty: #buttonText toValue: each first.
  					aButton].
  	fileTypeRow addAllMorphs: fileTypeButtons.
  	aFileList directoryChangeBlock: [:newDir | self
  			enableTypeButtons: fileTypeButtons
  			info: fileTypeInfo
+ 			forDir: newDir].
- 			forDir: newDir] fixTemps.
  !

Item was removed:
- ----- Method: OrderedCollection>>errorConditionNotSatisfied (in category '*Etoys-Squeakland-private') -----
- errorConditionNotSatisfied
- 
- 	self error: 'no element satisfies condition'!

Item was removed:
- ----- Method: OrderedCollection>>grow (in category '*Etoys-Squeakland-adding') -----
- grow
- 	"Become larger. Typically, a subclass has to override this if the subclass
- 	adds instance variables."
- 	| newArray |
- 	newArray := Array new: self size + self growSize.
- 	newArray replaceFrom: 1 to: array size with: array startingAt: 1.
- 	array := newArray!

Item was removed:
- ----- Method: OrderedCollection>>growSize (in category '*Etoys-Squeakland-adding') -----
- growSize
- 	^ array size max: 2!

Item was removed:
- ----- Method: Random class>>theItsCompletelyBrokenTest (in category '*Etoys-Squeakland-testing') -----
- theItsCompletelyBrokenTest
- 	"Random theItsCompletelyBrokenTest"
- 	"The above should print as...
- 	(0.149243269650845 0.331633021743797 0.75619644800024 0.393701540023881 0.941783181364547 0.549929193942775 0.659962596213428 0.991354559078512 0.696074432551896 0.922987899707159 )
- 	If they are not these values (accounting for precision of printing) then something is horribly wrong: DO NOT USE THIS CODE FOR ANYTHING. "
- 	| rng |
- 	rng := Random new.
- 	rng seed: 2345678901.
- 	^ (1 to: 10) collect: [:i | rng next]!

Item was removed:
- ----- Method: Set>>init: (in category '*Etoys-Squeakland-private') -----
- init: n
- 	"Initialize array to an array size of n"
- 	array := Array new: n.
- 	tally := 0!

Item was removed:
- ----- Method: Set>>keyAt: (in category '*Etoys-Squeakland-private') -----
- keyAt: index
- 	"May be overridden by subclasses so that fixCollisions will work"
- 	^ array at: index!

Item was removed:
- ----- Method: Set>>noCheckAdd: (in category '*Etoys-Squeakland-private') -----
- noCheckAdd: anObject
- 	array at: (self findElementOrNil: anObject) put: anObject.
- 	tally := tally + 1!

Item was removed:
- ----- Method: Set>>swap:with: (in category '*Etoys-Squeakland-private') -----
- swap: oneIndex with: otherIndex
- 	"May be overridden by subclasses so that fixCollisions will work"
- 
- 	array swap: oneIndex with: otherIndex
- !

Item was removed:
- ----- Method: Set>>withArray: (in category '*Etoys-Squeakland-private') -----
- withArray: anArray
- 	"private -- for use only in copy"
- 	array := anArray!

Item was removed:
- ----- Method: SharedQueue>>init: (in category '*Etoys-Squeakland-private') -----
- init: size
- 
- 	contentsArray := Array new: size.
- 	readPosition := 1.
- 	writePosition := 1.
- 	accessProtect := Semaphore forMutualExclusion.
- 	readSynch := Semaphore new!

Item was removed:
- ----- Method: String>>findLastOccuranceOfString:startingAt: (in category '*Etoys-Squeakland-deprecated-3.10') -----
- findLastOccuranceOfString: subString startingAt: start 
- 	"Answer the index of the last occurance of subString within the receiver, starting at start. If 
- 	the receiver does not contain subString, answer 0."
- 
- 	^ self findLastOccurrenceOfString: subString startingAt: start
- !



More information about the Packages mailing list