[squeak-dev] The Inbox: EToys-ct.401.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 20 12:36:47 UTC 2020


A new version of EToys was added to project The Inbox:
http://source.squeak.org/inbox/EToys-ct.401.mcz

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

Name: EToys-ct.401
Author: ct
Time: 20 August 2020, 2:36:39.45064 pm
UUID: 5a05fe89-08aa-424a-b94a-b55283faff49
Ancestors: EToys-eem.400

Complements 60Deprecated-ct.80 (deprecation #doWithIndex: & Co.).

=============== Diff against EToys-eem.400 ===============

Item was changed:
  ----- Method: BookMorph>>saveBookForRevert (in category '*Etoys-Squeakland-master pages') -----
  saveBookForRevert
  	"Consider this the master version of the book, with regard to which pages are in it, what their order is, and what their content is"
  
  	| forRevert |
  	forRevert := OrderedCollection new.
+ 	pages withIndexDo: 
- 	pages doWithIndex: 
  		[: pg :index | 
  			pg setProperty: #revertKey toValue: index.
  			forRevert add: (index -> pg copy)].
  	self setProperty:# pagesForRevert toValue: forRevert!

Item was changed:
  ----- Method: Chess960Morph>>reinstallPieces (in category 'resizing') -----
  reinstallPieces
  
+ 	board whitePlayer pieces withIndexDo: [:pc :n |
- 	board whitePlayer pieces doWithIndex: [:pc :n |
  		pc isZero ifFalse: [
  			self addedPiece: pc at: n white: true]].
  
+ 	board blackPlayer pieces withIndexDo: [:pc :n |
- 	board blackPlayer pieces doWithIndex: [:pc :n |
  		pc isZero ifFalse: [
  			self addedPiece: pc at: n white: false]].!

Item was changed:
  ----- Method: Chess960Player>>addBlackPieces: (in category 'adding/removing') -----
  addBlackPieces: aChess960Configuration
  
  	self configuration: aChess960Configuration.
  
+ 	configuration positions withIndexDo: [:p :n | self addPiece: p at: 56+n].
- 	configuration positions doWithIndex: [:p :n | self addPiece: p at: 56+n].
  	49 to: 56 do:[:i| self addPiece: Pawn at: i].!

Item was changed:
  ----- Method: Chess960Player>>addWhitePieces: (in category 'adding/removing') -----
  addWhitePieces: aChess960Configuration
  
  	self configuration: aChess960Configuration.
  
+ 	configuration positions withIndexDo: [:p :n | self addPiece: p at: n].
- 	configuration positions doWithIndex: [:p :n | self addPiece: p at: n].
  	9 to: 16 do:[:i| self addPiece: Pawn at: i].
  !

Item was changed:
  ----- Method: ChineseCheckers>>drawOn: (in category 'drawing') -----
  drawOn: aCanvas 
  
  	| row1 row2 offset dotExtent |
  	super drawOn: aCanvas.   "Draw square board"
  
  	"Only draw rows in the clipping region"
  	dotExtent := (self width//25) asPoint.
  	offset := self pieceSize - dotExtent + 1 // 2.  "Offset of smaller dots rel to larger"
  	row1 := (self boardLocAt: aCanvas clipRect topLeft) x max: 1.
  	row2 := (self boardLocAt: aCanvas clipRect bottomRight) x min: board size.
  	row1 to: row2 do:
+ 		[:row | (board at: row) withIndexDo:
- 		[:row | (board at: row) doWithIndex:
  			[:cell :i | cell ifNotNil:
  				[aCanvas fillOval: ((self cellPointAt: (row at i)) + offset extent: dotExtent)
  					color: (colors at: cell+1)]]]!

Item was changed:
  ----- Method: CipherPanel>>encodedQuote: (in category 'initialization') -----
  encodedQuote: aString 
  	"World addMorph: CipherPanel new"
  	| morph prev |
  	aString isEmpty
  		ifTrue: [^ self].
  	(letterMorphs isNil
  			or: [self isClean])
  		ifFalse: [(self confirm: 'Are you sure you want to discard all typing?' translated)
  				ifFalse: [^ self]].
  	haveTypedHere := false.
  	quote := aString asUppercase.
  	prev := nil.
  	originalMorphs := quote asArray
+ 				withIndexCollect: [:c :i | WordGameLetterMorph new plain indexInQuote: i id1: nil;
- 				collectWithIndex: [:c :i | WordGameLetterMorph new plain indexInQuote: i id1: nil;
  						
  						setLetter: (quote at: i)].
  	letterMorphs := OrderedCollection new.
  	decodingMorphs := quote asArray
+ 				withIndexCollect: [:c :i | (quote at: i) isLetter
- 				collectWithIndex: [:c :i | (quote at: i) isLetter
  						ifTrue: [morph := WordGameLetterMorph new underlined indexInQuote: i id1: nil.
  							morph
  								on: #mouseDown
  								send: #mouseDownEvent:letterMorph:
  								to: self.
  							morph
  								on: #keyStroke
  								send: #keyStrokeEvent:letterMorph:
  								to: self.
  							letterMorphs addLast: morph.
  							morph predecessor: prev.
  							prev
  								ifNotNil: [prev successor: morph].
  							prev := morph]
  						ifFalse: [WordGameLetterMorph new plain indexInQuote: i id1: nil;
  								
  								setLetter: (quote at: i)]].
  	self color: originalMorphs first color.
  	self extent: 500 @ 500!

Item was changed:
  ----- Method: DocLibrary>>saveDocCheck: (in category 'doc pane') -----
  saveDocCheck: aMorph
  	"Make sure the document gets attached to the version of the code that the user was looking at.  Is there a version of this method in a changeSet beyond the updates we know about?  Works even when the user has internal update numbers and the documentation is for external updates (It always is)."
  
  	| classAndMethod parts selector class lastUp beyond ours docFor unNum ok key verList ext response |
  	classAndMethod := aMorph valueOfProperty: #classAndMethod.
  	classAndMethod ifNil: [
  		^ self error: 'need to know the class and method'].	"later let user set it"
  	parts := classAndMethod findTokens: ' .'.
  	selector := parts last asSymbol.
  	class := Smalltalk at: (parts first asSymbol) ifAbsent: [^ self saveDoc: aMorph].
  	parts size = 3 ifTrue: [class := class class].
  	"Four indexes we are looking for:
  		docFor = highest numbered below lastUpdate that has method.
  		unNum = a higher unnumbered set that has method.
  		lastUp = lastUpdate we know about in methodVersions
  		beyond = any set about lastUp that has the method."
+ 	ChangeSet allChangeSets withIndexDo: [:cs :ind | "youngest first"
- 	ChangeSet allChangeSets doWithIndex: [:cs :ind | "youngest first"
  		(cs name includesSubstring: lastUpdateName) ifTrue: [lastUp := ind].
  		(cs atSelector: selector class: class) ~~ #none ifTrue: [
  			lastUp ifNotNil: [beyond := ind. ours := cs name]
  				ifNil: [cs name first isDigit ifTrue: [docFor := ind] 
  						ifFalse: [unNum := ind. ours := cs name]]]].
  	"See if version the user sees is the version he is documenting"
  	ok := beyond == nil.
  	unNum ifNotNil: [docFor ifNotNil: [ok := docFor > unNum]
  						ifNil: [ok := false]].  "old changeSets gone"
  	ok ifTrue: [^ self saveDoc: aMorph].
  
  	key := DocLibrary properStemFor: classAndMethod.
  	verList := (methodVersions at: key ifAbsent: [#()]), #(0 0).
  	ext := verList first.	"external update number we will write to"
  	response := (PopUpMenu labels: 'Cancel\Broadcast Page' withCRs)
  				startUpWithCaption: 'You are documenting a method in External Update ', ext asString, '.\There is a more recent version of that method in ' withCRs, ours, 
  '.\If you are explaining the newer version, please Cancel.\Wait until that version appears in an External Update.' withCRs.
  	response = 2 ifTrue: [self saveDoc: aMorph].
  !

Item was changed:
  ----- Method: EventRollMorph>>setMediaEventMorphs (in category 'display') -----
  setMediaEventMorphs
  	"Place morphs representing the media track on the roll."
  
  	| aMorph aWheel |
  	mediaTrack ifEmpty: [^ self].
  	aWheel := Color wheel: mediaTrack size.
+ 	mediaTrack withIndexDo:
- 	mediaTrack doWithIndex:
  		[:evt :index |
  			aMorph := MediaEventMorph new.
  			aMorph hResizing: #shrinkWrap.
  			aMorph vResizing: #shrinkWrap.
  			aMorph color: ((aWheel at: index) alpha: 0.5).
  			aMorph event: evt.
  			aMorph extent: ((evt durationInMilliseconds / millisecondsPerPixel) @ 32).
  			aMorph left: ((evt timeStamp - startTime)/ millisecondsPerPixel).
  			aMorph top: 84.
  			actualRoll addMorphBack: aMorph]!

Item was changed:
  ----- Method: MentoringEventRecorder>>mergeMediaEvent: (in category 'event handling') -----
  mergeMediaEvent: anEvent
  	"Merge the event, presently time-stamped with a relative time-stamp., with my existing tape.  Answer the merged tape.  It is the responsibility of the sender to notify other objects that may be interested in the change, such as an event roll."
  
  	| itsTimeStamp eventFollowingIt newTape anIndex itsCopy copysTimeStamp |
  	itsTimeStamp :=  anEvent timeStamp.
  	itsCopy := anEvent copy.
  	itsCopy timeStamp: (copysTimeStamp := itsTimeStamp + tape first timeStamp).
  
  	eventFollowingIt := tape detect: [:evt | evt timeStamp > copysTimeStamp]  ifNone: [nil].
  	anIndex := eventFollowingIt
  		ifNil:
  			[tape size + 1]
  		ifNotNil:
  			[tape indexOf: eventFollowingIt].
  
  	newTape := Array streamContents:
  		[:aStream | 
+ 			tape withIndexDo:
- 			tape doWithIndex:
  				[:evt :index |
  					index = anIndex ifTrue:
  						[aStream nextPut: itsCopy].
  					aStream nextPut: evt].
  			anIndex > tape size ifTrue: [aStream nextPut: itsCopy]].
  
  	tape := newTape!

Item was changed:
  ----- Method: MouseEventEditor>>initializeFor:forEventRoll: (in category 'initialization') -----
  initializeFor: aMouseEventSequenceMorph forEventRoll: aRoll
  	"Initialize the receiver as an editor for the given mouse-event-sequence and event-roll."
  
  	| aTheatre aMorph |
  	self color: (Color green muchLighter alpha: 0.7).
  	aTheatre := aRoll eventTheatre.
  	mouseEventSequenceMorph := aMouseEventSequenceMorph.
  	self extent: aTheatre initialContentArea extent.
  	self setNameTo: 'mouse event editor'.
+ 	mouseEventSequenceMorph events withIndexDo:
- 	mouseEventSequenceMorph events doWithIndex:
  		[:evt :index |
  			aMorph := self discRepresentingEvent: evt index: index.
  			aMorph center: evt position - aTheatre initialContentArea topLeft.
  			self addMorphFront: aMorph]!

Item was changed:
  ----- Method: Player>>absorbBackgroundDataFrom:forInstanceVariables: (in category 'slots-kernel') -----
  absorbBackgroundDataFrom: aLine forInstanceVariables: slotNames
  	"Fill my background fields from the substrings in a tab-delimited line of data.  At the moment this only really cateres to string-valued items"
  
+ 	slotNames withIndexDo:
- 	slotNames doWithIndex:
  		[:aSlotName :anIndex |
  			aLine do:
  				[:aValue |
  					self instVarNamed: aSlotName put: aValue] toFieldNumber: anIndex]!

Item was changed:
  ----- Method: Player>>universalTilesForInterface: (in category 'scripts-kernel') -----
  universalTilesForInterface: aMethodInterface
  	"Return universal tiles for the given method interface.  Record who self is."
  
  	| ms itsSelector argList makeSelfGlobal phrase aType |
  	itsSelector := aMethodInterface selector.
  	argList := OrderedCollection new.
+ 	aMethodInterface argumentVariables withIndexDo:
- 	aMethodInterface argumentVariables doWithIndex:
  		[:anArgumentVariable :anIndex | | argTile | 
  			argTile := ScriptingSystem tileForArgType: (aType := aMethodInterface typeForArgumentNumber: anIndex).
  			argList add: (aType == #Player 
  				ifTrue: [argTile actualObject]
  				ifFalse: [argTile literal]).	"default value for each type"].
  
  	ms := MessageSend receiver: self selector: itsSelector arguments: argList asArray.
  	"For CardPlayers, use 'self'.  For others, name me, and use my global name."
  	makeSelfGlobal := self class officialClass ~~ CardPlayer.
  	phrase := ms asTilesIn: self class globalNames: makeSelfGlobal.
  	makeSelfGlobal ifFalse: [phrase setProperty: #scriptedPlayer toValue: self].
  	^ phrase
  !

Item was changed:
  ----- Method: QuickGuideMorph class>>getWordyName:forCategory: (in category 'initialization') -----
  getWordyName: guideName forCategory: guideCategory
  	"With guideName and category already filled in, make a name in words.  Remove the cat name, and trailing digits.  Separate words at capital letters.  NavBarHowToUse3 -> 'How To Use'  "
  
  	| gn mm tt |
  	gn := guideName allButFirst: guideCategory size.
  	gn := gn withoutTrailingDigits.
  	mm := gn size.
+ 	gn reversed withIndexDo: [:cc :ind | 
- 	gn reversed doWithIndex: [:cc :ind | 
  		ind < mm  ifTrue: [
  			cc isUppercase ifTrue: [ 
  				tt := mm + 1 - ind.
  				gn := (gn copyFrom: 1 to: tt-1), ' ', (gn copyFrom: tt to: gn size)].
  			cc == $- ifTrue: [
  				tt := mm + 1 - ind.
  				gn at: tt put: $ ].	"convert dash to space"
  			]].
  	^ gn!

Item was changed:
  ----- Method: ScriptEditorMorph>>indexOfMorphAbove: (in category 'dropping/grabbing') -----
  indexOfMorphAbove: aPoint
  	"Return index of lowest morph whose bottom is above aPoint.
  	Will return 0 if the first morph is not above aPoint"
+ 	submorphs withIndexDo:
- 	submorphs doWithIndex:
  		[:m :i | m fullBounds bottom >= aPoint y ifTrue:
  					[^ (i max: firstTileRow) - 1]].
  	^ submorphs size!

Item was changed:
  ----- Method: ScriptEditorMorph>>reinsertSavedTiles: (in category 'other') -----
  reinsertSavedTiles: savedTiles
  	"Revert the scriptor to show the saved tiles"
  
+ 	self submorphs withIndexDo: [:m :i | i > 1 ifTrue: [m delete]].
- 	self submorphs doWithIndex: [:m :i | i > 1 ifTrue: [m delete]].
  	self addAllMorphs: savedTiles.
  	self allMorphsDo: [:m | m isTileScriptingElement ifTrue: [m bringUpToDate]].
  	self install.
  	self showingMethodPane: false!

Item was changed:
  ----- Method: SmalltalkImage>>macVmMajorMinorBuildVersion (in category '*Etoys-Squeakland-system attribute') -----
  macVmMajorMinorBuildVersion	
  	"SmalltalkImage current macVmMajorMinorBuildVersion"
  	| aString rawTokens versionPart versionTokens versionArray |
  	aString := self vmVersion.
  	aString ifNil: [^ #(0 0 0)].
  	rawTokens := ((aString copyAfterLast: $])
  				findTokens: $ ).
  	versionPart := rawTokens detect: [:each | each includes: $.] ifNone: [^#(0 0 0)]. 
  	versionTokens := versionPart findTokens: $..
+ 	versionArray := #(0 0 0) withIndexCollect: [:each :index |
- 	versionArray := #(0 0 0) collectWithIndex: [:each :index |
  		(versionTokens at: index ifAbsent:['']) initialIntegerOrNil ifNil: [each]].
  	^versionArray!

Item was changed:
  ----- Method: StackMorph>>getAllText (in category 'menu') -----
  getAllText
  	"Collect the text for each card.  Just point at strings so don't have to recopy them.  (Parallel array of urls for ID of cards.  Remote cards not working yet.)
  	allText = Array (cards size) of arrays (fields in it) of strings of text.
  	allTextUrls = Array (cards size) of urls or card numbers."
  
  	| oldUrls oldStringLists allText allTextUrls |
  	self writeSingletonData.
  	oldUrls := self valueOfProperty: #allTextUrls ifAbsent: [#()].
  	oldStringLists := self valueOfProperty: #allText ifAbsent: [#()].
  	allText := self privateCards collect: [:pg | OrderedCollection new].
  	allTextUrls := Array new: self privateCards size.
+ 	self privateCards withIndexDo: [:aCard :ind | | aUrl which |
- 	self privateCards doWithIndex: [:aCard :ind | | aUrl which |
  		aUrl := aCard url.  aCard isInMemory 
  			ifTrue: [(allText at: ind) addAll: (aCard allStringsAfter: nil).
  				aUrl ifNil: [aUrl := ind].
  				allTextUrls at: ind put: aUrl]
  			ifFalse: ["Order of cards on server may be different.  (later keep up to date?)"
  				"*** bug in this algorithm if delete a page?"
  				which := oldUrls indexOf: aUrl.
  				allTextUrls at: ind put: aUrl.
  				which = 0 ifFalse: [allText at: ind put: (oldStringLists at: which)]]].
  	self setProperty: #allText toValue: allText.
  	self setProperty: #allTextUrls toValue: allTextUrls.
  	^ allText!



More information about the Squeak-dev mailing list