The Trunk: EToys-mt.383.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: EToys-mt.383.mcz

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

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

Name: EToys-mt.383
Author: mt
Time: 4 March 2020, 5:02:24.289827 pm
UUID: 65cbaa81-5887-b542-bbce-bbe45e41ed84
Ancestors: EToys-mt.382

Removes more deprecated message sends.

=============== Diff against EToys-mt.382 ===============

Item was changed:
  ----- Method: CategoryViewer>>showCategoriesFor: (in category 'categories') -----
  showCategoriesFor: aSymbol
  "Put up a pop-up list of categories in which aSymbol is filed; replace the receiver with a CategoryViewer for the one the user selects, if any"
 
  | allCategories aVocabulary hits meths chosen aMenu aCaption symbolToReport |
  aVocabulary := self currentVocabulary.
  allCategories := scriptedPlayer categoriesForVocabulary: aVocabulary limitClass: ProtoObject.
 
  hits := allCategories select:
  [:aCategory |
  meths := aVocabulary allMethodsInCategory: aCategory forInstance: scriptedPlayer ofClass: scriptedPlayer class.
  meths includes: aSymbol].
 
  hits isEmpty ifTrue: [^ self inform: 'this tile is not actually suitable for use with this kind of object' translated].
 
+ symbolToReport := (aSymbol beginsWith: 'get') ifTrue: [aSymbol inherentSelector] ifFalse: [aSymbol].
- symbolToReport := (aSymbol beginsWith: 'get') ifTrue: [Utilities inherentSelectorForGetter: aSymbol] ifFalse: [aSymbol].
 
  aMenu := SelectionMenu selections: hits.
  aCaption := hits size = 1
  ifTrue:
  ['is in the following category' translated]
  ifFalse:
  ['can be found in the following categories' translated].
 
  chosen := aMenu startUpWithCaption:  symbolToReport, ' ', aCaption.
  chosen isEmptyOrNil ifFalse:
  [self outerViewer addCategoryViewerFor: chosen atEnd: true]
 
  !

