[squeak-dev] The Trunk: EToys-mt.386.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 5 12:21:20 UTC 2020


Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.386.mcz

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

Name: EToys-mt.386
Author: mt
Time: 5 March 2020, 1:21:10.351611 pm
UUID: 86fc41a2-1bfb-7f43-95be-515947b458e1
Ancestors: EToys-mt.385

Removes more deprecated message sends. Adds some new deprecations.

=============== Diff against EToys-mt.385 ===============

Item was changed:
  ----- Method: CategoryViewer>>addNamePaneTo: (in category 'header pane') -----
  addNamePaneTo: header 
  	"Add the namePane, which is a pop-up"
  
  	| triangle aLabel |
  	namePane := BorderedMorph new.
  	namePane layoutPolicy: TableLayout new.
  	namePane hResizing: #spaceFill.
  	namePane listDirection: #leftToRight.
  	namePane wrapCentering: #center.
  	namePane cellInset: 2.
  	namePane layoutInset: 6 @ 0.
  
  	namePane color: ScriptingSystem baseColor.
+ 	namePane borderColor: (self userInterfaceTheme titleBorderColor
- 	namePane borderColor: (self userInterfaceTheme menuTitleBorderColor
  ifNil: [(Color r: 0.6 g: 0.7 b: 1)]).
  	namePane borderWidth: 0.
  
  	namePane height: TileMorph defaultH.
  	namePane useRoundedCornersInEtoys.
  
  	triangle := ImageMorph new image: (ScriptingSystem formAtKey: #MenuTriangle).
  	namePane addMorph: triangle.
  	aLabel := StringMorph contents: '---------' font: ScriptingSystem fontForViewerCategoryPopups.
  
  	namePane addMorphBack: aLabel.
  	namePane on: #mouseDown send: #chooseCategory to: self.
  	header addMorphBack: namePane!

Item was changed:
  ----- Method: CharRecog>>recogPar (in category 'historical & disused') -----
  recogPar | prv cdir result features char r s t dir |
  
  "Inits"				(p := Pen new) defaultNib: 1; down.
  	"for points"		pts := ReadWriteStream on: #().
  
  "Event Loop"	
+ 		[EventSensor default anyButtonPressed] whileFalse: [(EventSensor default peekPosition x < 50) ifTrue: [^''].].
- 		[Sensor anyButtonPressed] whileFalse: [(Sensor mousePoint x < 50) ifTrue: [^''].].
  
  "First-Time"			pts reset.		
  "will hold features"		ftrs := ''.
  
+ 					  (EventSensor default anyButtonPressed) ifTrue:
+ 						[pts nextPut: (bmin := bmax := t := s := sts := EventSensor default peekPosition).
- 					  (Sensor anyButtonPressed) ifTrue:
- 						[pts nextPut: (bmin := bmax := t := s := sts := Sensor mousePoint).
  						p place: sts. cdir := nil.
  
+ "Each-Time"		[EventSensor default anyButtonPressed] whileTrue:
- "Each-Time"		[Sensor anyButtonPressed] whileTrue:
  						[
+ "ink raw input"			p goto: (r := EventSensor default peekPosition).
- "ink raw input"			p goto: (r := Sensor mousePoint).
  "smooth it"				s := (0.5*s) + (0.5*r).
  "thin the stream"		((s x - t x) abs > 3 or:[(s y - t y) abs > 3]) ifTrue:
  							[ pts nextPut: t. 
  "bounding box"			bmin := bmin min: s. bmax := bmax max: s.
  "get current dir"				dir := (self fourDirsFrom: t to: s). t := s.
  							dir ~= ' dot... ' ifTrue: [
  "store new dirs"					cdir ~= dir ifTrue: [ftrs := ftrs, (cdir := dir)]].
  "for inked t's" 			p place: t; go: 1; place: r.
  							].
   "End Each-Time Loop"	].
  
  "Last-Time"	
  "start a new recog for next point"	[CharRecog new recognize] fork.
  
  "save last points"		pts nextPut: t; nextPut: r.
  "find rest of features"	features := self extractFeatures.
  "find char..."			char := CharacterDictionary at: features ifAbsent:
  "...or get from user"			[ result := FillInTheBlank request:
  							 'Not recognized. type char, or type ~: ', features.
  "ignore or..."				result = '~' ifTrue: ['']
  "...enter new char"			ifFalse: [CharacterDictionary at: features put: result. result]].
  
  "control the editor"		(char = 'cr' ifTrue: [Transcript cr] ifFalse:
  						[char = 'bs' ifTrue: [Transcript bs] ifFalse:
  						[char = 'tab' ifTrue:[Transcript tab] ifFalse:
  						[Transcript show: char]]]). 
  
  "End First-Time Loop"	]. 
  
  
  
  			   
   !

Item was changed:
  ----- Method: CharRecog>>recognize (in category 'historical & disused') -----
  recognize | prv cdir result features char r s t dir |
  
  "Alan Kay's recognizer as of 1/31/96.  This version preserved for historical purposes, and also because it's still called by the not-yet-deployed method recogPar.  Within the current image, the recognizer is now called via #recognizeAndDispatch:until:"
  
  
  "Inits"				(p := Pen new) defaultNib: 1; down.
  	"for points"		pts := ReadWriteStream on: #().
  
  "Event Loop"	
+ 					[(EventSensor default peekPosition x) < 50] whileFalse:
- 					[(Sensor mousePoint x) < 50] whileFalse:
  
  "First-Time"			[pts reset.		
  "will hold features"		ftrs := ''.
  
+ 					  (EventSensor default anyButtonPressed) ifTrue:
+ 						[pts nextPut: (bmin := bmax := t := s := sts := EventSensor default peekPosition).
- 					  (Sensor anyButtonPressed) ifTrue:
- 						[pts nextPut: (bmin := bmax := t := s := sts := Sensor mousePoint).
  						p place: sts. cdir := nil.
  
+ "Each-Time"		[EventSensor default anyButtonPressed] whileTrue:
- "Each-Time"		[Sensor anyButtonPressed] whileTrue:
  						[
+ "ink raw input"			p goto: (r := EventSensor default peekPosition).
- "ink raw input"			p goto: (r := Sensor mousePoint).
  "smooth it"				s := (0.5*s) + (0.5*r).
  "thin the stream"		((s x - t x) abs > 3 or:[(s y - t y) abs > 3]) ifTrue:
  							[ pts nextPut: t. 
  "bounding box"			bmin := bmin min: s. bmax := bmax max: s.
  "get current dir"				dir := (self fourDirsFrom: t to: s). t := s.
  							dir ~= ' dot... ' ifTrue: [
  "store new dirs"					cdir ~= dir ifTrue: [ftrs := ftrs, (cdir := dir)]].
  "for inked t's" 			p place: t; go: 1; place: r.
  							].
   "End Each-Time Loop"	].
  
  "Last-Time"	
  
  "save last points"		pts nextPut: t; nextPut: r.
  "find rest of features"	features := self extractFeatures.
  "find char..."			char := CharacterDictionary at: features ifAbsent:
  "...or get from user"			[ result := FillInTheBlank request:
  							 'Not recognized. type char, or type ~: ', features.
  "ignore or..."				result = '~' ifTrue: ['']
  "...enter new char"			ifFalse: [CharacterDictionary at: features put: result. result]].
  
  "control the editor"		(char = 'cr' ifTrue: [Transcript cr] ifFalse:
  						[char = 'bs' ifTrue: [Transcript bs] ifFalse:
  						[char = 'tab' ifTrue:[Transcript tab] ifFalse:
  						[Transcript show: char]]]). 
  
  "End First-Time Loop"	]. 
  
  "End Event-Loop" ]. 
  
  			   
   !

Item was changed:
  ----- Method: CharRecog>>recognizeAndDispatch:ifUnrecognized:until: (in category 'recognizer') -----
  recognizeAndDispatch: charDispatchBlock ifUnrecognized: unrecognizedFeaturesBlock until: terminationBlock
  	"Recognize characters, and dispatch each one found by evaluating charDispatchBlock; proceed until terminationBlock is true.  This method derives directly from Alan's 1/96 #recognize method, but factors out the character dispatch and the termination condition from the main body of the method.  2/2/96 sw.   2/5/96 sw: switch to using a class variable for the character dictionary, and don't put vacuous entries in the dictionary if the user gives an empty response to the prompt, and don't send empty characters onward, and use a variant of the FillInTheBlank that keeps the prompt clear of the working window.  8/17/96 tk: Turn cr, tab, bs into strings so they work.
  	 9/18/96 sw: in this variant, the block for handling unrecognized features is handed in as an argument, so that in some circumstances we can avoid putting up a prompt.  unrecognizedFeaturesBlock should be a one-argument block, which is handed in the features and which is expected to return a string which indicates the determined translation -- empty if none."
  
  	| prv cdir features char r s t dir |
  
  "Inits"				(p := Pen new) defaultNib: 1; down.
  	"for points"		pts := ReadWriteStream on: #().
  
  "Event Loop"	
  					[terminationBlock value] whileFalse:
  
  "First-Time"			[pts reset.		
  "will hold features"		ftrs := ''.
  
+ 					  (EventSensor default anyButtonPressed) ifTrue:
+ 						[pts nextPut: (bmin := bmax := t := s := sts := EventSensor default peekPosition).
- 					  (Sensor anyButtonPressed) ifTrue:
- 						[pts nextPut: (bmin := bmax := t := s := sts := Sensor mousePoint).
  						p place: sts. cdir := nil.
  
+ "Each-Time"		[EventSensor default anyButtonPressed] whileTrue:
+ "ink raw input"			[p goto: (r := EventSensor default peekPosition).
- "Each-Time"		[Sensor anyButtonPressed] whileTrue:
- "ink raw input"			[p goto: (r := Sensor mousePoint).
  "smooth it"				s := (0.5*s) + (0.5*r).
  "thin the stream"		((s x - t x) abs > 3 or:[(s y - t y) abs > 3]) ifTrue:
  							[pts nextPut: t. 
  "bounding box"				bmin := bmin min: s. bmax := bmax max: s.
  "get current dir"				dir := (self fourDirsFrom: t to: s). t := s.
  							dir ~= ' dot... ' ifTrue:
  "store new dirs"					[cdir ~= dir ifTrue: [ftrs := ftrs, (cdir := dir)]].
  "for inked t's" 				p place: t; go: 1; place: r]].
   "End Each-Time Loop"
  
  "Last-Time"	
  "save last points"		pts nextPut: t; nextPut: r.
  "find rest of features"	features := self extractFeatures.
  "find char..."			char := CharacterDictionary at: features ifAbsent:
  							[unrecognizedFeaturesBlock value: features].
  
  "special chars"		char size > 0 ifTrue:
  						[char = 'tab' ifTrue: [char := Tab].
  						char = 'cr' ifTrue:	[char := CR].
  "must be a string"		char class == Character ifTrue: 
  							[char := String with: char].
  						char = 'bs' ifTrue:	[char := BS].
  "control the editor"		charDispatchBlock value: char]]]
   !

Item was changed:
  ----- Method: CharRecog>>recognizeAndPutInTranscript (in category 'historical & disused') -----
  recognizeAndPutInTranscript
  	"Call Alan's recognizer repeatedly until the mouse is near the left edge of the screen, and dispatch keystrokes inferred to the Trancript.  2/2/96 sw"
  
  	^ self recognizeAndDispatch:
  
  		[:char | (char = 'cr') ifTrue: [Transcript cr] ifFalse:
  						[char = 'bs' ifTrue: [Transcript bs] ifFalse:
  						[char = 'tab' ifTrue:[Transcript tab] ifFalse:
  						[Transcript show: char]]]]
  
  		until:
+ 			[EventSensor default peekPosition x < 50]
- 			[Sensor mousePoint x < 50]
  
  "CharRecog new recognizeAndPutInTranscript"!

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 doWithIndex: [:cs :ind | "youngest first"
+ 		(cs name includesSubstring: lastUpdateName) ifTrue: [lastUp := ind].
- 		(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: KedamaAttributeEvaluator>>sortDependencies (in category 'actions') -----
  sortDependencies
  
  	| t keys array |
  	t := TopologicalSorter new.
  	keys := attributedTree allOccurences contents.
+ 	dependencies keys do: [:key |
- 	dependencies fasterKeys do: [:key |
  		array := (dependencies at: key) contents.
  		dependencies at: key put: array.
  	].
  	t collection: keys.
  	t edges: dependencies.
  	^ t sort.
  !

Item was changed:
  ----- Method: PasteUpMorph class>>putativeAdditionsToViewerCategoryPlayfieldOptions (in category '*Etoys-Squeakland-eToys-scripting') -----
  putativeAdditionsToViewerCategoryPlayfieldOptions
  	"Answer playfield options additions.  Some of these are not yet underpinned by code in the current image; these will follow in due course."
  
  	^ #(#'playfield options' (
  		(command roundUpStrays 'Bring back all objects whose current coordinates keep them from being visible, so that at least a portion of each of my interior objects can be seen.')
  		(command makeFitContents 'Adjust my bounds so that I fit precisely around all the objects within me')
  		(command showAllPlayers 'Make visible the viewers for all players which have user-written scripts in this playfield.')
  		(command hideAllPlayers 'Make invisible the viewers for all players in this playfield. This will save space before you publish this project')
  		(command shuffleSubmorphs 'Rearranges my contents in random order')
- 		(command restoreDisplay 'Redraws the screen')
  		(command showAllObjectNames 'show names beneath all the objects currently in my interior, except for those for which showing such names is inappropriate.')
  		(command hideAllObjectNames 'stop showing names beneath all the objects of my interior,  If any of them is marked to "always show name", remove that designation')))!

Item was changed:
  ----- Method: Preferences class>>openNewPreferencesPanel (in category '*Etoys-Squeakland-preferences panel') -----
  openNewPreferencesPanel
  	"Create and open a new Preferences Panel"
  
  	| window |
  	window := self preferencesControlPanel.
  	self currentWorld addMorphFront: window.
  	window center: self currentWorld center.
+ 	window beKeyWindow.
- 	window activateAndForceLabelToShow.
  
  "Preferences openNewPreferencesPanel"!

Item was removed:
- ----- Method: Preferences class>>windowColorHelp (in category '*Etoys-Squeakland-window colors') -----
- windowColorHelp
- 	"Provide help for the window-color panel"
- 
- 	| helpString |
- 	helpString := 
- 'The "Window Colors" panel lets you select colors for many kinds of standard Squeak windows.
- 
- You can change your color preference for any particular tool by clicking on the color swatch and then selecting the desired color from the resulting color-picker.
- 
- The three buttons entitled "Bright", "Pastel", and "White" let you revert to any of three different standard color schemes.  
- 
- The choices you make in the Window Colors panel only affect the colors of new windows that you open.
- 
- You can make other tools have their colors governed by this panel by simply implementing #windowColorSpecification on the class side of the model -- consult implementors of that method to see examples of how to do this.'.
- 
- 	 (StringHolder new contents: helpString)
- 		openLabel: 'About Window Colors' translated
- 
- 	"Preferences windowColorHelp"!

Item was removed:
- ----- Method: Preferences class>>windowSpecificationPanel (in category '*Etoys-Squeakland-window colors') -----
- windowSpecificationPanel
- 	"Put up a panel for specifying window colors"
- 
- 	"Preferences windowSpecificationPanel"
- 	| aPanel buttonRow aButton aRow aSwatch aColor aWindow aMiniWorld aStringMorph |
- 	aPanel := AlignmentMorph newColumn hResizing: #shrinkWrap; vResizing: #shrinkWrap;
- 		layoutInset: 0.
- 
- 	aPanel addMorph: (buttonRow := AlignmentMorph newRow color: (aColor := Color tan lighter)).
- 	
- 	buttonRow addTransparentSpacerOfSize: 2 at 0.
- 	buttonRow addMorphBack: (SimpleButtonMorph new label: '?'; target: self; actionSelector: #windowColorHelp; setBalloonText: 'Click for an explanation of this panel' translated; color: Color veryVeryLightGray; yourself).
- 	buttonRow addTransparentSpacerOfSize: 8 at 0.
- 	#(	('Bright' 	installBrightWindowColors	yellow
- 					'Use standard bright colors for all windows.')
- 		('Pastel'		installPastelWindowColors	paleMagenta
- 					'Use standard pastel colors for all windows.')
- 		('White'	installUniformWindowColors		white
- 					'Use white backgrounds for all standard windows.')) translatedNoop do:
- 
- 		[:quad |
- 			aButton := (SimpleButtonMorph new target: self)
- 				label: quad first translated;
- 				actionSelector: quad second;
- 				color: (Color colorFrom: quad third);
- 				setBalloonText: quad fourth translated;
- 				yourself.
- 			buttonRow addMorphBack: aButton.
- 			buttonRow addTransparentSpacerOfSize: 10 at 0].
- 
- 	self windowColorTable do:
- 		[:colorSpec | 
- 			aRow := AlignmentMorph newRow color: aColor.
- 			aSwatch := ColorSwatch new
- 				target: self;
- 				getSelector: #windowColorFor:;
- 				putSelector: #setWindowColorFor:to:;
- 				argument: colorSpec classSymbol;
- 				extent: (40 @ 20);
- 				setBalloonText: ('Click here to change the standard color to be used for {1} windows.' format: {colorSpec wording translated});
- 				yourself.
- 			aRow addMorphFront: aSwatch.
- 			aRow addTransparentSpacerOfSize: (12 @ 1).
- 			aRow addMorphBack: (aStringMorph := StringMorph contents: colorSpec wording translated font: TextStyle defaultFont).
- 			aStringMorph setBalloonText: colorSpec helpMessage translated.
- 			aPanel addMorphBack: aRow].
- 
- 	 Smalltalk isMorphic
-                 ifTrue:
-                         [aWindow := aPanel wrappedInWindowWithTitle: 'Window Colors' translated.
- 					" don't allow the window to be picked up by clicking inside "
- 					aPanel on: #mouseDown send: #yourself to: aPanel.
- 					self currentWorld addMorphCentered: aWindow.
- 					aWindow activateAndForceLabelToShow ]
-                 ifFalse:
-                         [(aMiniWorld := MVCWiWPasteUpMorph newWorldForProject: nil)
- 						addMorph: aPanel.
-                            aMiniWorld startSteppingSubmorphsOf: aPanel.
-                         MorphWorldView openOn: aMiniWorld
-                                 label: 'Window Colors' translated
-                                 extent: aMiniWorld fullBounds extent]!

Item was removed:
- ----- Method: SMSqueakMap>>windowColorToUse (in category '*Etoys-Squeakland-model access') -----
- windowColorToUse
- 
- 	^ self userInterfaceTheme uniformWindowColor ifNil: [Color veryVeryLightGray]!

Item was changed:
  ----- Method: SoundLibraryTool>>listing (in category 'initialization') -----
  listing
  	| list newList format soundData selectorList formatList |
  	list := SampledSound soundLibrary keys sort.
  	selectorList := OrderedCollection new.
  	formatList := OrderedCollection new.
  	list
  		do: [:each | 
  			soundData := (SampledSound soundLibrary at: each) second.
  			soundData isNumber
  				ifTrue: [format := 'uncompressed']
  				ifFalse: [(soundData includesSubString: 'Vorbis')
  						ifTrue: [format := 'Vorbis']
  						ifFalse: [(soundData includesSubString: 'Speex')
  								ifTrue: [format := 'Speex']
+ 								ifFalse: [(soundData includesSubstring: 'GSM')
- 								ifFalse: [(soundData includesSubString: 'GSM')
  										ifTrue: [format := 'GSM']]]].
  			selectorList add: each.
  			formatList add:  format].
  	 newList := OrderedCollection new.
  	newList add: selectorList asArray.
  	showCompression
  		ifTrue:[newList add: formatList asArray]
  		ifFalse:[newList add:  (Array new: (formatList size) withAll:' ')].
  	^newList!

Item was changed:
  ----- Method: UserText>>drawOn: (in category 'drawing') -----
  drawOn: aCanvas
  	"Render the receiver on the given canvas."
  
  	super drawOn: aCanvas.
  	aCanvas isShadowDrawing
  		ifTrue: [^ self].
  	self hasFocus
  		ifTrue: [aCanvas
  				frameRectangle: (self fullBounds insetBy: 0)
+ 				color: self keyboardFocusColor]!
- 				color: Preferences keyboardFocusColor]!

Item was changed:
  ----- Method: Viewer class>>innerBorderColor (in category '*Etoys-Squeakland-constants') -----
  innerBorderColor
+ 	^ (UserInterfaceTheme current get: #titleBorderColor for: self) ifNil: [(Color r: 0.6 g: 0.7 b: 1)]!
- 	^ Preferences menuTitleBorderColor!



More information about the Squeak-dev mailing list