Item was changed:
  ----- Method: DialectParser>>parseArgsAndTemps:notifying: (in category 'as yet unclassified') -----
  parseArgsAndTemps: aString notifying: req
  "Parse the argument, aString, notifying req if an error occurs. Otherwise,
  answer a two-element Array containing Arrays of strings (the argument
  names and temporary variable names)."
 
  aString == nil ifTrue: [^#()].
  doitFlag := false. "Don't really know if a doit or not!!"
  ^self initPattern: aString
- notifying: req
  return: [:pattern | (pattern at: 2) , self temporaries]!

Item was changed:
  ----- Method: KedamaExamplerPlayer>>userDefinedSlotGetters (in category '*Etoys-Squeakland-private') -----
  userDefinedSlotGetters
 
+ ^ turtles info keys asArray collect: [:e | e asGetterSelector].
- ^ turtles info keys asArray collect: [:e | Utilities getterSelectorFor: e].
  !

Item was changed:
  ----- Method: KedamaExamplerPlayer>>userDefinedSlotSetters (in category '*Etoys-Squeakland-private') -----
  userDefinedSlotSetters
 
+ ^ turtles info keys asArray collect: [:e | e asSetterSelector].
- ^ turtles info keys asArray collect: [:e | Utilities setterSelectorFor: e].
  !

Item was changed:
  ----- Method: KedamaSequenceExecutionStub>>removeSlotNamed: (in category 'method management') -----
  removeSlotNamed: aSlotName
 
+ self class removeSelectorSilently: aSlotName asGetterSelector.
+ self class removeSelectorSilently: aSlotName asSetterSelector.
- self class removeSelectorSilently: (Utilities getterSelectorFor: aSlotName).
- self class removeSelectorSilently: (Utilities setterSelectorFor: aSlotName).
  self compileAllAccessors.
  !

Item was changed:
  ----- Method: KedamaTurtleVectorPlayer2>>removeVectorSlotNamed: (in category 'player protocol') -----
  removeVectorSlotNamed: aSlotName
 
  | index newArrays |
  index := info at: aSlotName asSymbol ifAbsent: [^ self].
  newArrays := (arrays copyFrom: 1 to: index - 1), (arrays copyFrom: index + 1 to: arrays size).
  types replaceFrom: index to: types size - 1 with: types startingAt: index + 1.
 
  info removeKey: aSlotName asSymbol.
  info associationsDo: [:assoc | assoc value > index ifTrue: [info at: assoc key put: assoc value - 1]].
  arrays := newArrays.
+ self class removeSelectorSilently: aSlotName asGetterSelector.
+ self class removeSelectorSilently: aSlotName asSetterSelector.
- self class removeSelectorSilently: (Utilities getterSelectorFor: aSlotName).
- self class removeSelectorSilently: (Utilities setterSelectorFor: aSlotName).
  self compileAllAccessors.
  !

Item was changed:
  ----- Method: Parser>>parseArgsAndTemps:notifying: (in category '*Etoys-Squeakland-public access') -----
  parseArgsAndTemps: aString notifying: req
          "Parse the argument, aString, notifying req if an error occurs. Otherwise,
          answer a two-element Array containing Arrays of strings (the argument
          names and temporary variable names)."
 
          (req notNil and: [RequestAlternateSyntaxSetting signal]) ifTrue:
                  [^ (self as: DialectParser) parseArgsAndTemps: aString notifying: req].
          aString == nil ifTrue: [^#()].
          doitFlag := false.               "Don't really know if a doit or not!!"
          ^self initPattern: aString
-                 notifying: req
                  return: [:pattern | (pattern at: 2) , (self temporariesIn: (pattern at: 1))]!

Item was changed:
  ----- Method: PhraseTileMorph>>updatingOperatorNodeWith: (in category '*Etoys-Squeakland-code generation') -----
  updatingOperatorNodeWith: encoder
 
  | sel rec args |
+ sel := submorphs second assignmentRoot asGetterSelector.
- sel := Utilities getterSelectorFor: submorphs second assignmentRoot.
  rec := submorphs first parseNodeWith: encoder.
  args := WriteStream on: (Array new: 3).
 
  ((submorphs second isMemberOf: TileCommandWithArgumentMorph)
  or: [(submorphs second isMemberOf: KedamaSetColorComponentTile)
  or: [submorphs second isMemberOf: KedamaSetPixelValueTile]]) ifTrue: [
  args nextPut: (submorphs second parseNodeWith: encoder).
  ].
 
  ^ MessageNode new
  receiver: rec
  selector: sel
  arguments: args contents
  precedence: (sel precedence)
  from: encoder
  sourceRange: nil.
  !

Item was changed:
  ----- Method: Player>>getPageCount (in category '*Etoys-Squeakland-playing commands') -----
  getPageCount
 
  | b |
+ b := ScrapBook default scrapBook renderedMorph.
- b := Utilities scrapsBook renderedMorph.
  ^ b ifNotNil: [b pages size] ifNil: [1].
  !

Item was changed:
  ----- Method: Player>>getPrecisionFor: (in category '*Etoys-Squeakland-slots-user') -----
  getPrecisionFor: slotName
  "get the precision for the given slot name"
 
  | aGetter places precision |
  precision := 1.
  (self slotInfo includesKey: slotName)
  ifTrue:
  ["it's a user slot"
  precision := (self slotInfoAt: slotName) floatPrecision]
  ifFalse:
  ["reference to system slots"
+ aGetter := slotName asGetterSelector.
- aGetter := Utilities getterSelectorFor: slotName.
  self costume renderedMorph ifNotNil: [ :morph |
  places := morph decimalPlacesForGetter: aGetter.
  precision := Utilities floatPrecisionForDecimalPlaces: places ]].
  ^precision!

Item was changed:
  ----- Method: Player>>removeWatchersOfSlotNamed: (in category '*Etoys-Squeakland-translation') -----
  removeWatchersOfSlotNamed: aName
  "A variable has been removed.  Deal with possible watchers."
 
  | aGetter |
+ aGetter := aName asGetterSelector.
- aGetter := Utilities getterSelectorFor: aName.
  self allPossibleWatchersFromWorld do: [:aWatcher |
  (aWatcher getSelector = aGetter) ifTrue:
  [aWatcher stopStepping.
  (aWatcher ownerThatIsA: WatcherWrapper) ifNotNil:
  [:aWrapper | aWrapper delete]]]!

Item was changed:
  ----- Method: Player>>setPrecisionFor:precision: (in category '*Etoys-Squeakland-slots-user') -----
  setPrecisionFor: slotName precision: aNumber
  | val |
  (self slotInfo includesKey: slotName)
  ifTrue:
  ["it's a user slot"
 
  (self slotInfoAt: slotName)
  floatPrecision: (Utilities floatPrecisionForDecimalPlaces: aNumber).
  self class allInstancesDo:
  [:anInst |
  aNumber == 0
  ifFalse:
  [((val := anInst instVarNamed: slotName asString) isInteger)
  ifTrue: [anInst instVarNamed: slotName asString put: val asFloat]].
  anInst updateAllViewers]]
  ifFalse:
  ["it's specifying a preference for precision on a system-defined numeric slot"
 
+ self noteDecimalPlaces: aNumber forGetter: slotName asGetterSelector.
- self noteDecimalPlaces: aNumber forGetter: (Utilities getterSelectorFor: slotName).
  self updateAllViewers]!

Item was changed:
  ----- Method: Utilities class>>emptyScrapsBookGC (in category '*Etoys-Squeakland-scraps') -----
  emptyScrapsBookGC
  "Get rid of trashed siblings so they won't appear in allSiblingsDo:"
  "Utilities emptyScrapsBookGC"
 
  | doGC |
  doGC := (ScrapsBook ifNotNil: [ScrapsBook pages size > 1]) ~~ false.
+ ScrapBook default emptyScrapBook.
- self emptyScrapsBook.
  doGC ifTrue: [Smalltalk garbageCollect].!

Item was changed:
  ----- Method: WatcherWrapper>>getter (in category '*Etoys-Squeakland-accessing') -----
  getter
  "Answer the selector that serves as the getter for this watcher."
 
+ ^  self valueOfProperty: #getter ifAbsent: [variableName asGetterSelector]!
- ^  self valueOfProperty: #getter ifAbsent: [Utilities getterSelectorFor: variableName]!