The Trunk: EToys-mt.368.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
21 messages Options
12
Reply | Threaded
Open this post in threaded view
|

The Trunk: EToys-mt.368.mcz

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

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+ "Answer the receiver, scaled such that it has the desired width."
+
+ newWidth = self width ifTrue: [^ self].
+ ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+ self helpText editWithLabel: 'FreeCell Help'.!
- | window helpMorph |
- window := SystemWindow labelled: 'FreeCell Help' translated.
- window model: self.
- helpMorph := (PluggableTextMorph new editString: self helpText) lock.
- window
- addMorph: helpMorph
- frame: (0 @ 0 extent: 1 @ 1).
- window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+ super color: aColor.
+
+ "Migrate old instances."
+ inner color: Color transparent.
+
+ "Keep iris visible."
+ aColor = iris color
+ ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+ ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
  "initialize the state of the receiver"
  super initialize.
  ""
  inner := EllipseMorph new.
+ inner color: Color transparent.
- inner color: self color.
  inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
- inner borderColor: self color.
  inner borderWidth: 0.
  ""
  iris := EllipseMorph new.
  iris color: Color white.
  iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
  self addMorphCentered: inner.
  inner addMorphCentered: iris.
  ""
  self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+ ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+ iris color: aColor.
+
+ "Keep iris visible."
+ aColor = self color
+ ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+ ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+ ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
  | a b theta x y |
  theta := (cp - self center) theta.
  a := inner width // 2.
  b := inner height // 2.
  x := a * (theta cos).
  y := b * (theta sin).
  iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
  | cp |
  cp := self globalPointToLocal: self world primaryHand position.
  (inner containsPoint: cp)
  ifTrue: [iris position: (cp - (iris extent // 2))]
+ ifFalse: [self irisPos: cp].!
- ifFalse: [self irisPos: cp].
- self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
  ^ decimalPlacesButton
  ifNil: [Utilities
  decimalPlacesForFloatPrecision: (self targetPlayer
+ defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
- defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
  ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
  "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
  | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
  aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
  aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
  Preferences universalTiles ifTrue: [
  aScriptEditor install.
  "aScriptEditor hResizing: #shrinkWrap;
  vResizing: #shrinkWrap;
  cellPositioning: #topLeft;
  setProperty: #autoFitContents toValue: true."
  aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+ tw := aScriptEditor findA: ScrollPane.
- tw := aScriptEditor findA: TwoWayScrollPane.
  aPhrase ifNotNil:
  [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
  blk addMorphFront: aPhrase.
  aPhrase accept.
  ].
  SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
  ] ifFalse: [
  aPhrase
  ifNotNil: [aScriptEditor phrase: aPhrase] "does an install"
  ifNil: [aScriptEditor install]
  ].
  self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
  "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
  self updateScriptsCategoryOfViewers.
  ].
  ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
  "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
  | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
  aPasteUpMorph removeAllMorphs.
 
  aFont := Preferences standardListFont.
+ aColor := aPanel windowColorToUse.
- aColor := aPanel defaultBackgroundColor.
  tabbedPalette := TabbedPalette newSticky.
  tabbedPalette dropEnabled: false.
  (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
  highlightColor: Color red regularColor: Color brown darker darker.
  tabbedPalette on: #mouseDown send: #yourself to: #().
  maxEntriesPerCategory := 0.
  self listOfCategories do:
  [:aCat |
  controlPage := AlignmentMorph newColumn beSticky color: aColor.
  controlPage on: #mouseDown send: #yourself to: #().
  controlPage dropEnabled: false.
  controlPage borderColor: aColor;
  layoutInset: 4.
  (prefObjects := self preferenceObjectsInCategory: aCat) do:
  [:aPreference | | button |
  button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
  button ifNotNil: [controlPage addMorphBack: button]].
  controlPage setNameTo: aCat asString.
  aCat = #?
  ifTrue: [aPanel addHelpItemsTo: controlPage].
  tabbedPalette addTabFor: controlPage font: aFont.
  aCat = 'search results' ifTrue:
  [(tabbedPalette tabNamed: aCat) setBalloonText:
  'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
  maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
  tabbedPalette selectTabNamed: '?'.
  tabsMorph rowsNoWiderThan: aPasteUpMorph width.
  aPasteUpMorph on: #mouseDown send: #yourself to: #().
  anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
  aPasteUpMorph extent: anExtent.
  aPasteUpMorph color: aColor.
  aPasteUpMorph addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
  "Toggle between auto fit to size of code and manual resize with scrolling"
  | tw |
+ (tw := self findA: ScrollPane) ifNil: [^ self].
- (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
  (self hasProperty: #autoFitContents)
  ifTrue: [self removeProperty: #autoFitContents.
  self hResizing: #rigid; vResizing: #rigid]
  ifFalse: [self setProperty: #autoFitContents toValue: true.
  self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
  tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
  | newExtent tw menu |
  newExtent := x max: self minWidth @ self minHeight.
+ (tw := self findA: ScrollPane) ifNil:
- (tw := self findA: TwoWayScrollPane) ifNil:
  ["This was the old behavior"
  ^ super extent: newExtent].
 
  (self hasProperty: #autoFitContents) ifTrue: [
  menu := MenuMorph new defaultTarget: self.
  menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
  menu addTitle: 'To resize the script, uncheck the box below' translated.
  menu popUpEvent: nil in: self world .
  ^ self].
 
  "Allow the user to resize to any size"
  tw extent: ((newExtent x max: self firstSubmorph width)
  @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
  ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
  "Possibly delete the tiles, but only if using universal tiles."
 
  | tw |
  Preferences universalTiles ifFalse: [^self].
+ (tw := self findA: ScrollPane) isNil
- (tw := self findA: TwoWayScrollPane) isNil
  ifFalse:
  [self setProperty: #sizeAtHibernate toValue: self extent. "+ tw xScrollerHeight"
  submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+ | on |
+ on := soundInput isRecording.
+ self stop.
+ fft := FFT new: aSize.
+ self resetDisplay.
+ on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
  "Set the size of the FFT used for frequency analysis."
 
+ | aMenu sz |
- | aMenu sz on |
  aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
  ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
  sz := aMenu startUp.
  sz ifNil: [^ self].
+ self fftSize: sz.!
- on := soundInput isRecording.
- self stop.
- fft := FFT new: sz.
- self resetDisplay.
- on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
  | tw |
+ (tw := outerMorph findA: ScrollPane) ifNil: [^self].
- (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
  tw hResizing: #spaceFill;
  vResizing: #spaceFill;
  color: Color transparent;
  setProperty: #hideUnneededScrollbars toValue: true.
  outerMorph
  hResizing: #shrinkWrap;
  vResizing: #shrinkWrap;
  cellPositioning: #topLeft.
  outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
  "The object that owns this script layout"
 
  | oo higher |
  oo := self owner.
  [higher := oo isSyntaxMorph.
  higher := higher or: [oo class == TransformMorph].
+ higher := higher or: [oo class == ScrollPane].
- higher := higher or: [oo class == TwoWayScrollPane].
  higher ifFalse: [^ oo].
  higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
- "Answer a scroll pane in which the receiver is scrollable"
-
- ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+ | sel |
- | window widget sel |
  sel := ''.
  self firstSubmorph allMorphs do: [:rr |
+ (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
- (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
- window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
- widget := self inAScrollPane.
- widget color: Color paleOrange.
- window
- addMorph: widget
- frame: (0@0 extent: 1.0@1.0).
- window openInWorldExtent: (
- self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
- )
 
+ ^ self inAScrollPane
+ color: Color paleOrange;
+ openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+ ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
  self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+ (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+ ifFalse: [self borderColor: self stdBorderColor]
+ ifTrue: [
+ (self hasProperty: #deselectedBorderColor)
+ ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+ ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
- self borderColor: (
- (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
- ifFalse: [self borderColor: self stdBorderColor]
- ifTrue: [
- (self hasProperty: #deselectedBorderColor)
- ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
- ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
  "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
  | pad newPad functionPhrase |
  pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
  (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
  newPad := TilePadMorph new setType: #Number.
+ newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
- newPad hResizing: #shrinkWrap; vResizing: #spacefill.
  functionPhrase := FunctionTile new.
  newPad addMorphBack: functionPhrase.
  pad owner replaceSubmorph: pad by: newPad.
  functionPhrase operator: #abs pad: pad.
  functionPhrase addSuffixArrow.
  self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
  "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
  | newPad functionPhrase |
  newPad := TilePadMorph new setType: #Number.
+ newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
- newPad hResizing: #shrinkWrap; vResizing: #spacefill.
  functionPhrase := FunctionTile new.
  newPad addMorphBack: functionPhrase.
  owner replaceSubmorph: self by: newPad.
  functionPhrase operator: #abs pad: self.
  self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
  ^ parent addToken: self name
  type: #variable
+ on: self shallowCopy "don't hand out the prototype!! See VariableNode>>initialize"
- on: self clone "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
  ^ self new
  fontName: aString;
  color: aColor;
  centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
  "WorldWindow test2."
 
  | window world scrollPane |
  world := WiWPasteUpMorph newWorldForProject: nil.
  window := (WorldWindow labelled: 'Scrollable World') model: world.
+ window addMorph: (scrollPane := ScrollPane new model: world)
- window addMorph: (scrollPane := TwoWayScrollPane new model: world)
  frame: (0@0 extent: 1.0@1.0).
  scrollPane scroller addMorph: world.
  world hostWindow: window.
  window openInWorld
  !


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Christoph Thiede

Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?


Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
Gesendet: Mittwoch, 13. November 2019 12:15:14
An: [hidden email]; [hidden email]
Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
 
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.368.mcz

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+        "Answer the receiver, scaled such that it has the desired width."
+
+        newWidth = self width ifTrue: [^ self].
+        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+        self helpText editWithLabel: 'FreeCell Help'.!
-        | window helpMorph |
-        window := SystemWindow labelled: 'FreeCell Help' translated.
-        window model: self.
-        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
-        window
-                addMorph: helpMorph
-                frame: (0 @ 0 extent: 1 @ 1).
-        window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+        super color: aColor.
+       
+        "Migrate old instances."
+        inner color: Color transparent.
+       
+        "Keep iris visible."
+        aColor = iris color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
         "initialize the state of the receiver"
         super initialize.
         ""
         inner := EllipseMorph new.
+        inner color: Color transparent.
-        inner color: self color.
         inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
-        inner borderColor: self color.
         inner borderWidth: 0.
  ""
         iris := EllipseMorph new.
         iris color: Color white.
         iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
         self addMorphCentered: inner.
         inner addMorphCentered: iris.
  ""
         self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+        ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+        iris color: aColor.
+       
+        "Keep iris visible."
+        aColor = self color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+        ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
         | a b theta x y |
         theta := (cp - self center) theta.
         a := inner width // 2.
         b := inner height // 2.
         x := a * (theta cos).
         y := b * (theta sin).
         iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
         | cp |
         cp := self globalPointToLocal: self world primaryHand position.
         (inner containsPoint: cp)
                 ifTrue: [iris position: (cp - (iris extent // 2))]
+                ifFalse: [self irisPos: cp].!
-                ifFalse: [self irisPos: cp].
-        self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
         ^ decimalPlacesButton
                 ifNil: [Utilities
                                 decimalPlacesForFloatPrecision: (self targetPlayer
+                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
-                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
                 ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
         "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
         | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
         aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
         aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
         Preferences universalTiles ifTrue: [
                 aScriptEditor install.
                 "aScriptEditor hResizing: #shrinkWrap;
                         vResizing: #shrinkWrap;
                         cellPositioning: #topLeft;
                         setProperty: #autoFitContents toValue: true."
                 aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+                tw := aScriptEditor findA: ScrollPane.
-                tw := aScriptEditor findA: TwoWayScrollPane.
                 aPhrase ifNotNil:
                         [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
                         blk addMorphFront: aPhrase.
                         aPhrase accept.
                 ].
                 SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
         ] ifFalse: [
                 aPhrase
                                 ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
                                 ifNil: [aScriptEditor install]
         ].
         self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
                 "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
         self updateScriptsCategoryOfViewers.
  ].
         ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
         "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
         | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
         aPasteUpMorph removeAllMorphs.
 
         aFont := Preferences standardListFont.
+        aColor := aPanel windowColorToUse.
-        aColor := aPanel defaultBackgroundColor.
         tabbedPalette := TabbedPalette newSticky.
         tabbedPalette dropEnabled: false.
         (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
                  highlightColor: Color red regularColor: Color brown darker darker.
         tabbedPalette on: #mouseDown send: #yourself to: #().
         maxEntriesPerCategory := 0.
         self listOfCategories do:
                 [:aCat |
                         controlPage := AlignmentMorph newColumn beSticky color: aColor.
                         controlPage on: #mouseDown send: #yourself to: #().
                         controlPage dropEnabled: false.
                         controlPage borderColor: aColor;
                                  layoutInset: 4.
                         (prefObjects := self preferenceObjectsInCategory: aCat) do:
                                 [:aPreference | | button |
                                         button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
                                         button ifNotNil: [controlPage addMorphBack: button]].
                         controlPage setNameTo: aCat asString.
                         aCat = #?
                                 ifTrue: [aPanel addHelpItemsTo: controlPage].
                         tabbedPalette addTabFor: controlPage font: aFont.
                         aCat = 'search results' ifTrue:
                                 [(tabbedPalette tabNamed: aCat) setBalloonText:
                                         'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
                 maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
         tabbedPalette selectTabNamed: '?'.
         tabsMorph rowsNoWiderThan: aPasteUpMorph width.
         aPasteUpMorph on: #mouseDown send: #yourself to: #().
         anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
         aPasteUpMorph extent: anExtent.
         aPasteUpMorph color: aColor.
         aPasteUpMorph     addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
         "Toggle between auto fit to size of code and manual resize with scrolling"
         | tw |
+        (tw := self findA: ScrollPane) ifNil: [^ self].
-        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
         (self hasProperty: #autoFitContents)
                 ifTrue: [self removeProperty: #autoFitContents.
                         self hResizing: #rigid; vResizing: #rigid]
                 ifFalse: [self setProperty: #autoFitContents toValue: true.
                         self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
         tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
         | newExtent tw menu |
         newExtent := x max: self minWidth @ self minHeight.
+        (tw := self findA: ScrollPane) ifNil:
-        (tw := self findA: TwoWayScrollPane) ifNil:
                 ["This was the old behavior"
                 ^ super extent: newExtent].
 
         (self hasProperty: #autoFitContents) ifTrue: [
                 menu := MenuMorph new defaultTarget: self.
                 menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
                 menu addTitle: 'To resize the script, uncheck the box below' translated.
                 menu popUpEvent: nil in: self world     .
                 ^ self].
 
         "Allow the user to resize to any size"
         tw extent: ((newExtent x max: self firstSubmorph width)
                                 @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
         ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
         "Possibly delete the tiles, but only if using universal tiles."
 
         | tw |
         Preferences universalTiles ifFalse: [^self].
+        (tw := self findA: ScrollPane) isNil
-        (tw := self findA: TwoWayScrollPane) isNil
                 ifFalse:
                         [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
                         submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+        | on |
+        on := soundInput isRecording.
+        self stop.
+        fft := FFT new: aSize.
+        self resetDisplay.
+        on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
         "Set the size of the FFT used for frequency analysis."
 
+        | aMenu sz |
-        | aMenu sz on |
         aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
         ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
         sz := aMenu startUp.
         sz ifNil: [^ self].
+        self fftSize: sz.!
-        on := soundInput isRecording.
-        self stop.
-        fft := FFT new: sz.
-        self resetDisplay.
-        on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
         | tw |
+        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
-        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
         tw hResizing: #spaceFill;
                 vResizing: #spaceFill;
                 color: Color transparent;
                 setProperty: #hideUnneededScrollbars toValue: true.
         outerMorph
                 hResizing: #shrinkWrap;
                 vResizing: #shrinkWrap;
                 cellPositioning: #topLeft.
         outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
         "The object that owns this script layout"
 
         | oo higher |
         oo := self owner.
         [higher := oo isSyntaxMorph.
         higher := higher or: [oo class == TransformMorph].
+        higher := higher or: [oo class == ScrollPane].
-        higher := higher or: [oo class == TwoWayScrollPane].
         higher ifFalse: [^ oo].
         higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
-        "Answer a scroll pane in which the receiver is scrollable"
-
-        ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+        | sel |
-        | window widget sel |
         sel := ''.
         self firstSubmorph allMorphs do: [:rr |
+                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
-        widget := self inAScrollPane.
-        widget color: Color paleOrange.
-        window
-                addMorph: widget
-                frame: (0@0 extent: 1.0@1.0).
-        window openInWorldExtent: (
-                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
-        )
 
+        ^ self inAScrollPane
+                color: Color paleOrange;
+                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+        ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
         self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+                        ifFalse: [self borderColor: self stdBorderColor]
+                        ifTrue: [
+                                (self hasProperty: #deselectedBorderColor)
+                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
-                self borderColor: (
-                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
-                                ifFalse: [self borderColor: self stdBorderColor]
-                                ifTrue: [
-                                        (self hasProperty: #deselectedBorderColor)
-                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
-                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
         "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
         | pad newPad functionPhrase |
         pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
         (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         pad owner replaceSubmorph: pad by: newPad.
         functionPhrase operator: #abs pad: pad.
         functionPhrase addSuffixArrow.
         self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
         "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
         | newPad functionPhrase |
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         owner replaceSubmorph: self by: newPad.
         functionPhrase operator: #abs pad: self.
         self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
         ^ parent addToken: self name
                         type: #variable
+                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
-                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
         ^ self new
                 fontName: aString;
                 color: aColor;
                 centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
         "WorldWindow test2."
 
         | window world scrollPane |
         world := WiWPasteUpMorph newWorldForProject: nil.
         window := (WorldWindow labelled: 'Scrollable World') model: world.
+        window addMorph: (scrollPane := ScrollPane new model: world)
-        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
                 frame: (0@0 extent: 1.0@1.0).
         scrollPane scroller addMorph: world.
         world hostWindow: window.
         window openInWorld
  !




Carpe Squeak!
Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

marcel.taeumel
Hi Christoph,

I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.

Best,
Marcel

Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:

Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?


Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
Gesendet: Mittwoch, 13. November 2019 12:15:14
An: [hidden email]; [hidden email]
Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
 
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.368.mcz

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+        "Answer the receiver, scaled such that it has the desired width."
+
+        newWidth = self width ifTrue: [^ self].
+        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+        self helpText editWithLabel: 'FreeCell Help'.!
-        | window helpMorph |
-        window := SystemWindow labelled: 'FreeCell Help' translated.
-        window model: self.
-        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
-        window
-                addMorph: helpMorph
-                frame: (0 @ 0 extent: 1 @ 1).
-        window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+        super color: aColor.
+       
+        "Migrate old instances."
+        inner color: Color transparent.
+       
+        "Keep iris visible."
+        aColor = iris color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
         "initialize the state of the receiver"
         super initialize.
         ""
         inner := EllipseMorph new.
+        inner color: Color transparent.
-        inner color: self color.
         inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
-        inner borderColor: self color.
         inner borderWidth: 0.
  ""
         iris := EllipseMorph new.
         iris color: Color white.
         iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
         self addMorphCentered: inner.
         inner addMorphCentered: iris.
  ""
         self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+        ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+        iris color: aColor.
+       
+        "Keep iris visible."
+        aColor = self color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+        ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
         | a b theta x y |
         theta := (cp - self center) theta.
         a := inner width // 2.
         b := inner height // 2.
         x := a * (theta cos).
         y := b * (theta sin).
         iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
         | cp |
         cp := self globalPointToLocal: self world primaryHand position.
         (inner containsPoint: cp)
                 ifTrue: [iris position: (cp - (iris extent // 2))]
+                ifFalse: [self irisPos: cp].!
-                ifFalse: [self irisPos: cp].
-        self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
         ^ decimalPlacesButton
                 ifNil: [Utilities
                                 decimalPlacesForFloatPrecision: (self targetPlayer
+                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
-                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
                 ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
         "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
         | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
         aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
         aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
         Preferences universalTiles ifTrue: [
                 aScriptEditor install.
                 "aScriptEditor hResizing: #shrinkWrap;
                         vResizing: #shrinkWrap;
                         cellPositioning: #topLeft;
                         setProperty: #autoFitContents toValue: true."
                 aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+                tw := aScriptEditor findA: ScrollPane.
-                tw := aScriptEditor findA: TwoWayScrollPane.
                 aPhrase ifNotNil:
                         [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
                         blk addMorphFront: aPhrase.
                         aPhrase accept.
                 ].
                 SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
         ] ifFalse: [
                 aPhrase
                                 ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
                                 ifNil: [aScriptEditor install]
         ].
         self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
                 "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
         self updateScriptsCategoryOfViewers.
  ].
         ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
         "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
         | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
         aPasteUpMorph removeAllMorphs.
 
         aFont := Preferences standardListFont.
+        aColor := aPanel windowColorToUse.
-        aColor := aPanel defaultBackgroundColor.
         tabbedPalette := TabbedPalette newSticky.
         tabbedPalette dropEnabled: false.
         (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
                  highlightColor: Color red regularColor: Color brown darker darker.
         tabbedPalette on: #mouseDown send: #yourself to: #().
         maxEntriesPerCategory := 0.
         self listOfCategories do:
                 [:aCat |
                         controlPage := AlignmentMorph newColumn beSticky color: aColor.
                         controlPage on: #mouseDown send: #yourself to: #().
                         controlPage dropEnabled: false.
                         controlPage borderColor: aColor;
                                  layoutInset: 4.
                         (prefObjects := self preferenceObjectsInCategory: aCat) do:
                                 [:aPreference | | button |
                                         button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
                                         button ifNotNil: [controlPage addMorphBack: button]].
                         controlPage setNameTo: aCat asString.
                         aCat = #?
                                 ifTrue: [aPanel addHelpItemsTo: controlPage].
                         tabbedPalette addTabFor: controlPage font: aFont.
                         aCat = 'search results' ifTrue:
                                 [(tabbedPalette tabNamed: aCat) setBalloonText:
                                         'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
                 maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
         tabbedPalette selectTabNamed: '?'.
         tabsMorph rowsNoWiderThan: aPasteUpMorph width.
         aPasteUpMorph on: #mouseDown send: #yourself to: #().
         anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
         aPasteUpMorph extent: anExtent.
         aPasteUpMorph color: aColor.
         aPasteUpMorph     addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
         "Toggle between auto fit to size of code and manual resize with scrolling"
         | tw |
+        (tw := self findA: ScrollPane) ifNil: [^ self].
-        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
         (self hasProperty: #autoFitContents)
                 ifTrue: [self removeProperty: #autoFitContents.
                         self hResizing: #rigid; vResizing: #rigid]
                 ifFalse: [self setProperty: #autoFitContents toValue: true.
                         self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
         tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
         | newExtent tw menu |
         newExtent := x max: self minWidth @ self minHeight.
+        (tw := self findA: ScrollPane) ifNil:
-        (tw := self findA: TwoWayScrollPane) ifNil:
                 ["This was the old behavior"
                 ^ super extent: newExtent].
 
         (self hasProperty: #autoFitContents) ifTrue: [
                 menu := MenuMorph new defaultTarget: self.
                 menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
                 menu addTitle: 'To resize the script, uncheck the box below' translated.
                 menu popUpEvent: nil in: self world     .
                 ^ self].
 
         "Allow the user to resize to any size"
         tw extent: ((newExtent x max: self firstSubmorph width)
                                 @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
         ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
         "Possibly delete the tiles, but only if using universal tiles."
 
         | tw |
         Preferences universalTiles ifFalse: [^self].
+        (tw := self findA: ScrollPane) isNil
-        (tw := self findA: TwoWayScrollPane) isNil
                 ifFalse:
                         [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
                         submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+        | on |
+        on := soundInput isRecording.
+        self stop.
+        fft := FFT new: aSize.
+        self resetDisplay.
+        on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
         "Set the size of the FFT used for frequency analysis."
 
+        | aMenu sz |
-        | aMenu sz on |
         aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
         ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
         sz := aMenu startUp.
         sz ifNil: [^ self].
+        self fftSize: sz.!
-        on := soundInput isRecording.
-        self stop.
-        fft := FFT new: sz.
-        self resetDisplay.
-        on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
         | tw |
+        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
-        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
         tw hResizing: #spaceFill;
                 vResizing: #spaceFill;
                 color: Color transparent;
                 setProperty: #hideUnneededScrollbars toValue: true.
         outerMorph
                 hResizing: #shrinkWrap;
                 vResizing: #shrinkWrap;
                 cellPositioning: #topLeft.
         outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
         "The object that owns this script layout"
 
         | oo higher |
         oo := self owner.
         [higher := oo isSyntaxMorph.
         higher := higher or: [oo class == TransformMorph].
+        higher := higher or: [oo class == ScrollPane].
-        higher := higher or: [oo class == TwoWayScrollPane].
         higher ifFalse: [^ oo].
         higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
-        "Answer a scroll pane in which the receiver is scrollable"
-
-        ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+        | sel |
-        | window widget sel |
         sel := ''.
         self firstSubmorph allMorphs do: [:rr |
+                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
-        widget := self inAScrollPane.
-        widget color: Color paleOrange.
-        window
-                addMorph: widget
-                frame: (0@0 extent: 1.0@1.0).
-        window openInWorldExtent: (
-                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
-        )
 
+        ^ self inAScrollPane
+                color: Color paleOrange;
+                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+        ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
         self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+                        ifFalse: [self borderColor: self stdBorderColor]
+                        ifTrue: [
+                                (self hasProperty: #deselectedBorderColor)
+                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
-                self borderColor: (
-                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
-                                ifFalse: [self borderColor: self stdBorderColor]
-                                ifTrue: [
-                                        (self hasProperty: #deselectedBorderColor)
-                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
-                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
         "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
         | pad newPad functionPhrase |
         pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
         (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         pad owner replaceSubmorph: pad by: newPad.
         functionPhrase operator: #abs pad: pad.
         functionPhrase addSuffixArrow.
         self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
         "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
         | newPad functionPhrase |
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         owner replaceSubmorph: self by: newPad.
         functionPhrase operator: #abs pad: self.
         self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
         ^ parent addToken: self name
                         type: #variable
+                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
-                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
         ^ self new
                 fontName: aString;
                 color: aColor;
                 centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
         "WorldWindow test2."
 
         | window world scrollPane |
         world := WiWPasteUpMorph newWorldForProject: nil.
         window := (WorldWindow labelled: 'Scrollable World') model: world.
+        window addMorph: (scrollPane := ScrollPane new model: world)
-        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
                 frame: (0@0 extent: 1.0@1.0).
         scrollPane scroller addMorph: world.
         world hostWindow: window.
         window openInWorld
  !




Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Chris Muller-3
Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes?  Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.   Please let that sink in for a moment.

Even ignoring that, it also bloats the readability of the history.  There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.

Best,
  Chris

On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]> wrote:
Hi Christoph,

I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.

Best,
Marcel

Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:

Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?


Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
Gesendet: Mittwoch, 13. November 2019 12:15:14
An: [hidden email]; [hidden email]
Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
 
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.368.mcz

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+        "Answer the receiver, scaled such that it has the desired width."
+
+        newWidth = self width ifTrue: [^ self].
+        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+        self helpText editWithLabel: 'FreeCell Help'.!
-        | window helpMorph |
-        window := SystemWindow labelled: 'FreeCell Help' translated.
-        window model: self.
-        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
-        window
-                addMorph: helpMorph
-                frame: (0 @ 0 extent: 1 @ 1).
-        window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+        super color: aColor.
+       
+        "Migrate old instances."
+        inner color: Color transparent.
+       
+        "Keep iris visible."
+        aColor = iris color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
         "initialize the state of the receiver"
         super initialize.
         ""
         inner := EllipseMorph new.
+        inner color: Color transparent.
-        inner color: self color.
         inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
-        inner borderColor: self color.
         inner borderWidth: 0.
  ""
         iris := EllipseMorph new.
         iris color: Color white.
         iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
         self addMorphCentered: inner.
         inner addMorphCentered: iris.
  ""
         self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+        ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+        iris color: aColor.
+       
+        "Keep iris visible."
+        aColor = self color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+        ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
         | a b theta x y |
         theta := (cp - self center) theta.
         a := inner width // 2.
         b := inner height // 2.
         x := a * (theta cos).
         y := b * (theta sin).
         iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
         | cp |
         cp := self globalPointToLocal: self world primaryHand position.
         (inner containsPoint: cp)
                 ifTrue: [iris position: (cp - (iris extent // 2))]
+                ifFalse: [self irisPos: cp].!
-                ifFalse: [self irisPos: cp].
-        self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
         ^ decimalPlacesButton
                 ifNil: [Utilities
                                 decimalPlacesForFloatPrecision: (self targetPlayer
+                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
-                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
                 ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
         "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
         | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
         aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
         aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
         Preferences universalTiles ifTrue: [
                 aScriptEditor install.
                 "aScriptEditor hResizing: #shrinkWrap;
                         vResizing: #shrinkWrap;
                         cellPositioning: #topLeft;
                         setProperty: #autoFitContents toValue: true."
                 aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+                tw := aScriptEditor findA: ScrollPane.
-                tw := aScriptEditor findA: TwoWayScrollPane.
                 aPhrase ifNotNil:
                         [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
                         blk addMorphFront: aPhrase.
                         aPhrase accept.
                 ].
                 SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
         ] ifFalse: [
                 aPhrase
                                 ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
                                 ifNil: [aScriptEditor install]
         ].
         self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
                 "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
         self updateScriptsCategoryOfViewers.
  ].
         ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
         "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
         | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
         aPasteUpMorph removeAllMorphs.
 
         aFont := Preferences standardListFont.
+        aColor := aPanel windowColorToUse.
-        aColor := aPanel defaultBackgroundColor.
         tabbedPalette := TabbedPalette newSticky.
         tabbedPalette dropEnabled: false.
         (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
                  highlightColor: Color red regularColor: Color brown darker darker.
         tabbedPalette on: #mouseDown send: #yourself to: #().
         maxEntriesPerCategory := 0.
         self listOfCategories do:
                 [:aCat |
                         controlPage := AlignmentMorph newColumn beSticky color: aColor.
                         controlPage on: #mouseDown send: #yourself to: #().
                         controlPage dropEnabled: false.
                         controlPage borderColor: aColor;
                                  layoutInset: 4.
                         (prefObjects := self preferenceObjectsInCategory: aCat) do:
                                 [:aPreference | | button |
                                         button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
                                         button ifNotNil: [controlPage addMorphBack: button]].
                         controlPage setNameTo: aCat asString.
                         aCat = #?
                                 ifTrue: [aPanel addHelpItemsTo: controlPage].
                         tabbedPalette addTabFor: controlPage font: aFont.
                         aCat = 'search results' ifTrue:
                                 [(tabbedPalette tabNamed: aCat) setBalloonText:
                                         'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
                 maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
         tabbedPalette selectTabNamed: '?'.
         tabsMorph rowsNoWiderThan: aPasteUpMorph width.
         aPasteUpMorph on: #mouseDown send: #yourself to: #().
         anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
         aPasteUpMorph extent: anExtent.
         aPasteUpMorph color: aColor.
         aPasteUpMorph     addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
         "Toggle between auto fit to size of code and manual resize with scrolling"
         | tw |
+        (tw := self findA: ScrollPane) ifNil: [^ self].
-        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
         (self hasProperty: #autoFitContents)
                 ifTrue: [self removeProperty: #autoFitContents.
                         self hResizing: #rigid; vResizing: #rigid]
                 ifFalse: [self setProperty: #autoFitContents toValue: true.
                         self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
         tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
         | newExtent tw menu |
         newExtent := x max: self minWidth @ self minHeight.
+        (tw := self findA: ScrollPane) ifNil:
-        (tw := self findA: TwoWayScrollPane) ifNil:
                 ["This was the old behavior"
                 ^ super extent: newExtent].
 
         (self hasProperty: #autoFitContents) ifTrue: [
                 menu := MenuMorph new defaultTarget: self.
                 menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
                 menu addTitle: 'To resize the script, uncheck the box below' translated.
                 menu popUpEvent: nil in: self world     .
                 ^ self].
 
         "Allow the user to resize to any size"
         tw extent: ((newExtent x max: self firstSubmorph width)
                                 @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
         ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
         "Possibly delete the tiles, but only if using universal tiles."
 
         | tw |
         Preferences universalTiles ifFalse: [^self].
+        (tw := self findA: ScrollPane) isNil
-        (tw := self findA: TwoWayScrollPane) isNil
                 ifFalse:
                         [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
                         submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+        | on |
+        on := soundInput isRecording.
+        self stop.
+        fft := FFT new: aSize.
+        self resetDisplay.
+        on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
         "Set the size of the FFT used for frequency analysis."
 
+        | aMenu sz |
-        | aMenu sz on |
         aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
         ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
         sz := aMenu startUp.
         sz ifNil: [^ self].
+        self fftSize: sz.!
-        on := soundInput isRecording.
-        self stop.
-        fft := FFT new: sz.
-        self resetDisplay.
-        on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
         | tw |
+        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
-        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
         tw hResizing: #spaceFill;
                 vResizing: #spaceFill;
                 color: Color transparent;
                 setProperty: #hideUnneededScrollbars toValue: true.
         outerMorph
                 hResizing: #shrinkWrap;
                 vResizing: #shrinkWrap;
                 cellPositioning: #topLeft.
         outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
         "The object that owns this script layout"
 
         | oo higher |
         oo := self owner.
         [higher := oo isSyntaxMorph.
         higher := higher or: [oo class == TransformMorph].
+        higher := higher or: [oo class == ScrollPane].
-        higher := higher or: [oo class == TwoWayScrollPane].
         higher ifFalse: [^ oo].
         higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
-        "Answer a scroll pane in which the receiver is scrollable"
-
-        ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+        | sel |
-        | window widget sel |
         sel := ''.
         self firstSubmorph allMorphs do: [:rr |
+                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
-        widget := self inAScrollPane.
-        widget color: Color paleOrange.
-        window
-                addMorph: widget
-                frame: (0@0 extent: 1.0@1.0).
-        window openInWorldExtent: (
-                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
-        )
 
+        ^ self inAScrollPane
+                color: Color paleOrange;
+                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+        ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
         self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+                        ifFalse: [self borderColor: self stdBorderColor]
+                        ifTrue: [
+                                (self hasProperty: #deselectedBorderColor)
+                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
-                self borderColor: (
-                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
-                                ifFalse: [self borderColor: self stdBorderColor]
-                                ifTrue: [
-                                        (self hasProperty: #deselectedBorderColor)
-                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
-                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
         "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
         | pad newPad functionPhrase |
         pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
         (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         pad owner replaceSubmorph: pad by: newPad.
         functionPhrase operator: #abs pad: pad.
         functionPhrase addSuffixArrow.
         self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
         "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
         | newPad functionPhrase |
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         owner replaceSubmorph: self by: newPad.
         functionPhrase operator: #abs pad: self.
         self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
         ^ parent addToken: self name
                         type: #variable
+                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
-                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
         ^ self new
                 fontName: aString;
                 color: aColor;
                 centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
         "WorldWindow test2."
 
         | window world scrollPane |
         world := WiWPasteUpMorph newWorldForProject: nil.
         window := (WorldWindow labelled: 'Scrollable World') model: world.
+        window addMorph: (scrollPane := ScrollPane new model: world)
-        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
                 frame: (0@0 extent: 1.0@1.0).
         scrollPane scroller addMorph: world.
         world hostWindow: window.
         window openInWorld
  !





Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Christoph Thiede
Hi Chris, thank you for your feedback! While I personally think a few megabyte shouldn't be worth any premature optimization nowadays, I see that a good readability of the history should be preserved. Are you explicitly referring to EToys-ct.360 or also some others?

I always hesitate to put different changes together into one commit, as you can only accept or reject it atomarily, making it hard to revert only one of the changes ...

Best,
Christoph



On Wed, Nov 13, 2019 at 8:20 PM +0100, "Chris Muller" <[hidden email]> wrote:

Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes?  Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.   Please let that sink in for a moment.

Even ignoring that, it also bloats the readability of the history.  There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.

Best,
  Chris

On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]> wrote:
Hi Christoph,

I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.

Best,
Marcel

Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:

Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?


Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
Gesendet: Mittwoch, 13. November 2019 12:15:14
An: [hidden email]; [hidden email]
Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
 
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.368.mcz

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+        "Answer the receiver, scaled such that it has the desired width."
+
+        newWidth = self width ifTrue: [^ self].
+        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+        self helpText editWithLabel: 'FreeCell Help'.!
-        | window helpMorph |
-        window := SystemWindow labelled: 'FreeCell Help' translated.
-        window model: self.
-        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
-        window
-                addMorph: helpMorph
-                frame: (0 @ 0 extent: 1 @ 1).
-        window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+        super color: aColor.
+       
+        "Migrate old instances."
+        inner color: Color transparent.
+       
+        "Keep iris visible."
+        aColor = iris color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
         "initialize the state of the receiver"
         super initialize.
         ""
         inner := EllipseMorph new.
+        inner color: Color transparent.
-        inner color: self color.
         inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
-        inner borderColor: self color.
         inner borderWidth: 0.
  ""
         iris := EllipseMorph new.
         iris color: Color white.
         iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
         self addMorphCentered: inner.
         inner addMorphCentered: iris.
  ""
         self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+        ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+        iris color: aColor.
+       
+        "Keep iris visible."
+        aColor = self color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+        ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
         | a b theta x y |
         theta := (cp - self center) theta.
         a := inner width // 2.
         b := inner height // 2.
         x := a * (theta cos).
         y := b * (theta sin).
         iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
         | cp |
         cp := self globalPointToLocal: self world primaryHand position.
         (inner containsPoint: cp)
                 ifTrue: [iris position: (cp - (iris extent // 2))]
+                ifFalse: [self irisPos: cp].!
-                ifFalse: [self irisPos: cp].
-        self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
         ^ decimalPlacesButton
                 ifNil: [Utilities
                                 decimalPlacesForFloatPrecision: (self targetPlayer
+                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
-                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
                 ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
         "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
         | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
         aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
         aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
         Preferences universalTiles ifTrue: [
                 aScriptEditor install.
                 "aScriptEditor hResizing: #shrinkWrap;
                         vResizing: #shrinkWrap;
                         cellPositioning: #topLeft;
                         setProperty: #autoFitContents toValue: true."
                 aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+                tw := aScriptEditor findA: ScrollPane.
-                tw := aScriptEditor findA: TwoWayScrollPane.
                 aPhrase ifNotNil:
                         [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
                         blk addMorphFront: aPhrase.
                         aPhrase accept.
                 ].
                 SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
         ] ifFalse: [
                 aPhrase
                                 ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
                                 ifNil: [aScriptEditor install]
         ].
         self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
                 "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
         self updateScriptsCategoryOfViewers.
  ].
         ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
         "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
         | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
         aPasteUpMorph removeAllMorphs.
 
         aFont := Preferences standardListFont.
+        aColor := aPanel windowColorToUse.
-        aColor := aPanel defaultBackgroundColor.
         tabbedPalette := TabbedPalette newSticky.
         tabbedPalette dropEnabled: false.
         (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
                  highlightColor: Color red regularColor: Color brown darker darker.
         tabbedPalette on: #mouseDown send: #yourself to: #().
         maxEntriesPerCategory := 0.
         self listOfCategories do:
                 [:aCat |
                         controlPage := AlignmentMorph newColumn beSticky color: aColor.
                         controlPage on: #mouseDown send: #yourself to: #().
                         controlPage dropEnabled: false.
                         controlPage borderColor: aColor;
                                  layoutInset: 4.
                         (prefObjects := self preferenceObjectsInCategory: aCat) do:
                                 [:aPreference | | button |
                                         button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
                                         button ifNotNil: [controlPage addMorphBack: button]].
                         controlPage setNameTo: aCat asString.
                         aCat = #?
                                 ifTrue: [aPanel addHelpItemsTo: controlPage].
                         tabbedPalette addTabFor: controlPage font: aFont.
                         aCat = 'search results' ifTrue:
                                 [(tabbedPalette tabNamed: aCat) setBalloonText:
                                         'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
                 maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
         tabbedPalette selectTabNamed: '?'.
         tabsMorph rowsNoWiderThan: aPasteUpMorph width.
         aPasteUpMorph on: #mouseDown send: #yourself to: #().
         anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
         aPasteUpMorph extent: anExtent.
         aPasteUpMorph color: aColor.
         aPasteUpMorph     addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
         "Toggle between auto fit to size of code and manual resize with scrolling"
         | tw |
+        (tw := self findA: ScrollPane) ifNil: [^ self].
-        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
         (self hasProperty: #autoFitContents)
                 ifTrue: [self removeProperty: #autoFitContents.
                         self hResizing: #rigid; vResizing: #rigid]
                 ifFalse: [self setProperty: #autoFitContents toValue: true.
                         self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
         tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
         | newExtent tw menu |
         newExtent := x max: self minWidth @ self minHeight.
+        (tw := self findA: ScrollPane) ifNil:
-        (tw := self findA: TwoWayScrollPane) ifNil:
                 ["This was the old behavior"
                 ^ super extent: newExtent].
 
         (self hasProperty: #autoFitContents) ifTrue: [
                 menu := MenuMorph new defaultTarget: self.
                 menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
                 menu addTitle: 'To resize the script, uncheck the box below' translated.
                 menu popUpEvent: nil in: self world     .
                 ^ self].
 
         "Allow the user to resize to any size"
         tw extent: ((newExtent x max: self firstSubmorph width)
                                 @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
         ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
         "Possibly delete the tiles, but only if using universal tiles."
 
         | tw |
         Preferences universalTiles ifFalse: [^self].
+        (tw := self findA: ScrollPane) isNil
-        (tw := self findA: TwoWayScrollPane) isNil
                 ifFalse:
                         [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
                         submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+        | on |
+        on := soundInput isRecording.
+        self stop.
+        fft := FFT new: aSize.
+        self resetDisplay.
+        on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
         "Set the size of the FFT used for frequency analysis."
 
+        | aMenu sz |
-        | aMenu sz on |
         aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
         ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
         sz := aMenu startUp.
         sz ifNil: [^ self].
+        self fftSize: sz.!
-        on := soundInput isRecording.
-        self stop.
-        fft := FFT new: sz.
-        self resetDisplay.
-        on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
         | tw |
+        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
-        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
         tw hResizing: #spaceFill;
                 vResizing: #spaceFill;
                 color: Color transparent;
                 setProperty: #hideUnneededScrollbars toValue: true.
         outerMorph
                 hResizing: #shrinkWrap;
                 vResizing: #shrinkWrap;
                 cellPositioning: #topLeft.
         outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
         "The object that owns this script layout"
 
         | oo higher |
         oo := self owner.
         [higher := oo isSyntaxMorph.
         higher := higher or: [oo class == TransformMorph].
+        higher := higher or: [oo class == ScrollPane].
-        higher := higher or: [oo class == TwoWayScrollPane].
         higher ifFalse: [^ oo].
         higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
-        "Answer a scroll pane in which the receiver is scrollable"
-
-        ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+        | sel |
-        | window widget sel |
         sel := ''.
         self firstSubmorph allMorphs do: [:rr |
+                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
-        widget := self inAScrollPane.
-        widget color: Color paleOrange.
-        window
-                addMorph: widget
-                frame: (0@0 extent: 1.0@1.0).
-        window openInWorldExtent: (
-                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
-        )
 
+        ^ self inAScrollPane
+                color: Color paleOrange;
+                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+        ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
         self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+                        ifFalse: [self borderColor: self stdBorderColor]
+                        ifTrue: [
+                                (self hasProperty: #deselectedBorderColor)
+                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
-                self borderColor: (
-                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
-                                ifFalse: [self borderColor: self stdBorderColor]
-                                ifTrue: [
-                                        (self hasProperty: #deselectedBorderColor)
-                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
-                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
         "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
         | pad newPad functionPhrase |
         pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
         (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         pad owner replaceSubmorph: pad by: newPad.
         functionPhrase operator: #abs pad: pad.
         functionPhrase addSuffixArrow.
         self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
         "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
         | newPad functionPhrase |
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         owner replaceSubmorph: self by: newPad.
         functionPhrase operator: #abs pad: self.
         self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
         ^ parent addToken: self name
                         type: #variable
+                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
-                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
         ^ self new
                 fontName: aString;
                 color: aColor;
                 centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
         "WorldWindow test2."
 
         | window world scrollPane |
         world := WiWPasteUpMorph newWorldForProject: nil.
         window := (WorldWindow labelled: 'Scrollable World') model: world.
+        window addMorph: (scrollPane := ScrollPane new model: world)
-        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
                 frame: (0@0 extent: 1.0@1.0).
         scrollPane scroller addMorph: world.
         world hostWindow: window.
         window openInWorld
  !





Carpe Squeak!
Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

marcel.taeumel
In reply to this post by Chris Muller-3
> ... piddly little fixes ...
> ... such small changes are not worth burdening everyone's life ...
> ...  tiny improvements ...

Since I merged those commits and had to read and asses them, I can say that the granularity of them was fine. Except for that one duplication for the help in Freecell.

Let's focus on "recategorize methods". Yes, one could easily do that when fixing another issue. Unless it is a bigger quest such as Patrick's (pre) recent efforts to clean up lots of categories across classes.

Best,
Marcel

Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:

Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes?  Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.   Please let that sink in for a moment.

Even ignoring that, it also bloats the readability of the history.  There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.

Best,
  Chris

On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]> wrote:
Hi Christoph,

I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.

Best,
Marcel

Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:

Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?


Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
Gesendet: Mittwoch, 13. November 2019 12:15:14
An: [hidden email]; [hidden email]
Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
 
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.368.mcz

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+        "Answer the receiver, scaled such that it has the desired width."
+
+        newWidth = self width ifTrue: [^ self].
+        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+        self helpText editWithLabel: 'FreeCell Help'.!
-        | window helpMorph |
-        window := SystemWindow labelled: 'FreeCell Help' translated.
-        window model: self.
-        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
-        window
-                addMorph: helpMorph
-                frame: (0 @ 0 extent: 1 @ 1).
-        window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+        super color: aColor.
+       
+        "Migrate old instances."
+        inner color: Color transparent.
+       
+        "Keep iris visible."
+        aColor = iris color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
         "initialize the state of the receiver"
         super initialize.
         ""
         inner := EllipseMorph new.
+        inner color: Color transparent.
-        inner color: self color.
         inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
-        inner borderColor: self color.
         inner borderWidth: 0.
  ""
         iris := EllipseMorph new.
         iris color: Color white.
         iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
         self addMorphCentered: inner.
         inner addMorphCentered: iris.
  ""
         self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+        ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+        iris color: aColor.
+       
+        "Keep iris visible."
+        aColor = self color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+        ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
         | a b theta x y |
         theta := (cp - self center) theta.
         a := inner width // 2.
         b := inner height // 2.
         x := a * (theta cos).
         y := b * (theta sin).
         iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
         | cp |
         cp := self globalPointToLocal: self world primaryHand position.
         (inner containsPoint: cp)
                 ifTrue: [iris position: (cp - (iris extent // 2))]
+                ifFalse: [self irisPos: cp].!
-                ifFalse: [self irisPos: cp].
-        self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
         ^ decimalPlacesButton
                 ifNil: [Utilities
                                 decimalPlacesForFloatPrecision: (self targetPlayer
+                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
-                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
                 ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
         "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
         | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
         aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
         aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
         Preferences universalTiles ifTrue: [
                 aScriptEditor install.
                 "aScriptEditor hResizing: #shrinkWrap;
                         vResizing: #shrinkWrap;
                         cellPositioning: #topLeft;
                         setProperty: #autoFitContents toValue: true."
                 aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+                tw := aScriptEditor findA: ScrollPane.
-                tw := aScriptEditor findA: TwoWayScrollPane.
                 aPhrase ifNotNil:
                         [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
                         blk addMorphFront: aPhrase.
                         aPhrase accept.
                 ].
                 SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
         ] ifFalse: [
                 aPhrase
                                 ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
                                 ifNil: [aScriptEditor install]
         ].
         self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
                 "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
         self updateScriptsCategoryOfViewers.
  ].
         ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
         "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
         | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
         aPasteUpMorph removeAllMorphs.
 
         aFont := Preferences standardListFont.
+        aColor := aPanel windowColorToUse.
-        aColor := aPanel defaultBackgroundColor.
         tabbedPalette := TabbedPalette newSticky.
         tabbedPalette dropEnabled: false.
         (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
                  highlightColor: Color red regularColor: Color brown darker darker.
         tabbedPalette on: #mouseDown send: #yourself to: #().
         maxEntriesPerCategory := 0.
         self listOfCategories do:
                 [:aCat |
                         controlPage := AlignmentMorph newColumn beSticky color: aColor.
                         controlPage on: #mouseDown send: #yourself to: #().
                         controlPage dropEnabled: false.
                         controlPage borderColor: aColor;
                                  layoutInset: 4.
                         (prefObjects := self preferenceObjectsInCategory: aCat) do:
                                 [:aPreference | | button |
                                         button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
                                         button ifNotNil: [controlPage addMorphBack: button]].
                         controlPage setNameTo: aCat asString.
                         aCat = #?
                                 ifTrue: [aPanel addHelpItemsTo: controlPage].
                         tabbedPalette addTabFor: controlPage font: aFont.
                         aCat = 'search results' ifTrue:
                                 [(tabbedPalette tabNamed: aCat) setBalloonText:
                                         'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
                 maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
         tabbedPalette selectTabNamed: '?'.
         tabsMorph rowsNoWiderThan: aPasteUpMorph width.
         aPasteUpMorph on: #mouseDown send: #yourself to: #().
         anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
         aPasteUpMorph extent: anExtent.
         aPasteUpMorph color: aColor.
         aPasteUpMorph     addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
         "Toggle between auto fit to size of code and manual resize with scrolling"
         | tw |
+        (tw := self findA: ScrollPane) ifNil: [^ self].
-        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
         (self hasProperty: #autoFitContents)
                 ifTrue: [self removeProperty: #autoFitContents.
                         self hResizing: #rigid; vResizing: #rigid]
                 ifFalse: [self setProperty: #autoFitContents toValue: true.
                         self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
         tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
         | newExtent tw menu |
         newExtent := x max: self minWidth @ self minHeight.
+        (tw := self findA: ScrollPane) ifNil:
-        (tw := self findA: TwoWayScrollPane) ifNil:
                 ["This was the old behavior"
                 ^ super extent: newExtent].
 
         (self hasProperty: #autoFitContents) ifTrue: [
                 menu := MenuMorph new defaultTarget: self.
                 menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
                 menu addTitle: 'To resize the script, uncheck the box below' translated.
                 menu popUpEvent: nil in: self world     .
                 ^ self].
 
         "Allow the user to resize to any size"
         tw extent: ((newExtent x max: self firstSubmorph width)
                                 @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
         ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
         "Possibly delete the tiles, but only if using universal tiles."
 
         | tw |
         Preferences universalTiles ifFalse: [^self].
+        (tw := self findA: ScrollPane) isNil
-        (tw := self findA: TwoWayScrollPane) isNil
                 ifFalse:
                         [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
                         submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+        | on |
+        on := soundInput isRecording.
+        self stop.
+        fft := FFT new: aSize.
+        self resetDisplay.
+        on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
         "Set the size of the FFT used for frequency analysis."
 
+        | aMenu sz |
-        | aMenu sz on |
         aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
         ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
         sz := aMenu startUp.
         sz ifNil: [^ self].
+        self fftSize: sz.!
-        on := soundInput isRecording.
-        self stop.
-        fft := FFT new: sz.
-        self resetDisplay.
-        on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
         | tw |
+        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
-        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
         tw hResizing: #spaceFill;
                 vResizing: #spaceFill;
                 color: Color transparent;
                 setProperty: #hideUnneededScrollbars toValue: true.
         outerMorph
                 hResizing: #shrinkWrap;
                 vResizing: #shrinkWrap;
                 cellPositioning: #topLeft.
         outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
         "The object that owns this script layout"
 
         | oo higher |
         oo := self owner.
         [higher := oo isSyntaxMorph.
         higher := higher or: [oo class == TransformMorph].
+        higher := higher or: [oo class == ScrollPane].
-        higher := higher or: [oo class == TwoWayScrollPane].
         higher ifFalse: [^ oo].
         higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
-        "Answer a scroll pane in which the receiver is scrollable"
-
-        ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+        | sel |
-        | window widget sel |
         sel := ''.
         self firstSubmorph allMorphs do: [:rr |
+                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
-        widget := self inAScrollPane.
-        widget color: Color paleOrange.
-        window
-                addMorph: widget
-                frame: (0@0 extent: 1.0@1.0).
-        window openInWorldExtent: (
-                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
-        )
 
+        ^ self inAScrollPane
+                color: Color paleOrange;
+                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+        ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
         self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+                        ifFalse: [self borderColor: self stdBorderColor]
+                        ifTrue: [
+                                (self hasProperty: #deselectedBorderColor)
+                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
-                self borderColor: (
-                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
-                                ifFalse: [self borderColor: self stdBorderColor]
-                                ifTrue: [
-                                        (self hasProperty: #deselectedBorderColor)
-                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
-                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
         "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
         | pad newPad functionPhrase |
         pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
         (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         pad owner replaceSubmorph: pad by: newPad.
         functionPhrase operator: #abs pad: pad.
         functionPhrase addSuffixArrow.
         self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
         "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
         | newPad functionPhrase |
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         owner replaceSubmorph: self by: newPad.
         functionPhrase operator: #abs pad: self.
         self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
         ^ parent addToken: self name
                         type: #variable
+                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
-                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
         ^ self new
                 fontName: aString;
                 color: aColor;
                 centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
         "WorldWindow test2."
 
         | window world scrollPane |
         world := WiWPasteUpMorph newWorldForProject: nil.
         window := (WorldWindow labelled: 'Scrollable World') model: world.
+        window addMorph: (scrollPane := ScrollPane new model: world)
-        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
                 frame: (0@0 extent: 1.0@1.0).
         scrollPane scroller addMorph: world.
         world hostWindow: window.
         window openInWorld
  !





Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Torge Husfeldt
The system is at fault if it doesn’t support the granularity of changes which is convenient for the developers and reviewers.
Just my 2e-2€



Am 14.11.2019 um 09:33 schrieb Marcel Taeumel <[hidden email]>:


> ... piddly little fixes ...
> ... such small changes are not worth burdening everyone's life ...
> ...  tiny improvements ...

Since I merged those commits and had to read and asses them, I can say that the granularity of them was fine. Except for that one duplication for the help in Freecell.

Let's focus on "recategorize methods". Yes, one could easily do that when fixing another issue. Unless it is a bigger quest such as Patrick's (pre) recent efforts to clean up lots of categories across classes.

Best,
Marcel

Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:

Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes?  Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.   Please let that sink in for a moment.

Even ignoring that, it also bloats the readability of the history.  There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.

Best,
  Chris

On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]> wrote:
Hi Christoph,

I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.

Best,
Marcel

Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:

Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?


Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
Gesendet: Mittwoch, 13. November 2019 12:15:14
An: [hidden email]; [hidden email]
Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
 
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.368.mcz

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

Name: EToys-mt.368
Author: mt
Time: 13 November 2019, 12:15:07.673043 pm
UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367

Merge! Merge! Merge! Various fixes in Etoys-related places.

=============== Diff against EToys-kfr.363 ===============

Item was added:
+ ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
+ scaledToWidth: newWidth
+        "Answer the receiver, scaled such that it has the desired width."
+
+        newWidth = self width ifTrue: [^ self].
+        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
+ !

Item was changed:
  ----- Method: FreeCell>>help (in category 'actions') -----
  help
+
+        self helpText editWithLabel: 'FreeCell Help'.!
-        | window helpMorph |
-        window := SystemWindow labelled: 'FreeCell Help' translated.
-        window model: self.
-        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
-        window
-                addMorph: helpMorph
-                frame: (0 @ 0 extent: 1 @ 1).
-        window openInWorld!

Item was added:
+ ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
+ color: aColor
+
+        super color: aColor.
+       
+        "Migrate old instances."
+        inner color: Color transparent.
+       
+        "Keep iris visible."
+        aColor = iris color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was changed:
  ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
  initialize
         "initialize the state of the receiver"
         super initialize.
         ""
         inner := EllipseMorph new.
+        inner color: Color transparent.
-        inner color: self color.
         inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
-        inner borderColor: self color.
         inner borderWidth: 0.
  ""
         iris := EllipseMorph new.
         iris color: Color white.
         iris extent: (self extent * IrisSize) asIntegerPoint.
  ""
         self addMorphCentered: inner.
         inner addMorphCentered: iris.
  ""
         self extent: 26 @ 33!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
+ irisColor
+
+        ^ iris color!

Item was added:
+ ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
+ irisColor: aColor
+
+        iris color: aColor.
+       
+        "Keep iris visible."
+        aColor = self color
+                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
+                ifFalse: [iris borderWidth: 0].!

Item was added:
+ ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
+ irisPos
+
+        ^ iris position!

Item was changed:
+ ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
- ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
  irisPos: cp
 
         | a b theta x y |
         theta := (cp - self center) theta.
         a := inner width // 2.
         b := inner height // 2.
         x := a * (theta cos).
         y := b * (theta sin).
         iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!

Item was changed:
  ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
  step
         | cp |
         cp := self globalPointToLocal: self world primaryHand position.
         (inner containsPoint: cp)
                 ifTrue: [iris position: (cp - (iris extent // 2))]
+                ifFalse: [self irisPos: cp].!
-                ifFalse: [self irisPos: cp].
-        self changed "cover up gribblies if embedded in Flash"!

Item was changed:
  ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
  decimalPlaces
         ^ decimalPlacesButton
                 ifNil: [Utilities
                                 decimalPlacesForFloatPrecision: (self targetPlayer
+                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
-                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
                 ifNotNil: [:button| button label asNumber]!

Item was changed:
  ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
  newScriptorAround: aPhrase
         "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
 
         | aScriptEditor aUniclassScript tw blk |
  Cursor wait showWhile: [
         aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
         aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
 
         Preferences universalTiles ifTrue: [
                 aScriptEditor install.
                 "aScriptEditor hResizing: #shrinkWrap;
                         vResizing: #shrinkWrap;
                         cellPositioning: #topLeft;
                         setProperty: #autoFitContents toValue: true."
                 aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
+                tw := aScriptEditor findA: ScrollPane.
-                tw := aScriptEditor findA: TwoWayScrollPane.
                 aPhrase ifNotNil:
                         [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
                         blk addMorphFront: aPhrase.
                         aPhrase accept.
                 ].
                 SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
         ] ifFalse: [
                 aPhrase
                                 ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
                                 ifNil: [aScriptEditor install]
         ].
         self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
                 "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
         self updateScriptsCategoryOfViewers.
  ].
         ^ aScriptEditor!

Item was changed:
  ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
  initializePreferencePanel: aPanel in: aPasteUpMorph
         "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
 
         | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
         aPasteUpMorph removeAllMorphs.
 
         aFont := Preferences standardListFont.
+        aColor := aPanel windowColorToUse.
-        aColor := aPanel defaultBackgroundColor.
         tabbedPalette := TabbedPalette newSticky.
         tabbedPalette dropEnabled: false.
         (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
                  highlightColor: Color red regularColor: Color brown darker darker.
         tabbedPalette on: #mouseDown send: #yourself to: #().
         maxEntriesPerCategory := 0.
         self listOfCategories do:
                 [:aCat |
                         controlPage := AlignmentMorph newColumn beSticky color: aColor.
                         controlPage on: #mouseDown send: #yourself to: #().
                         controlPage dropEnabled: false.
                         controlPage borderColor: aColor;
                                  layoutInset: 4.
                         (prefObjects := self preferenceObjectsInCategory: aCat) do:
                                 [:aPreference | | button |
                                         button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
                                         button ifNotNil: [controlPage addMorphBack: button]].
                         controlPage setNameTo: aCat asString.
                         aCat = #?
                                 ifTrue: [aPanel addHelpItemsTo: controlPage].
                         tabbedPalette addTabFor: controlPage font: aFont.
                         aCat = 'search results' ifTrue:
                                 [(tabbedPalette tabNamed: aCat) setBalloonText:
                                         'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
                 maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
         tabbedPalette selectTabNamed: '?'.
         tabsMorph rowsNoWiderThan: aPasteUpMorph width.
         aPasteUpMorph on: #mouseDown send: #yourself to: #().
         anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
         aPasteUpMorph extent: anExtent.
         aPasteUpMorph color: aColor.
         aPasteUpMorph     addMorphBack: tabbedPalette.!

Item was changed:
  ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
         "Toggle between auto fit to size of code and manual resize with scrolling"
         | tw |
+        (tw := self findA: ScrollPane) ifNil: [^ self].
-        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
         (self hasProperty: #autoFitContents)
                 ifTrue: [self removeProperty: #autoFitContents.
                         self hResizing: #rigid; vResizing: #rigid]
                 ifFalse: [self setProperty: #autoFitContents toValue: true.
                         self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
         tw layoutChanged!

Item was changed:
  ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
  extent: x
 
         | newExtent tw menu |
         newExtent := x max: self minWidth @ self minHeight.
+        (tw := self findA: ScrollPane) ifNil:
-        (tw := self findA: TwoWayScrollPane) ifNil:
                 ["This was the old behavior"
                 ^ super extent: newExtent].
 
         (self hasProperty: #autoFitContents) ifTrue: [
                 menu := MenuMorph new defaultTarget: self.
                 menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
                 menu addTitle: 'To resize the script, uncheck the box below' translated.
                 menu popUpEvent: nil in: self world     .
                 ^ self].
 
         "Allow the user to resize to any size"
         tw extent: ((newExtent x max: self firstSubmorph width)
                                 @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
         ^ super extent: newExtent!

Item was changed:
  ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
  hibernate
         "Possibly delete the tiles, but only if using universal tiles."
 
         | tw |
         Preferences universalTiles ifFalse: [^self].
+        (tw := self findA: ScrollPane) isNil
-        (tw := self findA: TwoWayScrollPane) isNil
                 ifFalse:
                         [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
                         submorphs size > 1 ifTrue: [tw delete]]!

Item was added:
+ ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
+ fftSize: aSize
+
+        | on |
+        on := soundInput isRecording.
+        self stop.
+        fft := FFT new: aSize.
+        self resetDisplay.
+        on ifTrue: [self start].!

Item was changed:
  ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
  setFFTSize
         "Set the size of the FFT used for frequency analysis."
 
+        | aMenu sz |
-        | aMenu sz on |
         aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
         ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
         sz := aMenu startUp.
         sz ifNil: [^ self].
+        self fftSize: sz.!
-        on := soundInput isRecording.
-        self stop.
-        fft := FFT new: sz.
-        self resetDisplay.
-        on ifTrue: [self start].
- !

Item was changed:
  ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
  setSize: oldExtent andMakeResizable: outerMorph
         | tw |
+        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
-        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
         tw hResizing: #spaceFill;
                 vResizing: #spaceFill;
                 color: Color transparent;
                 setProperty: #hideUnneededScrollbars toValue: true.
         outerMorph
                 hResizing: #shrinkWrap;
                 vResizing: #shrinkWrap;
                 cellPositioning: #topLeft.
         outerMorph fullBounds.
  !

Item was changed:
  ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
  enclosingPane
         "The object that owns this script layout"
 
         | oo higher |
         oo := self owner.
         [higher := oo isSyntaxMorph.
         higher := higher or: [oo class == TransformMorph].
+        higher := higher or: [oo class == ScrollPane].
-        higher := higher or: [oo class == TwoWayScrollPane].
         higher ifFalse: [^ oo].
         higher] whileTrue: [oo := oo owner].
  !

Item was removed:
- ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
- inAScrollPane
-        "Answer a scroll pane in which the receiver is scrollable"
-
-        ^ self inATwoWayScrollPane!

Item was changed:
  ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
  openInWindow
 
+        | sel |
-        | window widget sel |
         sel := ''.
         self firstSubmorph allMorphs do: [:rr |
+                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
-        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
-        widget := self inAScrollPane.
-        widget color: Color paleOrange.
-        window
-                addMorph: widget
-                frame: (0@0 extent: 1.0@1.0).
-        window openInWorldExtent: (
-                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
-        )
 
+        ^ self inAScrollPane
+                color: Color paleOrange;
+                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
- !

Item was added:
+ ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
+ parseNodeWith: encoder asStatement: aBoolean
+
+        ^ self parseNode!

Item was changed:
  ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
  unhighlightBorder
 
         self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
+                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
+                        ifFalse: [self borderColor: self stdBorderColor]
+                        ifTrue: [
+                                (self hasProperty: #deselectedBorderColor)
+                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
+                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
-                self borderColor: (
-                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
-                                ifFalse: [self borderColor: self stdBorderColor]
-                                ifTrue: [
-                                        (self hasProperty: #deselectedBorderColor)
-                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
-                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!

Item was changed:
  ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
  wrapPhraseInFunction
         "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
 
         | pad newPad functionPhrase |
         pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
         (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         pad owner replaceSubmorph: pad by: newPad.
         functionPhrase operator: #abs pad: pad.
         functionPhrase addSuffixArrow.
         self scriptEdited
  !

Item was changed:
  ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
  wrapInFunction
         "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
 
         | newPad functionPhrase |
         newPad := TilePadMorph new setType: #Number.
+        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
-        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
         functionPhrase := FunctionTile new.
         newPad addMorphBack: functionPhrase.
         owner replaceSubmorph: self by: newPad.
         functionPhrase operator: #abs pad: self.
         self scriptEdited!

Item was changed:
  ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
  asMorphicSyntaxIn: parent
 
         ^ parent addToken: self name
                         type: #variable
+                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
-                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
  !

Item was changed:
+ ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
- ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
  fontName: aString bgColor: aColor centerColor: otherColor
         ^ self new
                 fontName: aString;
                 color: aColor;
                 centerColor: otherColor!

Item was changed:
  ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
  test2
         "WorldWindow test2."
 
         | window world scrollPane |
         world := WiWPasteUpMorph newWorldForProject: nil.
         window := (WorldWindow labelled: 'Scrollable World') model: world.
+        window addMorph: (scrollPane := ScrollPane new model: world)
-        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
                 frame: (0@0 extent: 1.0@1.0).
         scrollPane scroller addMorph: world.
         world hostWindow: window.
         window openInWorld
  !






Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Tobias Pape
In reply to this post by marcel.taeumel
small commits are great :D
        -t

> On 14.11.2019, at 09:32, Marcel Taeumel <[hidden email]> wrote:
>
> > ... piddly little fixes ...
> > ... such small changes are not worth burdening everyone's life ...
> > ...  tiny improvements ...
>
> Since I merged those commits and had to read and asses them, I can say that the granularity of them was fine. Except for that one duplication for the help in Freecell.
>
> Let's focus on "recategorize methods". Yes, one could easily do that when fixing another issue. Unless it is a bigger quest such as Patrick's (pre) recent efforts to clean up lots of categories across classes.
>
> Best,
> Marcel
>> Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:
>>
>> Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes?  Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.   Please let that sink in for a moment.
>>
>> Even ignoring that, it also bloats the readability of the history.  There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.
>>
>> Best,
>>   Chris
>>
>> On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]> wrote:
>> Hi Christoph,
>>
>> I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.
>>
>> Best,
>> Marcel
>>> Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:
>>>
>>> Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?
>>>
>>> Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
>>> Gesendet: Mittwoch, 13. November 2019 12:15:14
>>> An: [hidden email]; [hidden email]
>>> Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
>>>  
>>> Marcel Taeumel uploaded a new version of EToys to project The Trunk:
>>> http://source.squeak.org/trunk/EToys-mt.368.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: EToys-mt.368
>>> Author: mt
>>> Time: 13 November 2019, 12:15:07.673043 pm
>>> UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
>>> Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367
>>>
>>> Merge! Merge! Merge! Various fixes in Etoys-related places.
>>>
>>> =============== Diff against EToys-kfr.363 ===============
>>>
>>> Item was added:
>>> + ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
>>> + scaledToWidth: newWidth
>>> +        "Answer the receiver, scaled such that it has the desired width."
>>> +
>>> +        newWidth = self width ifTrue: [^ self].
>>> +        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
>>> + !
>>>
>>> Item was changed:
>>>   ----- Method: FreeCell>>help (in category 'actions') -----
>>>   help
>>> +
>>> +        self helpText editWithLabel: 'FreeCell Help'.!
>>> -        | window helpMorph |
>>> -        window := SystemWindow labelled: 'FreeCell Help' translated.
>>> -        window model: self.
>>> -        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
>>> -        window
>>> -                addMorph: helpMorph
>>> -                frame: (0 @ 0 extent: 1 @ 1).
>>> -        window openInWorld!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
>>> + color: aColor
>>> +
>>> +        super color: aColor.
>>> +        
>>> +        "Migrate old instances."
>>> +        inner color: Color transparent.
>>> +        
>>> +        "Keep iris visible."
>>> +        aColor = iris color
>>> +                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
>>> +                ifFalse: [iris borderWidth: 0].!
>>>
>>> Item was changed:
>>>   ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
>>>   initialize
>>>          "initialize the state of the receiver"
>>>          super initialize.
>>>          ""
>>>          inner := EllipseMorph new.
>>> +        inner color: Color transparent.
>>> -        inner color: self color.
>>>          inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
>>> -        inner borderColor: self color.
>>>          inner borderWidth: 0.
>>>   ""
>>>          iris := EllipseMorph new.
>>>          iris color: Color white.
>>>          iris extent: (self extent * IrisSize) asIntegerPoint.
>>>   ""
>>>          self addMorphCentered: inner.
>>>          inner addMorphCentered: iris.
>>>   ""
>>>          self extent: 26 @ 33!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
>>> + irisColor
>>> +
>>> +        ^ iris color!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
>>> + irisColor: aColor
>>> +
>>> +        iris color: aColor.
>>> +        
>>> +        "Keep iris visible."
>>> +        aColor = self color
>>> +                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
>>> +                ifFalse: [iris borderWidth: 0].!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
>>> + irisPos
>>> +
>>> +        ^ iris position!
>>>
>>> Item was changed:
>>> + ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
>>> - ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
>>>   irisPos: cp
>>>  
>>>          | a b theta x y |
>>>          theta := (cp - self center) theta.
>>>          a := inner width // 2.
>>>          b := inner height // 2.
>>>          x := a * (theta cos).
>>>          y := b * (theta sin).
>>>          iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!
>>>
>>> Item was changed:
>>>   ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
>>>   step
>>>          | cp |
>>>          cp := self globalPointToLocal: self world primaryHand position.
>>>          (inner containsPoint: cp)
>>>                  ifTrue: [iris position: (cp - (iris extent // 2))]
>>> +                ifFalse: [self irisPos: cp].!
>>> -                ifFalse: [self irisPos: cp].
>>> -        self changed "cover up gribblies if embedded in Flash"!
>>>
>>> Item was changed:
>>>   ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
>>>   decimalPlaces
>>>          ^ decimalPlacesButton
>>>                  ifNil: [Utilities
>>>                                  decimalPlacesForFloatPrecision: (self targetPlayer
>>> +                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
>>> -                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
>>>                  ifNotNil: [:button| button label asNumber]!
>>>
>>> Item was changed:
>>>   ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
>>>   newScriptorAround: aPhrase
>>>          "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
>>>  
>>>          | aScriptEditor aUniclassScript tw blk |
>>>   Cursor wait showWhile: [
>>>          aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
>>>          aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
>>>  
>>>          Preferences universalTiles ifTrue: [
>>>                  aScriptEditor install.
>>>                  "aScriptEditor hResizing: #shrinkWrap;
>>>                          vResizing: #shrinkWrap;
>>>                          cellPositioning: #topLeft;
>>>                          setProperty: #autoFitContents toValue: true."
>>>                  aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
>>> +                tw := aScriptEditor findA: ScrollPane.
>>> -                tw := aScriptEditor findA: TwoWayScrollPane.
>>>                  aPhrase ifNotNil:
>>>                          [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
>>>                          blk addMorphFront: aPhrase.
>>>                          aPhrase accept.
>>>                  ].
>>>                  SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
>>>          ] ifFalse: [
>>>                  aPhrase
>>>                                  ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
>>>                                  ifNil: [aScriptEditor install]
>>>          ].
>>>          self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
>>>                  "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
>>>          self updateScriptsCategoryOfViewers.
>>>   ].
>>>          ^ aScriptEditor!
>>>
>>> Item was changed:
>>>   ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
>>>   initializePreferencePanel: aPanel in: aPasteUpMorph
>>>          "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
>>>  
>>>          | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
>>>          aPasteUpMorph removeAllMorphs.
>>>  
>>>          aFont := Preferences standardListFont.
>>> +        aColor := aPanel windowColorToUse.
>>> -        aColor := aPanel defaultBackgroundColor.
>>>          tabbedPalette := TabbedPalette newSticky.
>>>          tabbedPalette dropEnabled: false.
>>>          (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
>>>                   highlightColor: Color red regularColor: Color brown darker darker.
>>>          tabbedPalette on: #mouseDown send: #yourself to: #().
>>>          maxEntriesPerCategory := 0.
>>>          self listOfCategories do:
>>>                  [:aCat |
>>>                          controlPage := AlignmentMorph newColumn beSticky color: aColor.
>>>                          controlPage on: #mouseDown send: #yourself to: #().
>>>                          controlPage dropEnabled: false.
>>>                          controlPage borderColor: aColor;
>>>                                   layoutInset: 4.
>>>                          (prefObjects := self preferenceObjectsInCategory: aCat) do:
>>>                                  [:aPreference | | button |
>>>                                          button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
>>>                                          button ifNotNil: [controlPage addMorphBack: button]].
>>>                          controlPage setNameTo: aCat asString.
>>>                          aCat = #?
>>>                                  ifTrue: [aPanel addHelpItemsTo: controlPage].
>>>                          tabbedPalette addTabFor: controlPage font: aFont.
>>>                          aCat = 'search results' ifTrue:
>>>                                  [(tabbedPalette tabNamed: aCat) setBalloonText:
>>>                                          'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
>>>                  maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
>>>          tabbedPalette selectTabNamed: '?'.
>>>          tabsMorph rowsNoWiderThan: aPasteUpMorph width.
>>>          aPasteUpMorph on: #mouseDown send: #yourself to: #().
>>>          anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
>>>          aPasteUpMorph extent: anExtent.
>>>          aPasteUpMorph color: aColor.
>>>          aPasteUpMorph     addMorphBack: tabbedPalette.!
>>>
>>> Item was changed:
>>>   ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
>>>   autoFitOnOff
>>>          "Toggle between auto fit to size of code and manual resize with scrolling"
>>>          | tw |
>>> +        (tw := self findA: ScrollPane) ifNil: [^ self].
>>> -        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
>>>          (self hasProperty: #autoFitContents)
>>>                  ifTrue: [self removeProperty: #autoFitContents.
>>>                          self hResizing: #rigid; vResizing: #rigid]
>>>                  ifFalse: [self setProperty: #autoFitContents toValue: true.
>>>                          self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
>>>          tw layoutChanged!
>>>
>>> Item was changed:
>>>   ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
>>>   extent: x
>>>  
>>>          | newExtent tw menu |
>>>          newExtent := x max: self minWidth @ self minHeight.
>>> +        (tw := self findA: ScrollPane) ifNil:
>>> -        (tw := self findA: TwoWayScrollPane) ifNil:
>>>                  ["This was the old behavior"
>>>                  ^ super extent: newExtent].
>>>  
>>>          (self hasProperty: #autoFitContents) ifTrue: [
>>>                  menu := MenuMorph new defaultTarget: self.
>>>                  menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
>>>                  menu addTitle: 'To resize the script, uncheck the box below' translated.
>>>                  menu popUpEvent: nil in: self world     .
>>>                  ^ self].
>>>  
>>>          "Allow the user to resize to any size"
>>>          tw extent: ((newExtent x max: self firstSubmorph width)
>>>                                  @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
>>>          ^ super extent: newExtent!
>>>
>>> Item was changed:
>>>   ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
>>>   hibernate
>>>          "Possibly delete the tiles, but only if using universal tiles."
>>>  
>>>          | tw |
>>>          Preferences universalTiles ifFalse: [^self].
>>> +        (tw := self findA: ScrollPane) isNil
>>> -        (tw := self findA: TwoWayScrollPane) isNil
>>>                  ifFalse:
>>>                          [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
>>>                          submorphs size > 1 ifTrue: [tw delete]]!
>>>
>>> Item was added:
>>> + ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
>>> + fftSize: aSize
>>> +
>>> +        | on |
>>> +        on := soundInput isRecording.
>>> +        self stop.
>>> +        fft := FFT new: aSize.
>>> +        self resetDisplay.
>>> +        on ifTrue: [self start].!
>>>
>>> Item was changed:
>>>   ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
>>>   setFFTSize
>>>          "Set the size of the FFT used for frequency analysis."
>>>  
>>> +        | aMenu sz |
>>> -        | aMenu sz on |
>>>          aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
>>>          ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
>>>          sz := aMenu startUp.
>>>          sz ifNil: [^ self].
>>> +        self fftSize: sz.!
>>> -        on := soundInput isRecording.
>>> -        self stop.
>>> -        fft := FFT new: sz.
>>> -        self resetDisplay.
>>> -        on ifTrue: [self start].
>>> - !
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
>>>   setSize: oldExtent andMakeResizable: outerMorph
>>>          | tw |
>>> +        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
>>> -        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
>>>          tw hResizing: #spaceFill;
>>>                  vResizing: #spaceFill;
>>>                  color: Color transparent;
>>>                  setProperty: #hideUnneededScrollbars toValue: true.
>>>          outerMorph
>>>                  hResizing: #shrinkWrap;
>>>                  vResizing: #shrinkWrap;
>>>                  cellPositioning: #topLeft.
>>>          outerMorph fullBounds.
>>>   !
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
>>>   enclosingPane
>>>          "The object that owns this script layout"
>>>  
>>>          | oo higher |
>>>          oo := self owner.
>>>          [higher := oo isSyntaxMorph.
>>>          higher := higher or: [oo class == TransformMorph].
>>> +        higher := higher or: [oo class == ScrollPane].
>>> -        higher := higher or: [oo class == TwoWayScrollPane].
>>>          higher ifFalse: [^ oo].
>>>          higher] whileTrue: [oo := oo owner].
>>>   !
>>>
>>> Item was removed:
>>> - ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
>>> - inAScrollPane
>>> -        "Answer a scroll pane in which the receiver is scrollable"
>>> -
>>> -        ^ self inATwoWayScrollPane!
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
>>>   openInWindow
>>>  
>>> +        | sel |
>>> -        | window widget sel |
>>>          sel := ''.
>>>          self firstSubmorph allMorphs do: [:rr |
>>> +                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
>>> -                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
>>> -        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
>>> -        widget := self inAScrollPane.
>>> -        widget color: Color paleOrange.
>>> -        window
>>> -                addMorph: widget
>>> -                frame: (0@0 extent: 1.0@1.0).
>>> -        window openInWorldExtent: (
>>> -                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
>>> -        )
>>>  
>>> +        ^ self inAScrollPane
>>> +                color: Color paleOrange;
>>> +                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
>>> - !
>>>
>>> Item was added:
>>> + ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
>>> + parseNodeWith: encoder asStatement: aBoolean
>>> +
>>> +        ^ self parseNode!
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
>>>   unhighlightBorder
>>>  
>>>          self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
>>> +                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
>>> +                        ifFalse: [self borderColor: self stdBorderColor]
>>> +                        ifTrue: [
>>> +                                (self hasProperty: #deselectedBorderColor)
>>> +                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
>>> +                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
>>> -                self borderColor: (
>>> -                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
>>> -                                ifFalse: [self borderColor: self stdBorderColor]
>>> -                                ifTrue: [
>>> -                                        (self hasProperty: #deselectedBorderColor)
>>> -                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
>>> -                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!
>>>
>>> Item was changed:
>>>   ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
>>>   wrapPhraseInFunction
>>>          "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
>>>  
>>>          | pad newPad functionPhrase |
>>>          pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
>>>          (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
>>>          newPad := TilePadMorph new setType: #Number.
>>> +        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
>>> -        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
>>>          functionPhrase := FunctionTile new.
>>>          newPad addMorphBack: functionPhrase.
>>>          pad owner replaceSubmorph: pad by: newPad.
>>>          functionPhrase operator: #abs pad: pad.
>>>          functionPhrase addSuffixArrow.
>>>          self scriptEdited
>>>   !
>>>
>>> Item was changed:
>>>   ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
>>>   wrapInFunction
>>>          "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
>>>  
>>>          | newPad functionPhrase |
>>>          newPad := TilePadMorph new setType: #Number.
>>> +        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
>>> -        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
>>>          functionPhrase := FunctionTile new.
>>>          newPad addMorphBack: functionPhrase.
>>>          owner replaceSubmorph: self by: newPad.
>>>          functionPhrase operator: #abs pad: self.
>>>          self scriptEdited!
>>>
>>> Item was changed:
>>>   ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
>>>   asMorphicSyntaxIn: parent
>>>  
>>>          ^ parent addToken: self name
>>>                          type: #variable
>>> +                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
>>> -                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
>>>   !
>>>
>>> Item was changed:
>>> + ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
>>> - ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
>>>   fontName: aString bgColor: aColor centerColor: otherColor
>>>          ^ self new
>>>                  fontName: aString;
>>>                  color: aColor;
>>>                  centerColor: otherColor!
>>>
>>> Item was changed:
>>>   ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
>>>   test2
>>>          "WorldWindow test2."
>>>  
>>>          | window world scrollPane |
>>>          world := WiWPasteUpMorph newWorldForProject: nil.
>>>          window := (WorldWindow labelled: 'Scrollable World') model: world.
>>> +        window addMorph: (scrollPane := ScrollPane new model: world)
>>> -        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
>>>                  frame: (0@0 extent: 1.0@1.0).
>>>          scrollPane scroller addMorph: world.
>>>          world hostWindow: window.
>>>          window openInWorld
>>>   !
>>>
>>>
>>
>



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Chris Muller-3
In reply to this post by Christoph Thiede
Hi Christoph,
 
I always hesitate to put different changes together into one commit, 

You're right to keep "different changes" in separate commits, and I did not suggest to put different changes into one commit.  A fix is not really a change.
 
as you can only accept or reject it atomarily, making it hard to revert only one of the changes ...

Mmmm, not true.  There's no way to reject any specific ancestor without branching.  Even if it were, the best and easiest way to "revert" a meaningful subset of behavior that way is if the ancestry were clean and delineated.  With a bunch of dust-sized improvements in the list, you have to wade through a bunch of (non)changes that never needed explaining in the first place.

Best,
  Chris



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: EToys-mt.368.mcz

Chris Muller-3
In reply to this post by Tobias Pape
You like "modularity" for your code and packages, you might consider extending the principle to your Versions too, that each would reflect a whole and meaningful Unit-Of-Improvement.

The system will become whatever we make it.  IMO, its worth crafting a deliberate narrative in the ancestry with wholesome commits and low noise.  Tiny, reactive, "incidentals" like method categorizations or comment tweaks or obvious fixes -- don't even need to be explained in the first place, much less stored and replicated.  You're smart and talented, it's not even worth your time.  I'd rather wait and get your whole improvement with the trivialities piggyback'd, but **not even mentioned** in the Version notes at all.  Can you imagine stepping through the history where every entry was about some golden nugget of functional improvement?   :)

Best,
  Chris


On Thu, Nov 14, 2019 at 3:03 PM Tobias Pape <[hidden email]> wrote:
small commits are great :D
        -t
> On 14.11.2019, at 09:32, Marcel Taeumel <[hidden email]> wrote:
>
> > ... piddly little fixes ...
> > ... such small changes are not worth burdening everyone's life ...
> > ...  tiny improvements ...
>
> Since I merged those commits and had to read and asses them, I can say that the granularity of them was fine. Except for that one duplication for the help in Freecell.
>
> Let's focus on "recategorize methods". Yes, one could easily do that when fixing another issue. Unless it is a bigger quest such as Patrick's (pre) recent efforts to clean up lots of categories across classes.
>
> Best,
> Marcel
>> Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:
>>
>> Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes?  Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.   Please let that sink in for a moment.
>>
>> Even ignoring that, it also bloats the readability of the history.  There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.
>>
>> Best,
>>   Chris
>>
>> On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]> wrote:
>> Hi Christoph,
>>
>> I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.
>>
>> Best,
>> Marcel
>>> Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email]>:
>>>
>>> Just for interest, is it usual & desired behavior that when installing these updates, the update log does not include any of my commit messages?
>>>
>>> Von: Squeak-dev <[hidden email]> im Auftrag von [hidden email] <[hidden email]>
>>> Gesendet: Mittwoch, 13. November 2019 12:15:14
>>> An: [hidden email]; [hidden email]
>>> Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
>>> 
>>> Marcel Taeumel uploaded a new version of EToys to project The Trunk:
>>> http://source.squeak.org/trunk/EToys-mt.368.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: EToys-mt.368
>>> Author: mt
>>> Time: 13 November 2019, 12:15:07.673043 pm
>>> UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
>>> Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367
>>>
>>> Merge! Merge! Merge! Various fixes in Etoys-related places.
>>>
>>> =============== Diff against EToys-kfr.363 ===============
>>>
>>> Item was added:
>>> + ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
>>> + scaledToWidth: newWidth
>>> +        "Answer the receiver, scaled such that it has the desired width."
>>> +
>>> +        newWidth = self width ifTrue: [^ self].
>>> +        ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
>>> + !
>>>
>>> Item was changed:
>>>   ----- Method: FreeCell>>help (in category 'actions') -----
>>>   help
>>> +
>>> +        self helpText editWithLabel: 'FreeCell Help'.!
>>> -        | window helpMorph |
>>> -        window := SystemWindow labelled: 'FreeCell Help' translated.
>>> -        window model: self.
>>> -        helpMorph := (PluggableTextMorph new editString: self helpText) lock.
>>> -        window
>>> -                addMorph: helpMorph
>>> -                frame: (0 @ 0 extent: 1 @ 1).
>>> -        window openInWorld!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
>>> + color: aColor
>>> +
>>> +        super color: aColor.
>>> +       
>>> +        "Migrate old instances."
>>> +        inner color: Color transparent.
>>> +       
>>> +        "Keep iris visible."
>>> +        aColor = iris color
>>> +                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
>>> +                ifFalse: [iris borderWidth: 0].!
>>>
>>> Item was changed:
>>>   ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
>>>   initialize
>>>          "initialize the state of the receiver"
>>>          super initialize.
>>>          ""
>>>          inner := EllipseMorph new.
>>> +        inner color: Color transparent.
>>> -        inner color: self color.
>>>          inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
>>> -        inner borderColor: self color.
>>>          inner borderWidth: 0.
>>>   ""
>>>          iris := EllipseMorph new.
>>>          iris color: Color white.
>>>          iris extent: (self extent * IrisSize) asIntegerPoint.
>>>   ""
>>>          self addMorphCentered: inner.
>>>          inner addMorphCentered: iris.
>>>   ""
>>>          self extent: 26 @ 33!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
>>> + irisColor
>>> +
>>> +        ^ iris color!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
>>> + irisColor: aColor
>>> +
>>> +        iris color: aColor.
>>> +       
>>> +        "Keep iris visible."
>>> +        aColor = self color
>>> +                ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
>>> +                ifFalse: [iris borderWidth: 0].!
>>>
>>> Item was added:
>>> + ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
>>> + irisPos
>>> +
>>> +        ^ iris position!
>>>
>>> Item was changed:
>>> + ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
>>> - ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
>>>   irisPos: cp
>>>   
>>>          | a b theta x y |
>>>          theta := (cp - self center) theta.
>>>          a := inner width // 2.
>>>          b := inner height // 2.
>>>          x := a * (theta cos).
>>>          y := b * (theta sin).
>>>          iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!
>>>
>>> Item was changed:
>>>   ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
>>>   step
>>>          | cp |
>>>          cp := self globalPointToLocal: self world primaryHand position.
>>>          (inner containsPoint: cp)
>>>                  ifTrue: [iris position: (cp - (iris extent // 2))]
>>> +                ifFalse: [self irisPos: cp].!
>>> -                ifFalse: [self irisPos: cp].
>>> -        self changed "cover up gribblies if embedded in Flash"!
>>>
>>> Item was changed:
>>>   ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
>>>   decimalPlaces
>>>          ^ decimalPlacesButton
>>>                  ifNil: [Utilities
>>>                                  decimalPlacesForFloatPrecision: (self targetPlayer
>>> +                                        defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
>>> -                                        defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
>>>                  ifNotNil: [:button| button label asNumber]!
>>>
>>> Item was changed:
>>>   ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
>>>   newScriptorAround: aPhrase
>>>          "Sprout a scriptor around aPhrase, thus making a new script.  aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
>>>   
>>>          | aScriptEditor aUniclassScript tw blk |
>>>   Cursor wait showWhile: [
>>>          aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
>>>          aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
>>>   
>>>          Preferences universalTiles ifTrue: [
>>>                  aScriptEditor install.
>>>                  "aScriptEditor hResizing: #shrinkWrap;
>>>                          vResizing: #shrinkWrap;
>>>                          cellPositioning: #topLeft;
>>>                          setProperty: #autoFitContents toValue: true."
>>>                  aScriptEditor insertUniversalTiles.  "Gets an empty SyntaxMorph for a MethodNode"
>>> +                tw := aScriptEditor findA: ScrollPane.
>>> -                tw := aScriptEditor findA: TwoWayScrollPane.
>>>                  aPhrase ifNotNil:
>>>                          [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
>>>                          blk addMorphFront: aPhrase.
>>>                          aPhrase accept.
>>>                  ].
>>>                  SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
>>>          ] ifFalse: [
>>>                  aPhrase
>>>                                  ifNotNil: [aScriptEditor phrase: aPhrase]       "does an install"
>>>                                  ifNil: [aScriptEditor install]
>>>          ].
>>>          self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
>>>                  "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
>>>          self updateScriptsCategoryOfViewers.
>>>   ].
>>>          ^ aScriptEditor!
>>>
>>> Item was changed:
>>>   ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
>>>   initializePreferencePanel: aPanel in: aPasteUpMorph
>>>          "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.  Also used to reset it after some change requires reformulation"
>>>   
>>>          | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent  prefObjects |
>>>          aPasteUpMorph removeAllMorphs.
>>>   
>>>          aFont := Preferences standardListFont.
>>> +        aColor := aPanel windowColorToUse.
>>> -        aColor := aPanel defaultBackgroundColor.
>>>          tabbedPalette := TabbedPalette newSticky.
>>>          tabbedPalette dropEnabled: false.
>>>          (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
>>>                   highlightColor: Color red regularColor: Color brown darker darker.
>>>          tabbedPalette on: #mouseDown send: #yourself to: #().
>>>          maxEntriesPerCategory := 0.
>>>          self listOfCategories do:
>>>                  [:aCat |
>>>                          controlPage := AlignmentMorph newColumn beSticky color: aColor.
>>>                          controlPage on: #mouseDown send: #yourself to: #().
>>>                          controlPage dropEnabled: false.
>>>                          controlPage borderColor: aColor;
>>>                                   layoutInset: 4.
>>>                          (prefObjects := self preferenceObjectsInCategory: aCat) do:
>>>                                  [:aPreference | | button |
>>>                                          button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
>>>                                          button ifNotNil: [controlPage addMorphBack: button]].
>>>                          controlPage setNameTo: aCat asString.
>>>                          aCat = #?
>>>                                  ifTrue: [aPanel addHelpItemsTo: controlPage].
>>>                          tabbedPalette addTabFor: controlPage font: aFont.
>>>                          aCat = 'search results' ifTrue:
>>>                                  [(tabbedPalette tabNamed: aCat) setBalloonText:
>>>                                          'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
>>>                  maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
>>>          tabbedPalette selectTabNamed: '?'.
>>>          tabsMorph rowsNoWiderThan: aPasteUpMorph width.
>>>          aPasteUpMorph on: #mouseDown send: #yourself to: #().
>>>          anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
>>>          aPasteUpMorph extent: anExtent.
>>>          aPasteUpMorph color: aColor.
>>>          aPasteUpMorph     addMorphBack: tabbedPalette.!
>>>
>>> Item was changed:
>>>   ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
>>>   autoFitOnOff
>>>          "Toggle between auto fit to size of code and manual resize with scrolling"
>>>          | tw |
>>> +        (tw := self findA: ScrollPane) ifNil: [^ self].
>>> -        (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
>>>          (self hasProperty: #autoFitContents)
>>>                  ifTrue: [self removeProperty: #autoFitContents.
>>>                          self hResizing: #rigid; vResizing: #rigid]
>>>                  ifFalse: [self setProperty: #autoFitContents toValue: true.
>>>                          self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
>>>          tw layoutChanged!
>>>
>>> Item was changed:
>>>   ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
>>>   extent: x
>>>   
>>>          | newExtent tw menu |
>>>          newExtent := x max: self minWidth @ self minHeight.
>>> +        (tw := self findA: ScrollPane) ifNil:
>>> -        (tw := self findA: TwoWayScrollPane) ifNil:
>>>                  ["This was the old behavior"
>>>                  ^ super extent: newExtent].
>>>   
>>>          (self hasProperty: #autoFitContents) ifTrue: [
>>>                  menu := MenuMorph new defaultTarget: self.
>>>                  menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
>>>                  menu addTitle: 'To resize the script, uncheck the box below' translated.
>>>                  menu popUpEvent: nil in: self world     .
>>>                  ^ self].
>>>   
>>>          "Allow the user to resize to any size"
>>>          tw extent: ((newExtent x max: self firstSubmorph width)
>>>                                  @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).  "inset?"
>>>          ^ super extent: newExtent!
>>>
>>> Item was changed:
>>>   ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
>>>   hibernate
>>>          "Possibly delete the tiles, but only if using universal tiles."
>>>   
>>>          | tw |
>>>          Preferences universalTiles ifFalse: [^self].
>>> +        (tw := self findA: ScrollPane) isNil
>>> -        (tw := self findA: TwoWayScrollPane) isNil
>>>                  ifFalse:
>>>                          [self setProperty: #sizeAtHibernate toValue: self extent.       "+ tw xScrollerHeight"
>>>                          submorphs size > 1 ifTrue: [tw delete]]!
>>>
>>> Item was added:
>>> + ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
>>> + fftSize: aSize
>>> +
>>> +        | on |
>>> +        on := soundInput isRecording.
>>> +        self stop.
>>> +        fft := FFT new: aSize.
>>> +        self resetDisplay.
>>> +        on ifTrue: [self start].!
>>>
>>> Item was changed:
>>>   ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
>>>   setFFTSize
>>>          "Set the size of the FFT used for frequency analysis."
>>>   
>>> +        | aMenu sz |
>>> -        | aMenu sz on |
>>>          aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
>>>          ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
>>>          sz := aMenu startUp.
>>>          sz ifNil: [^ self].
>>> +        self fftSize: sz.!
>>> -        on := soundInput isRecording.
>>> -        self stop.
>>> -        fft := FFT new: sz.
>>> -        self resetDisplay.
>>> -        on ifTrue: [self start].
>>> - !
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
>>>   setSize: oldExtent andMakeResizable: outerMorph
>>>          | tw |
>>> +        (tw := outerMorph findA: ScrollPane) ifNil: [^self].
>>> -        (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
>>>          tw hResizing: #spaceFill;
>>>                  vResizing: #spaceFill;
>>>                  color: Color transparent;
>>>                  setProperty: #hideUnneededScrollbars toValue: true.
>>>          outerMorph
>>>                  hResizing: #shrinkWrap;
>>>                  vResizing: #shrinkWrap;
>>>                  cellPositioning: #topLeft.
>>>          outerMorph fullBounds.
>>>   !
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
>>>   enclosingPane
>>>          "The object that owns this script layout"
>>>   
>>>          | oo higher |
>>>          oo := self owner.
>>>          [higher := oo isSyntaxMorph.
>>>          higher := higher or: [oo class == TransformMorph].
>>> +        higher := higher or: [oo class == ScrollPane].
>>> -        higher := higher or: [oo class == TwoWayScrollPane].
>>>          higher ifFalse: [^ oo].
>>>          higher] whileTrue: [oo := oo owner].
>>>   !
>>>
>>> Item was removed:
>>> - ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
>>> - inAScrollPane
>>> -        "Answer a scroll pane in which the receiver is scrollable"
>>> -
>>> -        ^ self inATwoWayScrollPane!
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
>>>   openInWindow
>>>   
>>> +        | sel |
>>> -        | window widget sel |
>>>          sel := ''.
>>>          self firstSubmorph allMorphs do: [:rr |
>>> +                (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
>>> -                        (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
>>> -        window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
>>> -        widget := self inAScrollPane.
>>> -        widget color: Color paleOrange.
>>> -        window
>>> -                addMorph: widget
>>> -                frame: (0@0 extent: 1.0@1.0).
>>> -        window openInWorldExtent: (
>>> -                self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
>>> -        )
>>>   
>>> +        ^ self inAScrollPane
>>> +                color: Color paleOrange;
>>> +                openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
>>> - !
>>>
>>> Item was added:
>>> + ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
>>> + parseNodeWith: encoder asStatement: aBoolean
>>> +
>>> +        ^ self parseNode!
>>>
>>> Item was changed:
>>>   ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
>>>   unhighlightBorder
>>>   
>>>          self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
>>> +                (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
>>> +                        ifFalse: [self borderColor: self stdBorderColor]
>>> +                        ifTrue: [
>>> +                                (self hasProperty: #deselectedBorderColor)
>>> +                                        ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
>>> +                                        ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
>>> -                self borderColor: (
>>> -                        (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
>>> -                                ifFalse: [self borderColor: self stdBorderColor]
>>> -                                ifTrue: [
>>> -                                        (self hasProperty: #deselectedBorderColor)
>>> -                                                ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
>>> -                                                ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!
>>>
>>> Item was changed:
>>>   ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
>>>   wrapPhraseInFunction
>>>          "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.  This applies for the moment only to numeric functions"
>>>   
>>>          | pad newPad functionPhrase |
>>>          pad := self ownerThatIsA: TilePadMorph.  "Or something higher than that???"
>>>          (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
>>>          newPad := TilePadMorph new setType: #Number.
>>> +        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
>>> -        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
>>>          functionPhrase := FunctionTile new.
>>>          newPad addMorphBack: functionPhrase.
>>>          pad owner replaceSubmorph: pad by: newPad.
>>>          functionPhrase operator: #abs pad: pad.
>>>          functionPhrase addSuffixArrow.
>>>          self scriptEdited
>>>   !
>>>
>>> Item was changed:
>>>   ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
>>>   wrapInFunction
>>>          "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
>>>   
>>>          | newPad functionPhrase |
>>>          newPad := TilePadMorph new setType: #Number.
>>> +        newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
>>> -        newPad hResizing: #shrinkWrap; vResizing: #spacefill.
>>>          functionPhrase := FunctionTile new.
>>>          newPad addMorphBack: functionPhrase.
>>>          owner replaceSubmorph: self by: newPad.
>>>          functionPhrase operator: #abs pad: self.
>>>          self scriptEdited!
>>>
>>> Item was changed:
>>>   ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
>>>   asMorphicSyntaxIn: parent
>>>   
>>>          ^ parent addToken: self name
>>>                          type: #variable
>>> +                        on: self shallowCopy    "don't hand out the prototype!! See VariableNode>>initialize"
>>> -                        on: self clone  "don't hand out the prototype!! See VariableNode>>initialize"
>>>   !
>>>
>>> Item was changed:
>>> + ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
>>> - ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
>>>   fontName: aString bgColor: aColor centerColor: otherColor
>>>          ^ self new
>>>                  fontName: aString;
>>>                  color: aColor;
>>>                  centerColor: otherColor!
>>>
>>> Item was changed:
>>>   ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
>>>   test2
>>>          "WorldWindow test2."
>>>   
>>>          | window world scrollPane |
>>>          world := WiWPasteUpMorph newWorldForProject: nil.
>>>          window := (WorldWindow labelled: 'Scrollable World') model: world.
>>> +        window addMorph: (scrollPane := ScrollPane new model: world)
>>> -        window addMorph: (scrollPane := TwoWayScrollPane new model: world)
>>>                  frame: (0@0 extent: 1.0@1.0).
>>>          scrollPane scroller addMorph: world.
>>>          world hostWindow: window.
>>>          window openInWorld
>>>   !
>>>
>>>
>>
>





Reply | Threaded
Open this post in threaded view
|

Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

David T. Lewis
In reply to this post by marcel.taeumel
Changing the subject line.

Small commits do generate more noise, but I find that it is
easier to read, assess, and manage the changes if the commits
are small. I have spent a good deal of time doing this for
http://www.squeaksource.com/TrunkUpdateStreamV3 and my perspective
is based largely on that experience.

If I were to point to something in need of improvement, I would say
that is the performance of our Monticello tools.

I *love* having the MC change management directly in the image where
everything is directly accessible, browseable, and minimally dependent
on external tools. But I have to admit that the tools are slow.
Processing the update stream is slow, comparing versions is slow,
and reading packages is slow. And I strongly suspect that if all of
these things were instantaniously fast, then none of us would care
about how big or small the commits were.

I may be wrong, but I have to suspect that some profiling of common
use cases, such as updating Squeak from the server, might identify
some huge opportunities for improvement.

But even if those improvements never happen, I think that small
commits are a good thing.

Dave


On Thu, Nov 14, 2019 at 09:32:51AM +0100, Marcel Taeumel wrote:

> > ...??piddly little fixes ...
> > ... such small changes are not worth burdening everyone's life ...
> > ...????tiny improvements ...
>
> Since I merged those commits and had to read and asses them, I can say that the granularity of them was fine. Except for that one duplication for the help in Freecell.
>
> Let's focus on "recategorize methods". Yes, one could easily do that when fixing another issue. Unless it is a bigger quest such as Patrick's (pre) recent efforts to clean up lots of categories across classes.
>
> Best,
> Marcel
> Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:
> Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes??? Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.?? ??Please let that sink in for a moment.
>
> Even ignoring that, it also bloats the readability of the history.?? There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.
>
> Best,
> ?? Chris
>
> On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email] [mailto:[hidden email]]> wrote:
>
> Hi Christoph,
>
> I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.
>
> Best,
> Marcel
> Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email] [mailto:[hidden email]]>:
> Just for interest, is it usual & desired behavior that when installing these updates, the update??log does not include??any of my commit messages?
> Von: Squeak-dev <[hidden email] [mailto:[hidden email]]> im Auftrag von [hidden email] [mailto:[hidden email]] <[hidden email] [mailto:[hidden email]]>
> Gesendet: Mittwoch, 13. November 2019 12:15:14
> An: [hidden email] [mailto:[hidden email]]; [hidden email] [mailto:[hidden email]]
> Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
> ??
> Marcel Taeumel uploaded a new version of EToys to project The Trunk:
> http://source.squeak.org/trunk/EToys-mt.368.mcz [http://source.squeak.org/trunk/EToys-mt.368.mcz]
>
> ==================== Summary ====================
>
> Name: EToys-mt.368
> Author: mt
> Time: 13 November 2019, 12:15:07.673043 pm
> UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
> Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367
>
> Merge! Merge! Merge! Various fixes in Etoys-related places.
>
> =============== Diff against EToys-kfr.363 ===============
>
> Item was added:
> + ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
> + scaledToWidth: newWidth
> +?????????????? "Answer the receiver, scaled such that it has the desired width."
> +
> +?????????????? newWidth = self width ifTrue: [^ self].
> +?????????????? ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
> + !
>
> Item was changed:
> ?? ----- Method: FreeCell>>help (in category 'actions') -----
> ?? help
> +
> +?????????????? self helpText editWithLabel: 'FreeCell Help'.!
> -?????????????? | window helpMorph |
> -?????????????? window := SystemWindow labelled: 'FreeCell Help' translated.
> -?????????????? window model: self.
> -?????????????? helpMorph := (PluggableTextMorph new editString: self helpText) lock.
> -?????????????? window
> -?????????????????????????????? addMorph: helpMorph
> -?????????????????????????????? frame: (0 @ 0 extent: 1 @ 1).
> -?????????????? window openInWorld!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
> + color: aColor
> +
> +?????????????? super color: aColor.
> +??????????????
> +?????????????? "Migrate old instances."
> +?????????????? inner color: Color transparent.
> +??????????????
> +?????????????? "Keep iris visible."
> +?????????????? aColor = iris color
> +?????????????????????????????? ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
> +?????????????????????????????? ifFalse: [iris borderWidth: 0].!
>
> Item was changed:
> ?? ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
> ?? initialize
> ???????????????? "initialize the state of the receiver"
> ???????????????? super initialize.
> ???????????????? ""
> ???????????????? inner := EllipseMorph new.
> +?????????????? inner color: Color transparent.
> -?????????????? inner color: self color.
> ???????????????? inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
> -?????????????? inner borderColor: self color.
> ???????????????? inner borderWidth: 0.
> ?? ""
> ???????????????? iris := EllipseMorph new.
> ???????????????? iris color: Color white.
> ???????????????? iris extent: (self extent * IrisSize) asIntegerPoint.
> ?? ""
> ???????????????? self addMorphCentered: inner.
> ???????????????? inner addMorphCentered: iris.
> ?? ""
> ???????????????? self extent: 26 @ 33!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
> + irisColor
> +
> +?????????????? ^ iris color!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
> + irisColor: aColor
> +
> +?????????????? iris color: aColor.
> +??????????????
> +?????????????? "Keep iris visible."
> +?????????????? aColor = self color
> +?????????????????????????????? ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
> +?????????????????????????????? ifFalse: [iris borderWidth: 0].!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
> + irisPos
> +
> +?????????????? ^ iris position!
>
> Item was changed:
> + ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
> - ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
> ?? irisPos: cp
> ??
> ???????????????? | a b theta x y |
> ???????????????? theta := (cp - self center) theta.
> ???????????????? a := inner width // 2.
> ???????????????? b := inner height // 2.
> ???????????????? x := a * (theta cos).
> ???????????????? y := b * (theta sin).
> ???????????????? iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!
>
> Item was changed:
> ?? ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
> ?? step
> ???????????????? | cp |
> ???????????????? cp := self globalPointToLocal: self world primaryHand position.
> ???????????????? (inner containsPoint: cp)
> ???????????????????????????????? ifTrue: [iris position: (cp - (iris extent // 2))]
> +?????????????????????????????? ifFalse: [self irisPos: cp].!
> -?????????????????????????????? ifFalse: [self irisPos: cp].
> -?????????????? self changed "cover up gribblies if embedded in Flash"!
>
> Item was changed:
> ?? ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
> ?? decimalPlaces
> ???????????????? ^ decimalPlacesButton
> ???????????????????????????????? ifNil: [Utilities
> ???????????????????????????????????????????????????????????????? decimalPlacesForFloatPrecision: (self targetPlayer
> +?????????????????????????????????????????????????????????????????????????????? defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
> -?????????????????????????????????????????????????????????????????????????????? defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
> ???????????????????????????????? ifNotNil: [:button| button label asNumber]!
>
> Item was changed:
> ?? ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
> ?? newScriptorAround: aPhrase
> ???????????????? "Sprout a scriptor around aPhrase, thus making a new script.?? aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
> ??
> ???????????????? | aScriptEditor aUniclassScript tw blk |
> ?? Cursor wait showWhile: [
> ???????????????? aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
> ???????????????? aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
> ??
> ???????????????? Preferences universalTiles ifTrue: [
> ???????????????????????????????? aScriptEditor install.
> ???????????????????????????????? "aScriptEditor hResizing: #shrinkWrap;
> ???????????????????????????????????????????????? vResizing: #shrinkWrap;
> ???????????????????????????????????????????????? cellPositioning: #topLeft;
> ???????????????????????????????????????????????? setProperty: #autoFitContents toValue: true."
> ???????????????????????????????? aScriptEditor insertUniversalTiles.?? "Gets an empty SyntaxMorph for a MethodNode"
> +?????????????????????????????? tw := aScriptEditor findA: ScrollPane.
> -?????????????????????????????? tw := aScriptEditor findA: TwoWayScrollPane.
> ???????????????????????????????? aPhrase ifNotNil:
> ???????????????????????????????????????????????? [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
> ???????????????????????????????????????????????? blk addMorphFront: aPhrase.
> ???????????????????????????????????????????????? aPhrase accept.
> ???????????????????????????????? ].
> ???????????????????????????????? SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
> ???????????????? ] ifFalse: [
> ???????????????????????????????? aPhrase
> ???????????????????????????????????????????????????????????????? ifNotNil: [aScriptEditor phrase: aPhrase]???????????? "does an install"
> ???????????????????????????????????????????????????????????????? ifNil: [aScriptEditor install]
> ???????????????? ].
> ???????????????? self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
> ???????????????????????????????? "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
> ???????????????? self updateScriptsCategoryOfViewers.
> ?? ].
> ???????????????? ^ aScriptEditor!
>
> Item was changed:
> ?? ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
> ?? initializePreferencePanel: aPanel in: aPasteUpMorph
> ???????????????? "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.?? Also used to reset it after some change requires reformulation"
> ??
> ???????????????? | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent?? prefObjects |
> ???????????????? aPasteUpMorph removeAllMorphs.
> ??
> ???????????????? aFont := Preferences standardListFont.
> +?????????????? aColor := aPanel windowColorToUse.
> -?????????????? aColor := aPanel defaultBackgroundColor.
> ???????????????? tabbedPalette := TabbedPalette newSticky.
> ???????????????? tabbedPalette dropEnabled: false.
> ???????????????? (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
> ?????????????????????????????????? highlightColor: Color red regularColor: Color brown darker darker.
> ???????????????? tabbedPalette on: #mouseDown send: #yourself to: #().
> ???????????????? maxEntriesPerCategory := 0.
> ???????????????? self listOfCategories do:
> ???????????????????????????????? [:aCat |
> ???????????????????????????????????????????????? controlPage := AlignmentMorph newColumn beSticky color: aColor.
> ???????????????????????????????????????????????? controlPage on: #mouseDown send: #yourself to: #().
> ???????????????????????????????????????????????? controlPage dropEnabled: false.
> ???????????????????????????????????????????????? controlPage borderColor: aColor;
> ?????????????????????????????????????????????????????????????????? layoutInset: 4.
> ???????????????????????????????????????????????? (prefObjects := self preferenceObjectsInCategory: aCat) do:
> ???????????????????????????????????????????????????????????????? [:aPreference | | button |
> ???????????????????????????????????????????????????????????????????????????????? button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
> ???????????????????????????????????????????????????????????????????????????????? button ifNotNil: [controlPage addMorphBack: button]].
> ???????????????????????????????????????????????? controlPage setNameTo: aCat asString.
> ???????????????????????????????????????????????? aCat = #?
> ???????????????????????????????????????????????????????????????? ifTrue: [aPanel addHelpItemsTo: controlPage].
> ???????????????????????????????????????????????? tabbedPalette addTabFor: controlPage font: aFont.
> ???????????????????????????????????????????????? aCat = 'search results' ifTrue:
> ???????????????????????????????????????????????????????????????? [(tabbedPalette tabNamed: aCat) setBalloonText:
> ???????????????????????????????????????????????????????????????????????????????? 'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
> ???????????????????????????????? maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
> ???????????????? tabbedPalette selectTabNamed: '?'.
> ???????????????? tabsMorph rowsNoWiderThan: aPasteUpMorph width.
> ???????????????? aPasteUpMorph on: #mouseDown send: #yourself to: #().
> ???????????????? anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
> ???????????????? aPasteUpMorph extent: anExtent.
> ???????????????? aPasteUpMorph color: aColor.
> ???????????????? aPasteUpMorph???????? addMorphBack: tabbedPalette.!
>
> Item was changed:
> ?? ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
> ?? autoFitOnOff
> ???????????????? "Toggle between auto fit to size of code and manual resize with scrolling"
> ???????????????? | tw |
> +?????????????? (tw := self findA: ScrollPane) ifNil: [^ self].
> -?????????????? (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
> ???????????????? (self hasProperty: #autoFitContents)
> ???????????????????????????????? ifTrue: [self removeProperty: #autoFitContents.
> ???????????????????????????????????????????????? self hResizing: #rigid; vResizing: #rigid]
> ???????????????????????????????? ifFalse: [self setProperty: #autoFitContents toValue: true.
> ???????????????????????????????????????????????? self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
> ???????????????? tw layoutChanged!
>
> Item was changed:
> ?? ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
> ?? extent: x
> ??
> ???????????????? | newExtent tw menu |
> ???????????????? newExtent := x max: self minWidth @ self minHeight.
> +?????????????? (tw := self findA: ScrollPane) ifNil:
> -?????????????? (tw := self findA: TwoWayScrollPane) ifNil:
> ???????????????????????????????? ["This was the old behavior"
> ???????????????????????????????? ^ super extent: newExtent].
> ??
> ???????????????? (self hasProperty: #autoFitContents) ifTrue: [
> ???????????????????????????????? menu := MenuMorph new defaultTarget: self.
> ???????????????????????????????? menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
> ???????????????????????????????? menu addTitle: 'To resize the script, uncheck the box below' translated.
> ???????????????????????????????? menu popUpEvent: nil in: self world???????? .
> ???????????????????????????????? ^ self].
> ??
> ???????????????? "Allow the user to resize to any size"
> ???????????????? tw extent: ((newExtent x max: self firstSubmorph width)
> ???????????????????????????????????????????????????????????????? @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).?? "inset?"
> ???????????????? ^ super extent: newExtent!
>
> Item was changed:
> ?? ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
> ?? hibernate
> ???????????????? "Possibly delete the tiles, but only if using universal tiles."
> ??
> ???????????????? | tw |
> ???????????????? Preferences universalTiles ifFalse: [^self].
> +?????????????? (tw := self findA: ScrollPane) isNil
> -?????????????? (tw := self findA: TwoWayScrollPane) isNil
> ???????????????????????????????? ifFalse:
> ???????????????????????????????????????????????? [self setProperty: #sizeAtHibernate toValue: self extent.???????????? "+ tw xScrollerHeight"
> ???????????????????????????????????????????????? submorphs size > 1 ifTrue: [tw delete]]!
>
> Item was added:
> + ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
> + fftSize: aSize
> +
> +?????????????? | on |
> +?????????????? on := soundInput isRecording.
> +?????????????? self stop.
> +?????????????? fft := FFT new: aSize.
> +?????????????? self resetDisplay.
> +?????????????? on ifTrue: [self start].!
>
> Item was changed:
> ?? ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
> ?? setFFTSize
> ???????????????? "Set the size of the FFT used for frequency analysis."
> ??
> +?????????????? | aMenu sz |
> -?????????????? | aMenu sz on |
> ???????????????? aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
> ???????????????? ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
> ???????????????? sz := aMenu startUp.
> ???????????????? sz ifNil: [^ self].
> +?????????????? self fftSize: sz.!
> -?????????????? on := soundInput isRecording.
> -?????????????? self stop.
> -?????????????? fft := FFT new: sz.
> -?????????????? self resetDisplay.
> -?????????????? on ifTrue: [self start].
> - !
>
> Item was changed:
> ?? ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
> ?? setSize: oldExtent andMakeResizable: outerMorph
> ???????????????? | tw |
> +?????????????? (tw := outerMorph findA: ScrollPane) ifNil: [^self].
> -?????????????? (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
> ???????????????? tw hResizing: #spaceFill;
> ???????????????????????????????? vResizing: #spaceFill;
> ???????????????????????????????? color: Color transparent;
> ???????????????????????????????? setProperty: #hideUnneededScrollbars toValue: true.
> ???????????????? outerMorph
> ???????????????????????????????? hResizing: #shrinkWrap;
> ???????????????????????????????? vResizing: #shrinkWrap;
> ???????????????????????????????? cellPositioning: #topLeft.
> ???????????????? outerMorph fullBounds.
> ?? !
>
> Item was changed:
> ?? ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
> ?? enclosingPane
> ???????????????? "The object that owns this script layout"
> ??
> ???????????????? | oo higher |
> ???????????????? oo := self owner.
> ???????????????? [higher := oo isSyntaxMorph.
> ???????????????? higher := higher or: [oo class == TransformMorph].
> +?????????????? higher := higher or: [oo class == ScrollPane].
> -?????????????? higher := higher or: [oo class == TwoWayScrollPane].
> ???????????????? higher ifFalse: [^ oo].
> ???????????????? higher] whileTrue: [oo := oo owner].
> ?? !
>
> Item was removed:
> - ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
> - inAScrollPane
> -?????????????? "Answer a scroll pane in which the receiver is scrollable"
> -
> -?????????????? ^ self inATwoWayScrollPane!
>
> Item was changed:
> ?? ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
> ?? openInWindow
> ??
> +?????????????? | sel |
> -?????????????? | window widget sel |
> ???????????????? sel := ''.
> ???????????????? self firstSubmorph allMorphs do: [:rr |
> +?????????????????????????????? (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
> -?????????????????????????????????????????????? (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
> -?????????????? window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
> -?????????????? widget := self inAScrollPane.
> -?????????????? widget color: Color paleOrange.
> -?????????????? window
> -?????????????????????????????? addMorph: widget
> -?????????????????????????????? frame: (0@0 extent: 1.0@1.0).
> -?????????????? window openInWorldExtent: (
> -?????????????????????????????? self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
> -?????????????? )
> ??
> +?????????????? ^ self inAScrollPane
> +?????????????????????????????? color: Color paleOrange;
> +?????????????????????????????? openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
> - !
>
> Item was added:
> + ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
> + parseNodeWith: encoder asStatement: aBoolean
> +
> +?????????????? ^ self parseNode!
>
> Item was changed:
> ?? ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
> ?? unhighlightBorder
> ??
> ???????????????? self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
> +?????????????????????????????? (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
> +?????????????????????????????????????????????? ifFalse: [self borderColor: self stdBorderColor]
> +?????????????????????????????????????????????? ifTrue: [
> +?????????????????????????????????????????????????????????????? (self hasProperty: #deselectedBorderColor)
> +?????????????????????????????????????????????????????????????????????????????? ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
> +?????????????????????????????????????????????????????????????????????????????? ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
> -?????????????????????????????? self borderColor: (
> -?????????????????????????????????????????????? (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
> -?????????????????????????????????????????????????????????????? ifFalse: [self borderColor: self stdBorderColor]
> -?????????????????????????????????????????????????????????????? ifTrue: [
> -?????????????????????????????????????????????????????????????????????????????? (self hasProperty: #deselectedBorderColor)
> -?????????????????????????????????????????????????????????????????????????????????????????????? ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
> -?????????????????????????????????????????????????????????????????????????????????????????????? ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!
>
> Item was changed:
> ?? ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
> ?? wrapPhraseInFunction
> ???????????????? "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.?? This applies for the moment only to numeric functions"
> ??
> ???????????????? | pad newPad functionPhrase |
> ???????????????? pad := self ownerThatIsA: TilePadMorph.?? "Or something higher than that???"
> ???????????????? (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
> ???????????????? newPad := TilePadMorph new setType: #Number.
> +?????????????? newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
> -?????????????? newPad hResizing: #shrinkWrap; vResizing: #spacefill.
> ???????????????? functionPhrase := FunctionTile new.
> ???????????????? newPad addMorphBack: functionPhrase.
> ???????????????? pad owner replaceSubmorph: pad by: newPad.
> ???????????????? functionPhrase operator: #abs pad: pad.
> ???????????????? functionPhrase addSuffixArrow.
> ???????????????? self scriptEdited
> ?? !
>
> Item was changed:
> ?? ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
> ?? wrapInFunction
> ???????????????? "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
> ??
> ???????????????? | newPad functionPhrase |
> ???????????????? newPad := TilePadMorph new setType: #Number.
> +?????????????? newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
> -?????????????? newPad hResizing: #shrinkWrap; vResizing: #spacefill.
> ???????????????? functionPhrase := FunctionTile new.
> ???????????????? newPad addMorphBack: functionPhrase.
> ???????????????? owner replaceSubmorph: self by: newPad.
> ???????????????? functionPhrase operator: #abs pad: self.
> ???????????????? self scriptEdited!
>
> Item was changed:
> ?? ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
> ?? asMorphicSyntaxIn: parent
> ??
> ???????????????? ^ parent addToken: self name
> ???????????????????????????????????????????????? type: #variable
> +?????????????????????????????????????????????? on: self shallowCopy?????? "don't hand out the prototype!! See VariableNode>>initialize"
> -?????????????????????????????????????????????? on: self clone?? "don't hand out the prototype!! See VariableNode>>initialize"
> ?? !
>
> Item was changed:
> + ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
> - ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
> ?? fontName: aString bgColor: aColor centerColor: otherColor
> ???????????????? ^ self new
> ???????????????????????????????? fontName: aString;
> ???????????????????????????????? color: aColor;
> ???????????????????????????????? centerColor: otherColor!
>
> Item was changed:
> ?? ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
> ?? test2
> ???????????????? "WorldWindow test2."
> ??
> ???????????????? | window world scrollPane |
> ???????????????? world := WiWPasteUpMorph newWorldForProject: nil.
> ???????????????? window := (WorldWindow labelled: 'Scrollable World') model: world.
> +?????????????? window addMorph: (scrollPane := ScrollPane new model: world)
> -?????????????? window addMorph: (scrollPane := TwoWayScrollPane new model: world)
> ???????????????????????????????? frame: (0@0 extent: 1.0@1.0).
> ???????????????? scrollPane scroller addMorph: world.
> ???????????????? world hostWindow: window.
> ???????????????? window openInWorld
> ?? !
>
>
>

>


Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

Nicolas Cellier
Hi all,
I don't recommend mixing cosmetic changes with functional changes, unless cosmetic changes are really scarce. My experience is that it is a recipe for switching the attention focus out of the functional changes, and as such it is parasiting at best or obstructing at worse the review process.
Also, we should not deny the value of cosmetic changes. They have some value. They require attention and review too, even if they won't break production.

We might want to amend tools. I hate loosing history, and I value the contextual analysis of certain design decision. But the frequency of such incursion into the past is gradually fading away. MC requires history for merging, but merging a too distant branch is becoming close to impossible anyway for human review. I tried it with Pharo some years ago, after repairing the conscious erasing of history that happened at each Pharo release (which is a very aggressive way to solve the problem, the worse-is-better-way)..
So having the whole history in memory is questionable. It's not the whole history, what about Smalltalk 72, 76, 80, the change-set and update stream era... We have to set a limit.

For browsing the history, I don't know what is worse, having a long list of small changes, or shorter list of squashed (in git parlance) unrelated changes. But this should be handled in the interface IMO. If we prefer grouping, this should be done by the browsing tool. For my own usage, it would have helped if the tool could filter the list by date range, modified class, method, pattern matching on commit message, ...

Somehow related, it happens that I group several changes in one commit, I did it recently in VMMaker, one change for solving Newspeak generated code, the other for avoiding generating variable named bool, which were obstructing my attempt to compile legacy Mac OS  carbon VM. I did regret, because the first change introduced a slip in generated code that made the build fail in the branch dedicated to second change... Using CI automation is another reason why we should value separation of concerns. If I want to merge the compile_legacy_MacOS branch, one may ask in the future why the hell the totally unrelated Newspeak change was introduced in this branch. That's an anti-pattern, especially if we use explicitely named feature branches (which we avoid currently in MC, partly for lack of tool support).

Last, MC does not behave so badly. I have far worse user experience using sourcetree on windows for file based projects on a gitlab server where load balancing configuration is not optimal, I can tell you that we should stop bashing ourselves ;)

Le ven. 15 nov. 2019 à 04:39, David T. Lewis <[hidden email]> a écrit :
Changing the subject line.

Small commits do generate more noise, but I find that it is
easier to read, assess, and manage the changes if the commits
are small. I have spent a good deal of time doing this for
http://www.squeaksource.com/TrunkUpdateStreamV3 and my perspective
is based largely on that experience.

If I were to point to something in need of improvement, I would say
that is the performance of our Monticello tools.

I *love* having the MC change management directly in the image where
everything is directly accessible, browseable, and minimally dependent
on external tools. But I have to admit that the tools are slow.
Processing the update stream is slow, comparing versions is slow,
and reading packages is slow. And I strongly suspect that if all of
these things were instantaniously fast, then none of us would care
about how big or small the commits were.

I may be wrong, but I have to suspect that some profiling of common
use cases, such as updating Squeak from the server, might identify
some huge opportunities for improvement.

But even if those improvements never happen, I think that small
commits are a good thing.

Dave


On Thu, Nov 14, 2019 at 09:32:51AM +0100, Marcel Taeumel wrote:
> > ...??piddly little fixes ...
> > ... such small changes are not worth burdening everyone's life ...
> > ...????tiny improvements ...
>
> Since I merged those commits and had to read and asses them, I can say that the granularity of them was fine. Except for that one duplication for the help in Freecell.
>
> Let's focus on "recategorize methods". Yes, one could easily do that when fixing another issue. Unless it is a bigger quest such as Patrick's (pre) recent efforts to clean up lots of categories across classes.
>
> Best,
> Marcel
> Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:
> Guys, would you please consider "batching up" piddly little fixes like "recatgorized one method" this into fewer, chunkier commits with other fixes??? Such small changes are not worth burdening everyone's life with an additional 2MB of memory, disk, network and CPU overhead -- in *every single image* they use going forward, forever.?? ??Please let that sink in for a moment.
>
> Even ignoring that, it also bloats the readability of the history.?? There's no use case where timestamping and versioning tiny improvements like this is useful, only micro harmful.
>
> Best,
> ?? Chris
>
> On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email] [mailto:[hidden email]]> wrote:
>
> Hi Christoph,
>
> I know. We should come up with a solution for that. Maybe re-print the commit messages of all ancestors as soon as the number of ancestors is > 1.
>
> Best,
> Marcel
> Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <[hidden email] [mailto:[hidden email]]>:
> Just for interest, is it usual & desired behavior that when installing these updates, the update??log does not include??any of my commit messages?
> Von: Squeak-dev <[hidden email] [mailto:[hidden email]]> im Auftrag von [hidden email] [mailto:[hidden email]] <[hidden email] [mailto:[hidden email]]>
> Gesendet: Mittwoch, 13. November 2019 12:15:14
> An: [hidden email] [mailto:[hidden email]]; [hidden email] [mailto:[hidden email]]
> Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
> ??
> Marcel Taeumel uploaded a new version of EToys to project The Trunk:
> http://source.squeak.org/trunk/EToys-mt.368.mcz [http://source.squeak.org/trunk/EToys-mt.368.mcz]
>
> ==================== Summary ====================
>
> Name: EToys-mt.368
> Author: mt
> Time: 13 November 2019, 12:15:07.673043 pm
> UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
> Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356, EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364, EToys-ct.365, EToys-ct.367
>
> Merge! Merge! Merge! Various fixes in Etoys-related places.
>
> =============== Diff against EToys-kfr.363 ===============
>
> Item was added:
> + ----- Method: Form>>scaledToWidth: (in category '*Etoys-Squeakland-scaling, rotation') -----
> + scaledToWidth: newWidth
> +?????????????? "Answer the receiver, scaled such that it has the desired width."
> +
> +?????????????? newWidth = self width ifTrue: [^ self].
> +?????????????? ^self magnify: self boundingBox by: (newWidth / self width) smoothing: 2.
> + !
>
> Item was changed:
> ?? ----- Method: FreeCell>>help (in category 'actions') -----
> ?? help
> +
> +?????????????? self helpText editWithLabel: 'FreeCell Help'.!
> -?????????????? | window helpMorph |
> -?????????????? window := SystemWindow labelled: 'FreeCell Help' translated.
> -?????????????? window model: self.
> -?????????????? helpMorph := (PluggableTextMorph new editString: self helpText) lock.
> -?????????????? window
> -?????????????????????????????? addMorph: helpMorph
> -?????????????????????????????? frame: (0 @ 0 extent: 1 @ 1).
> -?????????????? window openInWorld!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
> + color: aColor
> +
> +?????????????? super color: aColor.
> +??????????????
> +?????????????? "Migrate old instances."
> +?????????????? inner color: Color transparent.
> +??????????????
> +?????????????? "Keep iris visible."
> +?????????????? aColor = iris color
> +?????????????????????????????? ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
> +?????????????????????????????? ifFalse: [iris borderWidth: 0].!
>
> Item was changed:
> ?? ----- Method: MovingEyeMorph>>initialize (in category 'initialization') -----
> ?? initialize
> ???????????????? "initialize the state of the receiver"
> ???????????????? super initialize.
> ???????????????? ""
> ???????????????? inner := EllipseMorph new.
> +?????????????? inner color: Color transparent.
> -?????????????? inner color: self color.
> ???????????????? inner extent: (self extent * (1.0 @ 1.0 - IrisSize)) asIntegerPoint.
> -?????????????? inner borderColor: self color.
> ???????????????? inner borderWidth: 0.
> ?? ""
> ???????????????? iris := EllipseMorph new.
> ???????????????? iris color: Color white.
> ???????????????? iris extent: (self extent * IrisSize) asIntegerPoint.
> ?? ""
> ???????????????? self addMorphCentered: inner.
> ???????????????? inner addMorphCentered: iris.
> ?? ""
> ???????????????? self extent: 26 @ 33!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
> + irisColor
> +
> +?????????????? ^ iris color!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing') -----
> + irisColor: aColor
> +
> +?????????????? iris color: aColor.
> +??????????????
> +?????????????? "Keep iris visible."
> +?????????????? aColor = self color
> +?????????????????????????????? ifTrue: [iris borderWidth: 1; borderColor: aColor negated]
> +?????????????????????????????? ifFalse: [iris borderWidth: 0].!
>
> Item was added:
> + ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
> + irisPos
> +
> +?????????????? ^ iris position!
>
> Item was changed:
> + ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
> - ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet unclassified') -----
> ?? irisPos: cp
> ??
> ???????????????? | a b theta x y |
> ???????????????? theta := (cp - self center) theta.
> ???????????????? a := inner width // 2.
> ???????????????? b := inner height // 2.
> ???????????????? x := a * (theta cos).
> ???????????????? y := b * (theta sin).
> ???????????????? iris position: ((x@y) asIntegerPoint) + self center - (iris extent // 2).!
>
> Item was changed:
> ?? ----- Method: MovingEyeMorph>>step (in category 'stepping and presenter') -----
> ?? step
> ???????????????? | cp |
> ???????????????? cp := self globalPointToLocal: self world primaryHand position.
> ???????????????? (inner containsPoint: cp)
> ???????????????????????????????? ifTrue: [iris position: (cp - (iris extent // 2))]
> +?????????????????????????????? ifFalse: [self irisPos: cp].!
> -?????????????????????????????? ifFalse: [self irisPos: cp].
> -?????????????? self changed "cover up gribblies if embedded in Flash"!
>
> Item was changed:
> ?? ----- Method: NewVariableDialogMorph>>decimalPlaces (in category 'accessing') -----
> ?? decimalPlaces
> ???????????????? ^ decimalPlacesButton
> ???????????????????????????????? ifNil: [Utilities
> ???????????????????????????????????????????????????????????????? decimalPlacesForFloatPrecision: (self targetPlayer
> +?????????????????????????????????????????????????????????????????????????????? defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
> -?????????????????????????????????????????????????????????????????????????????? defaultFloatPrecisionFor: (Utilities getterSelectorFor: self varAcceptableName))]
> ???????????????????????????????? ifNotNil: [:button| button label asNumber]!
>
> Item was changed:
> ?? ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
> ?? newScriptorAround: aPhrase
> ???????????????? "Sprout a scriptor around aPhrase, thus making a new script.?? aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001) or a SyntaxMorph (2001 onward)"
> ??
> ???????????????? | aScriptEditor aUniclassScript tw blk |
> ?? Cursor wait showWhile: [
> ???????????????? aUniclassScript := self class permanentUserScriptFor: self unusedScriptName player: self.
> ???????????????? aScriptEditor := aUniclassScript instantiatedScriptEditorForPlayer: self.
> ??
> ???????????????? Preferences universalTiles ifTrue: [
> ???????????????????????????????? aScriptEditor install.
> ???????????????????????????????? "aScriptEditor hResizing: #shrinkWrap;
> ???????????????????????????????????????????????? vResizing: #shrinkWrap;
> ???????????????????????????????????????????????? cellPositioning: #topLeft;
> ???????????????????????????????????????????????? setProperty: #autoFitContents toValue: true."
> ???????????????????????????????? aScriptEditor insertUniversalTiles.?? "Gets an empty SyntaxMorph for a MethodNode"
> +?????????????????????????????? tw := aScriptEditor findA: ScrollPane.
> -?????????????????????????????? tw := aScriptEditor findA: TwoWayScrollPane.
> ???????????????????????????????? aPhrase ifNotNil:
> ???????????????????????????????????????????????? [blk := (tw scroller findA: SyntaxMorph "MethodNode") findA: BlockNode.
> ???????????????????????????????????????????????? blk addMorphFront: aPhrase.
> ???????????????????????????????????????????????? aPhrase accept.
> ???????????????????????????????? ].
> ???????????????????????????????? SyntaxMorph setSize: nil andMakeResizable: aScriptEditor.
> ???????????????? ] ifFalse: [
> ???????????????????????????????? aPhrase
> ???????????????????????????????????????????????????????????????? ifNotNil: [aScriptEditor phrase: aPhrase]???????????? "does an install"
> ???????????????????????????????????????????????????????????????? ifNil: [aScriptEditor install]
> ???????????????? ].
> ???????????????? self class allSubInstancesDo: [:anInst | anInst scriptInstantiationForSelector: aUniclassScript selector].
> ???????????????????????????????? "The above assures the presence of a ScriptInstantiation for the new selector in all siblings"
> ???????????????? self updateScriptsCategoryOfViewers.
> ?? ].
> ???????????????? ^ aScriptEditor!
>
> Item was changed:
> ?? ----- Method: Preferences class>>initializePreferencePanel:in: (in category '*Etoys-Squeakland-preferences panel') -----
> ?? initializePreferencePanel: aPanel in: aPasteUpMorph
> ???????????????? "Initialize the given Preferences panel. in the given pasteup, which is the top-level panel installed in the container window.?? Also used to reset it after some change requires reformulation"
> ??
> ???????????????? | tabbedPalette controlPage aColor aFont maxEntriesPerCategory tabsMorph anExtent?? prefObjects |
> ???????????????? aPasteUpMorph removeAllMorphs.
> ??
> ???????????????? aFont := Preferences standardListFont.
> +?????????????? aColor := aPanel windowColorToUse.
> -?????????????? aColor := aPanel defaultBackgroundColor.
> ???????????????? tabbedPalette := TabbedPalette newSticky.
> ???????????????? tabbedPalette dropEnabled: false.
> ???????????????? (tabsMorph := tabbedPalette tabsMorph) color: aColor darker;
> ?????????????????????????????????? highlightColor: Color red regularColor: Color brown darker darker.
> ???????????????? tabbedPalette on: #mouseDown send: #yourself to: #().
> ???????????????? maxEntriesPerCategory := 0.
> ???????????????? self listOfCategories do:
> ???????????????????????????????? [:aCat |
> ???????????????????????????????????????????????? controlPage := AlignmentMorph newColumn beSticky color: aColor.
> ???????????????????????????????????????????????? controlPage on: #mouseDown send: #yourself to: #().
> ???????????????????????????????????????????????? controlPage dropEnabled: false.
> ???????????????????????????????????????????????? controlPage borderColor: aColor;
> ?????????????????????????????????????????????????????????????????? layoutInset: 4.
> ???????????????????????????????????????????????? (prefObjects := self preferenceObjectsInCategory: aCat) do:
> ???????????????????????????????????????????????????????????????? [:aPreference | | button |
> ???????????????????????????????????????????????????????????????????????????????? button := aPreference representativeButtonWithColor: Color white inPanel: aPanel.
> ???????????????????????????????????????????????????????????????????????????????? button ifNotNil: [controlPage addMorphBack: button]].
> ???????????????????????????????????????????????? controlPage setNameTo: aCat asString.
> ???????????????????????????????????????????????? aCat = #?
> ???????????????????????????????????????????????????????????????? ifTrue: [aPanel addHelpItemsTo: controlPage].
> ???????????????????????????????????????????????? tabbedPalette addTabFor: controlPage font: aFont.
> ???????????????????????????????????????????????? aCat = 'search results' ifTrue:
> ???????????????????????????????????????????????????????????????? [(tabbedPalette tabNamed: aCat) setBalloonText:
> ???????????????????????????????????????????????????????????????????????????????? 'Use the ? category to find preferences by keyword; the results of your search will show up here' translated].
> ???????????????????????????????? maxEntriesPerCategory := maxEntriesPerCategory max: prefObjects size].
> ???????????????? tabbedPalette selectTabNamed: '?'.
> ???????????????? tabsMorph rowsNoWiderThan: aPasteUpMorph width.
> ???????????????? aPasteUpMorph on: #mouseDown send: #yourself to: #().
> ???????????????? anExtent := aPasteUpMorph width @ (490 max: (25 + tabsMorph height + (24 * maxEntriesPerCategory))).
> ???????????????? aPasteUpMorph extent: anExtent.
> ???????????????? aPasteUpMorph color: aColor.
> ???????????????? aPasteUpMorph???????? addMorphBack: tabbedPalette.!
>
> Item was changed:
> ?? ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu') -----
> ?? autoFitOnOff
> ???????????????? "Toggle between auto fit to size of code and manual resize with scrolling"
> ???????????????? | tw |
> +?????????????? (tw := self findA: ScrollPane) ifNil: [^ self].
> -?????????????? (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
> ???????????????? (self hasProperty: #autoFitContents)
> ???????????????????????????????? ifTrue: [self removeProperty: #autoFitContents.
> ???????????????????????????????????????????????? self hResizing: #rigid; vResizing: #rigid]
> ???????????????????????????????? ifFalse: [self setProperty: #autoFitContents toValue: true.
> ???????????????????????????????????????????????? self hResizing: #shrinkWrap; vResizing: #shrinkWrap].
> ???????????????? tw layoutChanged!
>
> Item was changed:
> ?? ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
> ?? extent: x
> ??
> ???????????????? | newExtent tw menu |
> ???????????????? newExtent := x max: self minWidth @ self minHeight.
> +?????????????? (tw := self findA: ScrollPane) ifNil:
> -?????????????? (tw := self findA: TwoWayScrollPane) ifNil:
> ???????????????????????????????? ["This was the old behavior"
> ???????????????????????????????? ^ super extent: newExtent].
> ??
> ???????????????? (self hasProperty: #autoFitContents) ifTrue: [
> ???????????????????????????????? menu := MenuMorph new defaultTarget: self.
> ???????????????????????????????? menu addUpdating: #autoFitString target: self action: #autoFitOnOff.
> ???????????????????????????????? menu addTitle: 'To resize the script, uncheck the box below' translated.
> ???????????????????????????????? menu popUpEvent: nil in: self world???????? .
> ???????????????????????????????? ^ self].
> ??
> ???????????????? "Allow the user to resize to any size"
> ???????????????? tw extent: ((newExtent x max: self firstSubmorph width)
> ???????????????????????????????????????????????????????????????? @ (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @ -4).?? "inset?"
> ???????????????? ^ super extent: newExtent!
>
> Item was changed:
> ?? ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
> ?? hibernate
> ???????????????? "Possibly delete the tiles, but only if using universal tiles."
> ??
> ???????????????? | tw |
> ???????????????? Preferences universalTiles ifFalse: [^self].
> +?????????????? (tw := self findA: ScrollPane) isNil
> -?????????????? (tw := self findA: TwoWayScrollPane) isNil
> ???????????????????????????????? ifFalse:
> ???????????????????????????????????????????????? [self setProperty: #sizeAtHibernate toValue: self extent.???????????? "+ tw xScrollerHeight"
> ???????????????????????????????????????????????? submorphs size > 1 ifTrue: [tw delete]]!
>
> Item was added:
> + ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category 'accessing') -----
> + fftSize: aSize
> +
> +?????????????? | on |
> +?????????????? on := soundInput isRecording.
> +?????????????? self stop.
> +?????????????? fft := FFT new: aSize.
> +?????????????? self resetDisplay.
> +?????????????? on ifTrue: [self start].!
>
> Item was changed:
> ?? ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu and buttons') -----
> ?? setFFTSize
> ???????????????? "Set the size of the FFT used for frequency analysis."
> ??
> +?????????????? | aMenu sz |
> -?????????????? | aMenu sz on |
> ???????????????? aMenu := CustomMenu new title: ('FFT size (currently {1})' translated format:{fft n}).
> ???????????????? ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r | aMenu add: r printString action: r].
> ???????????????? sz := aMenu startUp.
> ???????????????? sz ifNil: [^ self].
> +?????????????? self fftSize: sz.!
> -?????????????? on := soundInput isRecording.
> -?????????????? self stop.
> -?????????????? fft := FFT new: sz.
> -?????????????? self resetDisplay.
> -?????????????? on ifTrue: [self start].
> - !
>
> Item was changed:
> ?? ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in category 'as yet unclassified') -----
> ?? setSize: oldExtent andMakeResizable: outerMorph
> ???????????????? | tw |
> +?????????????? (tw := outerMorph findA: ScrollPane) ifNil: [^self].
> -?????????????? (tw := outerMorph findA: TwoWayScrollPane) ifNil: [^self].
> ???????????????? tw hResizing: #spaceFill;
> ???????????????????????????????? vResizing: #spaceFill;
> ???????????????????????????????? color: Color transparent;
> ???????????????????????????????? setProperty: #hideUnneededScrollbars toValue: true.
> ???????????????? outerMorph
> ???????????????????????????????? hResizing: #shrinkWrap;
> ???????????????????????????????? vResizing: #shrinkWrap;
> ???????????????????????????????? cellPositioning: #topLeft.
> ???????????????? outerMorph fullBounds.
> ?? !
>
> Item was changed:
> ?? ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing') -----
> ?? enclosingPane
> ???????????????? "The object that owns this script layout"
> ??
> ???????????????? | oo higher |
> ???????????????? oo := self owner.
> ???????????????? [higher := oo isSyntaxMorph.
> ???????????????? higher := higher or: [oo class == TransformMorph].
> +?????????????? higher := higher or: [oo class == ScrollPane].
> -?????????????? higher := higher or: [oo class == TwoWayScrollPane].
> ???????????????? higher ifFalse: [^ oo].
> ???????????????? higher] whileTrue: [oo := oo owner].
> ?? !
>
> Item was removed:
> - ----- Method: SyntaxMorph>>inAScrollPane (in category 'initialization') -----
> - inAScrollPane
> -?????????????? "Answer a scroll pane in which the receiver is scrollable"
> -
> -?????????????? ^ self inATwoWayScrollPane!
>
> Item was changed:
> ?? ----- Method: SyntaxMorph>>openInWindow (in category 'initialization') -----
> ?? openInWindow
> ??
> +?????????????? | sel |
> -?????????????? | window widget sel |
> ???????????????? sel := ''.
> ???????????????? self firstSubmorph allMorphs do: [:rr |
> +?????????????????????????????? (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
> -?????????????????????????????????????????????? (rr isKindOf: StringMorph) ifTrue: [sel := sel, rr contents]].
> -?????????????? window := (SystemWindow labelled: 'Tiles for ', self parsedInClass printString, '>>',sel).
> -?????????????? widget := self inAScrollPane.
> -?????????????? widget color: Color paleOrange.
> -?????????????? window
> -?????????????????????????????? addMorph: widget
> -?????????????????????????????? frame: (0@0 extent: 1.0@1.0).
> -?????????????? window openInWorldExtent: (
> -?????????????????????????????? self extent + (20@40) min: (Display boundingBox extent * 0.8) rounded
> -?????????????? )
> ??
> +?????????????? ^ self inAScrollPane
> +?????????????????????????????? color: Color paleOrange;
> +?????????????????????????????? openInWindowLabeled: 'Tiles for ', self parsedInClass printString, '>>', sel!
> - !
>
> Item was added:
> + ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category '*Etoys-Squeakland-code generation') -----
> + parseNodeWith: encoder asStatement: aBoolean
> +
> +?????????????? ^ self parseNode!
>
> Item was changed:
> ?? ----- Method: SyntaxMorph>>unhighlightBorder (in category 'highlighting') -----
> ?? unhighlightBorder
> ??
> ???????????????? self currentSelectionDo: [:innerMorph :mouseDownLoc :outerMorph |
> +?????????????????????????????? (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
> +?????????????????????????????????????????????? ifFalse: [self borderColor: self stdBorderColor]
> +?????????????????????????????????????????????? ifTrue: [
> +?????????????????????????????????????????????????????????????? (self hasProperty: #deselectedBorderColor)
> +?????????????????????????????????????????????????????????????????????????????? ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
> +?????????????????????????????????????????????????????????????????????????????? ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] ].!
> -?????????????????????????????? self borderColor: (
> -?????????????????????????????????????????????? (self == outerMorph or: [owner notNil and: [owner isSyntaxMorph not]])
> -?????????????????????????????????????????????????????????????? ifFalse: [self borderColor: self stdBorderColor]
> -?????????????????????????????????????????????????????????????? ifTrue: [
> -?????????????????????????????????????????????????????????????????????????????? (self hasProperty: #deselectedBorderColor)
> -?????????????????????????????????????????????????????????????????????????????????????????????? ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
> -?????????????????????????????????????????????????????????????????????????????????????????????? ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]] )].!
>
> Item was changed:
> ?? ----- Method: TileMorph>>wrapPhraseInFunction (in category '*Etoys-Squeakland-arrows') -----
> ?? wrapPhraseInFunction
> ???????????????? "The user made a gesture requesting that the phrase for which the receiver bears the widget hit be wrapped in a function.?? This applies for the moment only to numeric functions"
> ??
> ???????????????? | pad newPad functionPhrase |
> ???????????????? pad := self ownerThatIsA: TilePadMorph.?? "Or something higher than that???"
> ???????????????? (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper beep].
> ???????????????? newPad := TilePadMorph new setType: #Number.
> +?????????????? newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
> -?????????????? newPad hResizing: #shrinkWrap; vResizing: #spacefill.
> ???????????????? functionPhrase := FunctionTile new.
> ???????????????? newPad addMorphBack: functionPhrase.
> ???????????????? pad owner replaceSubmorph: pad by: newPad.
> ???????????????? functionPhrase operator: #abs pad: pad.
> ???????????????? functionPhrase addSuffixArrow.
> ???????????????? self scriptEdited
> ?? !
>
> Item was changed:
> ?? ----- Method: TilePadMorph>>wrapInFunction (in category '*Etoys-Squeakland-miscellaneous') -----
> ?? wrapInFunction
> ???????????????? "The user made a gesture requesting that the receiver be wrapped in a (numeric) function."
> ??
> ???????????????? | newPad functionPhrase |
> ???????????????? newPad := TilePadMorph new setType: #Number.
> +?????????????? newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
> -?????????????? newPad hResizing: #shrinkWrap; vResizing: #spacefill.
> ???????????????? functionPhrase := FunctionTile new.
> ???????????????? newPad addMorphBack: functionPhrase.
> ???????????????? owner replaceSubmorph: self by: newPad.
> ???????????????? functionPhrase operator: #abs pad: self.
> ???????????????? self scriptEdited!
>
> Item was changed:
> ?? ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
> ?? asMorphicSyntaxIn: parent
> ??
> ???????????????? ^ parent addToken: self name
> ???????????????????????????????????????????????? type: #variable
> +?????????????????????????????????????????????? on: self shallowCopy?????? "don't hand out the prototype!! See VariableNode>>initialize"
> -?????????????????????????????????????????????? on: self clone?? "don't hand out the prototype!! See VariableNode>>initialize"
> ?? !
>
> Item was changed:
> + ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'instance creation') -----
> - ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in category 'as yet unclassified') -----
> ?? fontName: aString bgColor: aColor centerColor: otherColor
> ???????????????? ^ self new
> ???????????????????????????????? fontName: aString;
> ???????????????????????????????? color: aColor;
> ???????????????????????????????? centerColor: otherColor!
>
> Item was changed:
> ?? ----- Method: WorldWindow class>>test2 (in category 'as yet unclassified') -----
> ?? test2
> ???????????????? "WorldWindow test2."
> ??
> ???????????????? | window world scrollPane |
> ???????????????? world := WiWPasteUpMorph newWorldForProject: nil.
> ???????????????? window := (WorldWindow labelled: 'Scrollable World') model: world.
> +?????????????? window addMorph: (scrollPane := ScrollPane new model: world)
> -?????????????? window addMorph: (scrollPane := TwoWayScrollPane new model: world)
> ???????????????????????????????? frame: (0@0 extent: 1.0@1.0).
> ???????????????? scrollPane scroller addMorph: world.
> ???????????????? world hostWindow: window.
> ???????????????? window openInWorld
> ?? !
>
>
>

>




Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

David T. Lewis
Nicolas,

There is a lot of good advice packed into this message. Thanks.

Dave


On Fri, Nov 15, 2019 at 10:05:32AM +0100, Nicolas Cellier wrote:

> Hi all,
> I don't recommend mixing cosmetic changes with functional changes, unless
> cosmetic changes are really scarce. My experience is that it is a recipe
> for switching the attention focus out of the functional changes, and as
> such it is parasiting at best or obstructing at worse the review process.
> Also, we should not deny the value of cosmetic changes. They have some
> value. They require attention and review too, even if they won't break
> production.
>
> We might want to amend tools. I hate loosing history, and I value the
> contextual analysis of certain design decision. But the frequency of such
> incursion into the past is gradually fading away. MC requires history for
> merging, but merging a too distant branch is becoming close to impossible
> anyway for human review. I tried it with Pharo some years ago, after
> repairing the conscious erasing of history that happened at each Pharo
> release (which is a very aggressive way to solve the problem, the
> worse-is-better-way)..
> So having the whole history in memory is questionable. It's not the whole
> history, what about Smalltalk 72, 76, 80, the change-set and update stream
> era... We have to set a limit.
>
> For browsing the history, I don't know what is worse, having a long list of
> small changes, or shorter list of squashed (in git parlance) unrelated
> changes. But this should be handled in the interface IMO. If we prefer
> grouping, this should be done by the browsing tool. For my own usage, it
> would have helped if the tool could filter the list by date range, modified
> class, method, pattern matching on commit message, ...
>
> Somehow related, it happens that I group several changes in one commit, I
> did it recently in VMMaker, one change for solving Newspeak generated code,
> the other for avoiding generating variable named bool, which were
> obstructing my attempt to compile legacy Mac OS  carbon VM. I did regret,
> because the first change introduced a slip in generated code that made the
> build fail in the branch dedicated to second change... Using CI automation
> is another reason why we should value separation of concerns. If I want to
> merge the compile_legacy_MacOS branch, one may ask in the future why the
> hell the totally unrelated Newspeak change was introduced in this branch.
> That's an anti-pattern, especially if we use explicitely named feature
> branches (which we avoid currently in MC, partly for lack of tool support).
>
> Last, MC does not behave so badly. I have far worse user experience using
> sourcetree on windows for file based projects on a gitlab server where load
> balancing configuration is not optimal, I can tell you that we should stop
> bashing ourselves ;)
>
> Le ven. 15 nov. 2019 ?? 04:39, David T. Lewis <[hidden email]> a ??crit :
>
> > Changing the subject line.
> >
> > Small commits do generate more noise, but I find that it is
> > easier to read, assess, and manage the changes if the commits
> > are small. I have spent a good deal of time doing this for
> > http://www.squeaksource.com/TrunkUpdateStreamV3 and my perspective
> > is based largely on that experience.
> >
> > If I were to point to something in need of improvement, I would say
> > that is the performance of our Monticello tools.
> >
> > I *love* having the MC change management directly in the image where
> > everything is directly accessible, browseable, and minimally dependent
> > on external tools. But I have to admit that the tools are slow.
> > Processing the update stream is slow, comparing versions is slow,
> > and reading packages is slow. And I strongly suspect that if all of
> > these things were instantaniously fast, then none of us would care
> > about how big or small the commits were.
> >
> > I may be wrong, but I have to suspect that some profiling of common
> > use cases, such as updating Squeak from the server, might identify
> > some huge opportunities for improvement.
> >
> > But even if those improvements never happen, I think that small
> > commits are a good thing.
> >
> > Dave
> >
> >
> > On Thu, Nov 14, 2019 at 09:32:51AM +0100, Marcel Taeumel wrote:
> > > > ...??piddly little fixes ...
> > > > ... such small changes are not worth burdening everyone's life ...
> > > > ...????tiny improvements ...
> > >
> > > Since I merged those commits and had to read and asses them, I can say
> > that the granularity of them was fine. Except for that one duplication for
> > the help in Freecell.
> > >
> > > Let's focus on "recategorize methods". Yes, one could easily do that
> > when fixing another issue. Unless it is a bigger quest such as Patrick's
> > (pre) recent efforts to clean up lots of categories across classes.
> > >
> > > Best,
> > > Marcel
> > > Am 13.11.2019 20:20:41 schrieb Chris Muller <[hidden email]>:
> > > Guys, would you please consider "batching up" piddly little fixes like
> > "recatgorized one method" this into fewer, chunkier commits with other
> > fixes??? Such small changes are not worth burdening everyone's life with an
> > additional 2MB of memory, disk, network and CPU overhead -- in *every
> > single image* they use going forward, forever.?? ??Please let that sink in
> > for a moment.
> > >
> > > Even ignoring that, it also bloats the readability of the history.??
> > There's no use case where timestamping and versioning tiny improvements
> > like this is useful, only micro harmful.
> > >
> > > Best,
> > > ?? Chris
> > >
> > > On Wed, Nov 13, 2019 at 6:33 AM Marcel Taeumel <[hidden email]
> > [mailto:[hidden email]]> wrote:
> > >
> > > Hi Christoph,
> > >
> > > I know. We should come up with a solution for that. Maybe re-print the
> > commit messages of all ancestors as soon as the number of ancestors is > 1.
> > >
> > > Best,
> > > Marcel
> > > Am 13.11.2019 12:51:06 schrieb Thiede, Christoph <
> > [hidden email] [mailto:
> > [hidden email]]>:
> > > Just for interest, is it usual & desired behavior that when installing
> > these updates, the update??log does not include??any of my commit messages?
> > > Von: Squeak-dev <[hidden email] [mailto:
> > [hidden email]]> im Auftrag von
> > [hidden email] [mailto:[hidden email]] <
> > [hidden email] [mailto:[hidden email]]>
> > > Gesendet: Mittwoch, 13. November 2019 12:15:14
> > > An: [hidden email] [mailto:
> > [hidden email]];
> > [hidden email] [mailto:
> > [hidden email]]
> > > Betreff: [squeak-dev] The Trunk: EToys-mt.368.mcz
> > > ??
> > > Marcel Taeumel uploaded a new version of EToys to project The Trunk:
> > > http://source.squeak.org/trunk/EToys-mt.368.mcz [
> > http://source.squeak.org/trunk/EToys-mt.368.mcz]
> > >
> > > ==================== Summary ====================
> > >
> > > Name: EToys-mt.368
> > > Author: mt
> > > Time: 13 November 2019, 12:15:07.673043 pm
> > > UUID: 3f6873fa-5111-ac4a-a108-9031e19e5f40
> > > Ancestors: EToys-kfr.363, EToys-ct.354, EToys-ct.355, EToys-ct.356,
> > EToys-ct.357, EToys-ct.358, EToys-ct.359, EToys-ct.360, EToys-ct.364,
> > EToys-ct.365, EToys-ct.367
> > >
> > > Merge! Merge! Merge! Various fixes in Etoys-related places.
> > >
> > > =============== Diff against EToys-kfr.363 ===============
> > >
> > > Item was added:
> > > + ----- Method: Form>>scaledToWidth: (in category
> > '*Etoys-Squeakland-scaling, rotation') -----
> > > + scaledToWidth: newWidth
> > > +?????????????? "Answer the receiver, scaled such that it has the
> > desired width."
> > > +
> > > +?????????????? newWidth = self width ifTrue: [^ self].
> > > +?????????????? ^self magnify: self boundingBox by: (newWidth / self
> > width) smoothing: 2.
> > > + !
> > >
> > > Item was changed:
> > > ?? ----- Method: FreeCell>>help (in category 'actions') -----
> > > ?? help
> > > +
> > > +?????????????? self helpText editWithLabel: 'FreeCell Help'.!
> > > -?????????????? | window helpMorph |
> > > -?????????????? window := SystemWindow labelled: 'FreeCell Help'
> > translated.
> > > -?????????????? window model: self.
> > > -?????????????? helpMorph := (PluggableTextMorph new editString: self
> > helpText) lock.
> > > -?????????????? window
> > > -?????????????????????????????? addMorph: helpMorph
> > > -?????????????????????????????? frame: (0 @ 0 extent: 1 @ 1).
> > > -?????????????? window openInWorld!
> > >
> > > Item was added:
> > > + ----- Method: MovingEyeMorph>>color: (in category 'accessing') -----
> > > + color: aColor
> > > +
> > > +?????????????? super color: aColor.
> > > +??????????????
> > > +?????????????? "Migrate old instances."
> > > +?????????????? inner color: Color transparent.
> > > +??????????????
> > > +?????????????? "Keep iris visible."
> > > +?????????????? aColor = iris color
> > > +?????????????????????????????? ifTrue: [iris borderWidth: 1;
> > borderColor: aColor negated]
> > > +?????????????????????????????? ifFalse: [iris borderWidth: 0].!
> > >
> > > Item was changed:
> > > ?? ----- Method: MovingEyeMorph>>initialize (in category
> > 'initialization') -----
> > > ?? initialize
> > > ???????????????? "initialize the state of the receiver"
> > > ???????????????? super initialize.
> > > ???????????????? ""
> > > ???????????????? inner := EllipseMorph new.
> > > +?????????????? inner color: Color transparent.
> > > -?????????????? inner color: self color.
> > > ???????????????? inner extent: (self extent * (1.0 @ 1.0 - IrisSize))
> > asIntegerPoint.
> > > -?????????????? inner borderColor: self color.
> > > ???????????????? inner borderWidth: 0.
> > > ?? ""
> > > ???????????????? iris := EllipseMorph new.
> > > ???????????????? iris color: Color white.
> > > ???????????????? iris extent: (self extent * IrisSize) asIntegerPoint.
> > > ?? ""
> > > ???????????????? self addMorphCentered: inner.
> > > ???????????????? inner addMorphCentered: iris.
> > > ?? ""
> > > ???????????????? self extent: 26 @ 33!
> > >
> > > Item was added:
> > > + ----- Method: MovingEyeMorph>>irisColor (in category 'accessing') -----
> > > + irisColor
> > > +
> > > +?????????????? ^ iris color!
> > >
> > > Item was added:
> > > + ----- Method: MovingEyeMorph>>irisColor: (in category 'accessing')
> > -----
> > > + irisColor: aColor
> > > +
> > > +?????????????? iris color: aColor.
> > > +??????????????
> > > +?????????????? "Keep iris visible."
> > > +?????????????? aColor = self color
> > > +?????????????????????????????? ifTrue: [iris borderWidth: 1;
> > borderColor: aColor negated]
> > > +?????????????????????????????? ifFalse: [iris borderWidth: 0].!
> > >
> > > Item was added:
> > > + ----- Method: MovingEyeMorph>>irisPos (in category 'accessing') -----
> > > + irisPos
> > > +
> > > +?????????????? ^ iris position!
> > >
> > > Item was changed:
> > > + ----- Method: MovingEyeMorph>>irisPos: (in category 'accessing') -----
> > > - ----- Method: MovingEyeMorph>>irisPos: (in category 'as yet
> > unclassified') -----
> > > ?? irisPos: cp
> > > ??
> > > ???????????????? | a b theta x y |
> > > ???????????????? theta := (cp - self center) theta.
> > > ???????????????? a := inner width // 2.
> > > ???????????????? b := inner height // 2.
> > > ???????????????? x := a * (theta cos).
> > > ???????????????? y := b * (theta sin).
> > > ???????????????? iris position: ((x@y) asIntegerPoint) + self center -
> > (iris extent // 2).!
> > >
> > > Item was changed:
> > > ?? ----- Method: MovingEyeMorph>>step (in category 'stepping and
> > presenter') -----
> > > ?? step
> > > ???????????????? | cp |
> > > ???????????????? cp := self globalPointToLocal: self world primaryHand
> > position.
> > > ???????????????? (inner containsPoint: cp)
> > > ???????????????????????????????? ifTrue: [iris position: (cp - (iris
> > extent // 2))]
> > > +?????????????????????????????? ifFalse: [self irisPos: cp].!
> > > -?????????????????????????????? ifFalse: [self irisPos: cp].
> > > -?????????????? self changed "cover up gribblies if embedded in Flash"!
> > >
> > > Item was changed:
> > > ?? ----- Method: NewVariableDialogMorph>>decimalPlaces (in category
> > 'accessing') -----
> > > ?? decimalPlaces
> > > ???????????????? ^ decimalPlacesButton
> > > ???????????????????????????????? ifNil: [Utilities
> > > ????????????????????????????????????????????????????????????????
> > decimalPlacesForFloatPrecision: (self targetPlayer
> > >
> > +??????????????????????????????????????????????????????????????????????????????
> > defaultFloatPrecisionFor: self varAcceptableName asSetterSelector)]
> > >
> > -??????????????????????????????????????????????????????????????????????????????
> > defaultFloatPrecisionFor: (Utilities getterSelectorFor: self
> > varAcceptableName))]
> > > ???????????????????????????????? ifNotNil: [:button| button label
> > asNumber]!
> > >
> > > Item was changed:
> > > ?? ----- Method: Player>>newScriptorAround: (in category 'viewer') -----
> > > ?? newScriptorAround: aPhrase
> > > ???????????????? "Sprout a scriptor around aPhrase, thus making a new
> > script.?? aPhrase may either be a PhraseTileMorph (classic tiles 1997-2001)
> > or a SyntaxMorph (2001 onward)"
> > > ??
> > > ???????????????? | aScriptEditor aUniclassScript tw blk |
> > > ?? Cursor wait showWhile: [
> > > ???????????????? aUniclassScript := self class permanentUserScriptFor:
> > self unusedScriptName player: self.
> > > ???????????????? aScriptEditor := aUniclassScript
> > instantiatedScriptEditorForPlayer: self.
> > > ??
> > > ???????????????? Preferences universalTiles ifTrue: [
> > > ???????????????????????????????? aScriptEditor install.
> > > ???????????????????????????????? "aScriptEditor hResizing: #shrinkWrap;
> > > ???????????????????????????????????????????????? vResizing: #shrinkWrap;
> > > ???????????????????????????????????????????????? cellPositioning:
> > #topLeft;
> > > ???????????????????????????????????????????????? setProperty:
> > #autoFitContents toValue: true."
> > > ???????????????????????????????? aScriptEditor insertUniversalTiles.??
> > "Gets an empty SyntaxMorph for a MethodNode"
> > > +?????????????????????????????? tw := aScriptEditor findA: ScrollPane.
> > > -?????????????????????????????? tw := aScriptEditor findA:
> > TwoWayScrollPane.
> > > ???????????????????????????????? aPhrase ifNotNil:
> > > ???????????????????????????????????????????????? [blk := (tw scroller
> > findA: SyntaxMorph "MethodNode") findA: BlockNode.
> > > ???????????????????????????????????????????????? blk addMorphFront:
> > aPhrase.
> > > ???????????????????????????????????????????????? aPhrase accept.
> > > ???????????????????????????????? ].
> > > ???????????????????????????????? SyntaxMorph setSize: nil
> > andMakeResizable: aScriptEditor.
> > > ???????????????? ] ifFalse: [
> > > ???????????????????????????????? aPhrase
> > > ????????????????????????????????????????????????????????????????
> > ifNotNil: [aScriptEditor phrase: aPhrase]???????????? "does an install"
> > > ???????????????????????????????????????????????????????????????? ifNil:
> > [aScriptEditor install]
> > > ???????????????? ].
> > > ???????????????? self class allSubInstancesDo: [:anInst | anInst
> > scriptInstantiationForSelector: aUniclassScript selector].
> > > ???????????????????????????????? "The above assures the presence of a
> > ScriptInstantiation for the new selector in all siblings"
> > > ???????????????? self updateScriptsCategoryOfViewers.
> > > ?? ].
> > > ???????????????? ^ aScriptEditor!
> > >
> > > Item was changed:
> > > ?? ----- Method: Preferences class>>initializePreferencePanel:in: (in
> > category '*Etoys-Squeakland-preferences panel') -----
> > > ?? initializePreferencePanel: aPanel in: aPasteUpMorph
> > > ???????????????? "Initialize the given Preferences panel. in the given
> > pasteup, which is the top-level panel installed in the container window.??
> > Also used to reset it after some change requires reformulation"
> > > ??
> > > ???????????????? | tabbedPalette controlPage aColor aFont
> > maxEntriesPerCategory tabsMorph anExtent?? prefObjects |
> > > ???????????????? aPasteUpMorph removeAllMorphs.
> > > ??
> > > ???????????????? aFont := Preferences standardListFont.
> > > +?????????????? aColor := aPanel windowColorToUse.
> > > -?????????????? aColor := aPanel defaultBackgroundColor.
> > > ???????????????? tabbedPalette := TabbedPalette newSticky.
> > > ???????????????? tabbedPalette dropEnabled: false.
> > > ???????????????? (tabsMorph := tabbedPalette tabsMorph) color: aColor
> > darker;
> > > ?????????????????????????????????? highlightColor: Color red
> > regularColor: Color brown darker darker.
> > > ???????????????? tabbedPalette on: #mouseDown send: #yourself to: #().
> > > ???????????????? maxEntriesPerCategory := 0.
> > > ???????????????? self listOfCategories do:
> > > ???????????????????????????????? [:aCat |
> > > ???????????????????????????????????????????????? controlPage :=
> > AlignmentMorph newColumn beSticky color: aColor.
> > > ???????????????????????????????????????????????? controlPage on:
> > #mouseDown send: #yourself to: #().
> > > ???????????????????????????????????????????????? controlPage
> > dropEnabled: false.
> > > ???????????????????????????????????????????????? controlPage
> > borderColor: aColor;
> > > ??????????????????????????????????????????????????????????????????
> > layoutInset: 4.
> > > ???????????????????????????????????????????????? (prefObjects := self
> > preferenceObjectsInCategory: aCat) do:
> > > ????????????????????????????????????????????????????????????????
> > [:aPreference | | button |
> > >
> > ????????????????????????????????????????????????????????????????????????????????
> > button := aPreference representativeButtonWithColor: Color white inPanel:
> > aPanel.
> > >
> > ????????????????????????????????????????????????????????????????????????????????
> > button ifNotNil: [controlPage addMorphBack: button]].
> > > ???????????????????????????????????????????????? controlPage setNameTo:
> > aCat asString.
> > > ???????????????????????????????????????????????? aCat = #?
> > > ???????????????????????????????????????????????????????????????? ifTrue:
> > [aPanel addHelpItemsTo: controlPage].
> > > ???????????????????????????????????????????????? tabbedPalette
> > addTabFor: controlPage font: aFont.
> > > ???????????????????????????????????????????????? aCat = 'search results'
> > ifTrue:
> > > ????????????????????????????????????????????????????????????????
> > [(tabbedPalette tabNamed: aCat) setBalloonText:
> > >
> > ????????????????????????????????????????????????????????????????????????????????
> > 'Use the ? category to find preferences by keyword; the results of your
> > search will show up here' translated].
> > > ???????????????????????????????? maxEntriesPerCategory :=
> > maxEntriesPerCategory max: prefObjects size].
> > > ???????????????? tabbedPalette selectTabNamed: '?'.
> > > ???????????????? tabsMorph rowsNoWiderThan: aPasteUpMorph width.
> > > ???????????????? aPasteUpMorph on: #mouseDown send: #yourself to: #().
> > > ???????????????? anExtent := aPasteUpMorph width @ (490 max: (25 +
> > tabsMorph height + (24 * maxEntriesPerCategory))).
> > > ???????????????? aPasteUpMorph extent: anExtent.
> > > ???????????????? aPasteUpMorph color: aColor.
> > > ???????????????? aPasteUpMorph???????? addMorphBack: tabbedPalette.!
> > >
> > > Item was changed:
> > > ?? ----- Method: ScriptEditorMorph>>autoFitOnOff (in category 'menu')
> > -----
> > > ?? autoFitOnOff
> > > ???????????????? "Toggle between auto fit to size of code and manual
> > resize with scrolling"
> > > ???????????????? | tw |
> > > +?????????????? (tw := self findA: ScrollPane) ifNil: [^ self].
> > > -?????????????? (tw := self findA: TwoWayScrollPane) ifNil: [^ self].
> > > ???????????????? (self hasProperty: #autoFitContents)
> > > ???????????????????????????????? ifTrue: [self removeProperty:
> > #autoFitContents.
> > > ???????????????????????????????????????????????? self hResizing: #rigid;
> > vResizing: #rigid]
> > > ???????????????????????????????? ifFalse: [self setProperty:
> > #autoFitContents toValue: true.
> > > ???????????????????????????????????????????????? self hResizing:
> > #shrinkWrap; vResizing: #shrinkWrap].
> > > ???????????????? tw layoutChanged!
> > >
> > > Item was changed:
> > > ?? ----- Method: ScriptEditorMorph>>extent: (in category 'other') -----
> > > ?? extent: x
> > > ??
> > > ???????????????? | newExtent tw menu |
> > > ???????????????? newExtent := x max: self minWidth @ self minHeight.
> > > +?????????????? (tw := self findA: ScrollPane) ifNil:
> > > -?????????????? (tw := self findA: TwoWayScrollPane) ifNil:
> > > ???????????????????????????????? ["This was the old behavior"
> > > ???????????????????????????????? ^ super extent: newExtent].
> > > ??
> > > ???????????????? (self hasProperty: #autoFitContents) ifTrue: [
> > > ???????????????????????????????? menu := MenuMorph new defaultTarget:
> > self.
> > > ???????????????????????????????? menu addUpdating: #autoFitString
> > target: self action: #autoFitOnOff.
> > > ???????????????????????????????? menu addTitle: 'To resize the script,
> > uncheck the box below' translated.
> > > ???????????????????????????????? menu popUpEvent: nil in: self
> > world???????? .
> > > ???????????????????????????????? ^ self].
> > > ??
> > > ???????????????? "Allow the user to resize to any size"
> > > ???????????????? tw extent: ((newExtent x max: self firstSubmorph width)
> > > ???????????????????????????????????????????????????????????????? @
> > (newExtent y - self firstSubmorph height)) - (self borderWidth * 2) + (-4 @
> > -4).?? "inset?"
> > > ???????????????? ^ super extent: newExtent!
> > >
> > > Item was changed:
> > > ?? ----- Method: ScriptEditorMorph>>hibernate (in category 'other') -----
> > > ?? hibernate
> > > ???????????????? "Possibly delete the tiles, but only if using universal
> > tiles."
> > > ??
> > > ???????????????? | tw |
> > > ???????????????? Preferences universalTiles ifFalse: [^self].
> > > +?????????????? (tw := self findA: ScrollPane) isNil
> > > -?????????????? (tw := self findA: TwoWayScrollPane) isNil
> > > ???????????????????????????????? ifFalse:
> > > ???????????????????????????????????????????????? [self setProperty:
> > #sizeAtHibernate toValue: self extent.???????????? "+ tw xScrollerHeight"
> > > ???????????????????????????????????????????????? submorphs size > 1
> > ifTrue: [tw delete]]!
> > >
> > > Item was added:
> > > + ----- Method: SpectrumAnalyzerMorph>>fftSize: (in category
> > 'accessing') -----
> > > + fftSize: aSize
> > > +
> > > +?????????????? | on |
> > > +?????????????? on := soundInput isRecording.
> > > +?????????????? self stop.
> > > +?????????????? fft := FFT new: aSize.
> > > +?????????????? self resetDisplay.
> > > +?????????????? on ifTrue: [self start].!
> > >
> > > Item was changed:
> > > ?? ----- Method: SpectrumAnalyzerMorph>>setFFTSize (in category 'menu
> > and buttons') -----
> > > ?? setFFTSize
> > > ???????????????? "Set the size of the FFT used for frequency analysis."
> > > ??
> > > +?????????????? | aMenu sz |
> > > -?????????????? | aMenu sz on |
> > > ???????????????? aMenu := CustomMenu new title: ('FFT size (currently
> > {1})' translated format:{fft n}).
> > > ???????????????? ((7 to: 10) collect: [:n | 2 raisedTo: n]) do:[:r |
> > aMenu add: r printString action: r].
> > > ???????????????? sz := aMenu startUp.
> > > ???????????????? sz ifNil: [^ self].
> > > +?????????????? self fftSize: sz.!
> > > -?????????????? on := soundInput isRecording.
> > > -?????????????? self stop.
> > > -?????????????? fft := FFT new: sz.
> > > -?????????????? self resetDisplay.
> > > -?????????????? on ifTrue: [self start].
> > > - !
> > >
> > > Item was changed:
> > > ?? ----- Method: SyntaxMorph class>>setSize:andMakeResizable: (in
> > category 'as yet unclassified') -----
> > > ?? setSize: oldExtent andMakeResizable: outerMorph
> > > ???????????????? | tw |
> > > +?????????????? (tw := outerMorph findA: ScrollPane) ifNil: [^self].
> > > -?????????????? (tw := outerMorph findA: TwoWayScrollPane) ifNil:
> > [^self].
> > > ???????????????? tw hResizing: #spaceFill;
> > > ???????????????????????????????? vResizing: #spaceFill;
> > > ???????????????????????????????? color: Color transparent;
> > > ???????????????????????????????? setProperty: #hideUnneededScrollbars
> > toValue: true.
> > > ???????????????? outerMorph
> > > ???????????????????????????????? hResizing: #shrinkWrap;
> > > ???????????????????????????????? vResizing: #shrinkWrap;
> > > ???????????????????????????????? cellPositioning: #topLeft.
> > > ???????????????? outerMorph fullBounds.
> > > ?? !
> > >
> > > Item was changed:
> > > ?? ----- Method: SyntaxMorph>>enclosingPane (in category 'accessing')
> > -----
> > > ?? enclosingPane
> > > ???????????????? "The object that owns this script layout"
> > > ??
> > > ???????????????? | oo higher |
> > > ???????????????? oo := self owner.
> > > ???????????????? [higher := oo isSyntaxMorph.
> > > ???????????????? higher := higher or: [oo class == TransformMorph].
> > > +?????????????? higher := higher or: [oo class == ScrollPane].
> > > -?????????????? higher := higher or: [oo class == TwoWayScrollPane].
> > > ???????????????? higher ifFalse: [^ oo].
> > > ???????????????? higher] whileTrue: [oo := oo owner].
> > > ?? !
> > >
> > > Item was removed:
> > > - ----- Method: SyntaxMorph>>inAScrollPane (in category
> > 'initialization') -----
> > > - inAScrollPane
> > > -?????????????? "Answer a scroll pane in which the receiver is
> > scrollable"
> > > -
> > > -?????????????? ^ self inATwoWayScrollPane!
> > >
> > > Item was changed:
> > > ?? ----- Method: SyntaxMorph>>openInWindow (in category
> > 'initialization') -----
> > > ?? openInWindow
> > > ??
> > > +?????????????? | sel |
> > > -?????????????? | window widget sel |
> > > ???????????????? sel := ''.
> > > ???????????????? self firstSubmorph allMorphs do: [:rr |
> > > +?????????????????????????????? (rr isKindOf: StringMorph) ifTrue: [sel
> > := sel, rr contents]].
> > > -?????????????????????????????????????????????? (rr isKindOf:
> > StringMorph) ifTrue: [sel := sel, rr contents]].
> > > -?????????????? window := (SystemWindow labelled: 'Tiles for ', self
> > parsedInClass printString, '>>',sel).
> > > -?????????????? widget := self inAScrollPane.
> > > -?????????????? widget color: Color paleOrange.
> > > -?????????????? window
> > > -?????????????????????????????? addMorph: widget
> > > -?????????????????????????????? frame: (0@0 extent: 1.0@1.0).
> > > -?????????????? window openInWorldExtent: (
> > > -?????????????????????????????? self extent + (20@40) min: (Display
> > boundingBox extent * 0.8) rounded
> > > -?????????????? )
> > > ??
> > > +?????????????? ^ self inAScrollPane
> > > +?????????????????????????????? color: Color paleOrange;
> > > +?????????????????????????????? openInWindowLabeled: 'Tiles for ', self
> > parsedInClass printString, '>>', sel!
> > > - !
> > >
> > > Item was added:
> > > + ----- Method: SyntaxMorph>>parseNodeWith:asStatement: (in category
> > '*Etoys-Squeakland-code generation') -----
> > > + parseNodeWith: encoder asStatement: aBoolean
> > > +
> > > +?????????????? ^ self parseNode!
> > >
> > > Item was changed:
> > > ?? ----- Method: SyntaxMorph>>unhighlightBorder (in category
> > 'highlighting') -----
> > > ?? unhighlightBorder
> > > ??
> > > ???????????????? self currentSelectionDo: [:innerMorph :mouseDownLoc
> > :outerMorph |
> > > +?????????????????????????????? (self == outerMorph or: [owner notNil
> > and: [owner isSyntaxMorph not]])
> > > +?????????????????????????????????????????????? ifFalse: [self
> > borderColor: self stdBorderColor]
> > > +?????????????????????????????????????????????? ifTrue: [
> > > +?????????????????????????????????????????????????????????????? (self
> > hasProperty: #deselectedBorderColor)
> > >
> > +??????????????????????????????????????????????????????????????????????????????
> > ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
> > >
> > +??????????????????????????????????????????????????????????????????????????????
> > ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]]
> > ].!
> > > -?????????????????????????????? self borderColor: (
> > > -?????????????????????????????????????????????? (self == outerMorph or:
> > [owner notNil and: [owner isSyntaxMorph not]])
> > > -?????????????????????????????????????????????????????????????? ifFalse:
> > [self borderColor: self stdBorderColor]
> > > -?????????????????????????????????????????????????????????????? ifTrue: [
> > >
> > -??????????????????????????????????????????????????????????????????????????????
> > (self hasProperty: #deselectedBorderColor)
> > >
> > -??????????????????????????????????????????????????????????????????????????????????????????????
> > ifTrue: [self borderColor: (self valueOfProperty: #deselectedBorderColor)]
> > >
> > -??????????????????????????????????????????????????????????????????????????????????????????????
> > ifFalse: [self borderStyle: (BorderStyle raised width: self borderWidth)]]
> > )].!
> > >
> > > Item was changed:
> > > ?? ----- Method: TileMorph>>wrapPhraseInFunction (in category
> > '*Etoys-Squeakland-arrows') -----
> > > ?? wrapPhraseInFunction
> > > ???????????????? "The user made a gesture requesting that the phrase for
> > which the receiver bears the widget hit be wrapped in a function.?? This
> > applies for the moment only to numeric functions"
> > > ??
> > > ???????????????? | pad newPad functionPhrase |
> > > ???????????????? pad := self ownerThatIsA: TilePadMorph.?? "Or something
> > higher than that???"
> > > ???????????????? (pad isNil or: [pad type ~= #Number]) ifTrue: [^ Beeper
> > beep].
> > > ???????????????? newPad := TilePadMorph new setType: #Number.
> > > +?????????????? newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
> > > -?????????????? newPad hResizing: #shrinkWrap; vResizing: #spacefill.
> > > ???????????????? functionPhrase := FunctionTile new.
> > > ???????????????? newPad addMorphBack: functionPhrase.
> > > ???????????????? pad owner replaceSubmorph: pad by: newPad.
> > > ???????????????? functionPhrase operator: #abs pad: pad.
> > > ???????????????? functionPhrase addSuffixArrow.
> > > ???????????????? self scriptEdited
> > > ?? !
> > >
> > > Item was changed:
> > > ?? ----- Method: TilePadMorph>>wrapInFunction (in category
> > '*Etoys-Squeakland-miscellaneous') -----
> > > ?? wrapInFunction
> > > ???????????????? "The user made a gesture requesting that the receiver
> > be wrapped in a (numeric) function."
> > > ??
> > > ???????????????? | newPad functionPhrase |
> > > ???????????????? newPad := TilePadMorph new setType: #Number.
> > > +?????????????? newPad hResizing: #shrinkWrap; vResizing: #spaceFill.
> > > -?????????????? newPad hResizing: #shrinkWrap; vResizing: #spacefill.
> > > ???????????????? functionPhrase := FunctionTile new.
> > > ???????????????? newPad addMorphBack: functionPhrase.
> > > ???????????????? owner replaceSubmorph: self by: newPad.
> > > ???????????????? functionPhrase operator: #abs pad: self.
> > > ???????????????? self scriptEdited!
> > >
> > > Item was changed:
> > > ?? ----- Method: VariableNode>>asMorphicSyntaxIn: (in category
> > '*Etoys-tiles') -----
> > > ?? asMorphicSyntaxIn: parent
> > > ??
> > > ???????????????? ^ parent addToken: self name
> > > ???????????????????????????????????????????????? type: #variable
> > > +?????????????????????????????????????????????? on: self
> > shallowCopy?????? "don't hand out the prototype!! See
> > VariableNode>>initialize"
> > > -?????????????????????????????????????????????? on: self clone?? "don't
> > hand out the prototype!! See VariableNode>>initialize"
> > > ?? !
> > >
> > > Item was changed:
> > > + ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in
> > category 'instance creation') -----
> > > - ----- Method: WatchMorph class>>fontName:bgColor:centerColor: (in
> > category 'as yet unclassified') -----
> > > ?? fontName: aString bgColor: aColor centerColor: otherColor
> > > ???????????????? ^ self new
> > > ???????????????????????????????? fontName: aString;
> > > ???????????????????????????????? color: aColor;
> > > ???????????????????????????????? centerColor: otherColor!
> > >
> > > Item was changed:
> > > ?? ----- Method: WorldWindow class>>test2 (in category 'as yet
> > unclassified') -----
> > > ?? test2
> > > ???????????????? "WorldWindow test2."
> > > ??
> > > ???????????????? | window world scrollPane |
> > > ???????????????? world := WiWPasteUpMorph newWorldForProject: nil.
> > > ???????????????? window := (WorldWindow labelled: 'Scrollable World')
> > model: world.
> > > +?????????????? window addMorph: (scrollPane := ScrollPane new model:
> > world)
> > > -?????????????? window addMorph: (scrollPane := TwoWayScrollPane new
> > model: world)
> > > ???????????????????????????????? frame: (0@0 extent: 1.0@1.0).
> > > ???????????????? scrollPane scroller addMorph: world.
> > > ???????????????? world hostWindow: window.
> > > ???????????????? window openInWorld
> > > ?? !
> > >
> > >
> > >
> >
> > >
> >
> >
> >

>


Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

Chris Muller-3
In reply to this post by David T. Lewis
Dave,

I think we've found basic consensus on this issue...

Small commits do generate more noise,

No they don't.  Size is unrelated to content / noise.

but I find that it is
easier to read, assess, and manage the changes if the commits
are small. I have spent a good deal of time doing this for
http://www.squeaksource.com/TrunkUpdateStreamV3 and my perspective
is based largely on that experience. 

If I were to point to something in need of improvement, I would say
that is the performance of our Monticello tools.

I *love* having the MC change management directly in the image where
everything is directly accessible, browseable, and minimally dependent
on external tools. But I have to admit that the tools are slow.
Processing the update stream is slow, comparing versions is slow,
and reading packages is slow.

It's a database, Dave, it responds to the laws of software physics.  Any database, including a strictly file-based one like we're using (not Magma), will perform more slowly as you put more objects into it.  It's unavoidable and why, as it grows, you want the highest percentage of objects in it to be meaningful.  Whether a large revert, or a small one-line comment fix, inconsequential objects become the noises that dilute the value of any database.

But all that is subordinate to the fact that the MC ancestry is _the_ artifact we make and put out and resides on all of our computers.  This makes it something to not carelessly ignore like the typical black-hole log file.

And I strongly suspect that if all of
these things were instantaniously fast, then none of us would care
about how big or small the commits were.

No, that's exactly backwards!  The truth is that _even if_ it were instantaniously fast, we all should still care about the quality of the ancestry.

Like I said, I think the recent commits have suggested consensus, no complaints here.  Maybe a bit small'ish for my taste, but Marcel is keeping the packaging (version description) comparably terse too.  It adds up to clear and meaningful unit-of-change.

There's always going to be _some_ noise, but we seem to be doing better.  With new people, it can be a good time to remember.
 

I may be wrong, but I have to suspect that some profiling of common
use cases, such as updating Squeak from the server, might identify
some huge opportunities for improvement.

There's a bug with the "Move to Treated" that I think is an easy fix.  I would love if you would update squeaksource.com to the latest code and use that experience to find/fix any bugs that we can then backport to source.squeak.org...
 
But even if those improvements never happen, I think that small
commits are a good thing.

Well, I do hope you don't think splitting a single piece of functionality across multiple small commits is a good thing.

 - Chris



Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

Jakob Reschke
"Quality of the ancestry" to me _includes_ separating "piddly" things from real, unrelated functional changes.

While the version list does grow with what you call noise, it keeps this noise out of the diffs. That is priceless. 

Monticello duplicating megabytes of data for every new version is a serious flaw and should be addressed. Fix the system, not its users. Adopt a new storage format, deduplicate ancestry nodes and definitions in memory, whatever.

Low quality history to me would mean that things are hard to find or recover. That means huge commits that do a dozen things at once or commits with useless messages like "fixing stuff" (or pick your favorites from commitlogsfromlastnight.com). On the other hand I can always quickly skip "Reformat code" in the list of versions.

Sometimes colleagues commit reformatting of whole files (not Smalltalk) together with their actual changes. It is a nightmare for reviewers.

Kind regards
Jakob


Chris Muller <[hidden email]> schrieb am Do., 21. Nov. 2019, 08:55:
Dave,

I think we've found basic consensus on this issue...

Small commits do generate more noise,

No they don't.  Size is unrelated to content / noise.

but I find that it is
easier to read, assess, and manage the changes if the commits
are small. I have spent a good deal of time doing this for
http://www.squeaksource.com/TrunkUpdateStreamV3 and my perspective
is based largely on that experience. 

If I were to point to something in need of improvement, I would say
that is the performance of our Monticello tools.

I *love* having the MC change management directly in the image where
everything is directly accessible, browseable, and minimally dependent
on external tools. But I have to admit that the tools are slow.
Processing the update stream is slow, comparing versions is slow,
and reading packages is slow.

It's a database, Dave, it responds to the laws of software physics.  Any database, including a strictly file-based one like we're using (not Magma), will perform more slowly as you put more objects into it.  It's unavoidable and why, as it grows, you want the highest percentage of objects in it to be meaningful.  Whether a large revert, or a small one-line comment fix, inconsequential objects become the noises that dilute the value of any database.

But all that is subordinate to the fact that the MC ancestry is _the_ artifact we make and put out and resides on all of our computers.  This makes it something to not carelessly ignore like the typical black-hole log file.

And I strongly suspect that if all of
these things were instantaniously fast, then none of us would care
about how big or small the commits were.

No, that's exactly backwards!  The truth is that _even if_ it were instantaniously fast, we all should still care about the quality of the ancestry.

Like I said, I think the recent commits have suggested consensus, no complaints here.  Maybe a bit small'ish for my taste, but Marcel is keeping the packaging (version description) comparably terse too.  It adds up to clear and meaningful unit-of-change.

There's always going to be _some_ noise, but we seem to be doing better.  With new people, it can be a good time to remember.
 

I may be wrong, but I have to suspect that some profiling of common
use cases, such as updating Squeak from the server, might identify
some huge opportunities for improvement.

There's a bug with the "Move to Treated" that I think is an easy fix.  I would love if you would update squeaksource.com to the latest code and use that experience to find/fix any bugs that we can then backport to source.squeak.org...
 
But even if those improvements never happen, I think that small
commits are a good thing.

Well, I do hope you don't think splitting a single piece of functionality across multiple small commits is a good thing.

 - Chris




Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

David T. Lewis
In reply to this post by Chris Muller-3
Hi Chris,

I was mainly offering my opinion based on my on experience tending
to the (unnofficial and private) www.squeaksource.com/TrunkUpdateStreamV3
which involves a good deal of reading, reviewing, and merging.

I can happily admit to another bias as well - I have been using
git for a while now (nothing related to Smalltalk), and I have to
say that it is a revelation. It is powerful, complex, and adaptable
from the outside, and on the inside it is nothing but simple. It is
also very, very fast.

So it turns out that good versioning tools do not need to be slow
and resource hungry. I guess it also shows that a small amount of
brilliant design goes a long way when it comes to performance.

Dave

p.s. No, I am NOT advocating use of git for Squeak (I'm not against
it either). But it is an existence proof that things do not have to
be slow and inefficient. Meanwhile, I continue to be very happy
with Monticello, it's really quite wonderful IMHO.

On Thu, Nov 21, 2019 at 01:54:22AM -0600, Chris Muller wrote:

> Dave,
>
> I think we've found basic consensus on this issue...
>
> Small commits do generate more noise,
>
>
> No they don't.  Size is unrelated to content / noise.
>
> but I find that it is
> > easier to read, assess, and manage the changes if the commits
> > are small. I have spent a good deal of time doing this for
> > http://www.squeaksource.com/TrunkUpdateStreamV3 and my perspective
> > is based largely on that experience.
>
>
> > If I were to point to something in need of improvement, I would say
> > that is the performance of our Monticello tools.
> >
> > I *love* having the MC change management directly in the image where
> > everything is directly accessible, browseable, and minimally dependent
> > on external tools. But I have to admit that the tools are slow.
> > Processing the update stream is slow, comparing versions is slow,
> > and reading packages is slow.
>
>
> It's a database, Dave, it responds to the laws of software physics.  Any
> database, including a strictly file-based one like we're using (not Magma),
> will perform more slowly as you put more objects into it.  It's unavoidable
> and why, as it grows, you want the highest percentage of objects in it to
> be meaningful.  Whether a large revert, or a small one-line comment fix,
> inconsequential objects become the noises that dilute the value of any
> database.
>
> But all that is subordinate to the fact that the MC ancestry is _the_
> artifact we make and put out and resides on all of our computers.  This
> makes it something to not carelessly ignore like the typical black-hole log
> file.
>
> And I strongly suspect that if all of
> > these things were instantaniously fast, then none of us would care
> > about how big or small the commits were.
> >
>
> No, that's exactly backwards!  The truth is that _even if_ it were
> instantaniously fast, we all should still care about the quality of the
> ancestry.
>
> Like I said, I think the recent commits have suggested consensus, no
> complaints here.  Maybe a bit small'ish for my taste, but Marcel is keeping
> the packaging (version description) comparably terse too.  It adds up to
> clear and meaningful unit-of-change.
>
> There's always going to be _some_ noise, but we seem to be doing better.
> With new people, it can be a good time to remember.
>
>
> >
> > I may be wrong, but I have to suspect that some profiling of common
> > use cases, such as updating Squeak from the server, might identify
> > some huge opportunities for improvement.
> >
>
> There's a bug with the "Move to Treated" that I think is an easy fix.  I
> would love if you would update squeaksource.com to the latest code and use
> that experience to find/fix any bugs that we can then backport to
> source.squeak.org...
>
>
> > But even if those improvements never happen, I think that small
> > commits are a good thing.
> >
>
> Well, I do hope you don't think splitting a single piece of functionality
> across multiple small commits is a good thing.
>
>  - Chris

>


Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

Chris Muller-4
So it turns out that good versioning tools do not need to be slow
and resource hungry. I guess it also shows that a small amount of
brilliant design goes a long way when it comes to performance.

Nonsense.  You haven't magically escaped the laws of software physics.  You were using github, which is run in a datacenter, right?  Dump enough into your git repository, and your use-cases will eventually start to slow down in performance.

I am curious how you're "using git" though because when I accessed a git project through Squeak, it was NOT fast, and it created a gigantic directory tree in my squeak directory which also slowed down my daily backup job tremendously.  The directory names were hugely long and it was problematic.

This is why I won't start actively using git until I can make a transparent MCGitRepository via their v4 API (GraphQL).  I haven't looked at the Schema yet, but I wouldn't be surprised if it, alone, is larger than the entire _implementation_ code of Monticello.  I'd say Avi's was a brilliant design, for sure.

 - Chris




Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

Jakob Reschke
Indeed, Git has its scalability problems as well. That's why Microsoft is developing "VFS for Git"  https://vfsforgit.org/ to address these issues, so they can use it for the massive Windows code base without being blocked by Git. Compared to that code base and its number of concurrent developers, Squeak and its ancestry are tiny, there should be no problems at all. And yet we argue regularly about saving space and time by folding a few Monticello versions together.

While the "laws of software physics" do apply to Git as well, Git still performs much better under their constraints than Monticello. I think people like to call that "more efficient". Monticello's abstract design may be nice, but its current approach to storage (which should be an implementation detail) is not. To make things worse, independent from Monticello, "how to store Smalltalk code in a file system" is another efficiency discussion as we can see in the opinions about the Tonel format.

Git never stores two equal objects twice (in a single repository, of course). Monticello does so happily with 90%+ of the snapshot and ancestry every time you press Save.

This technical shortcoming should be addressed. But it should not drive us to abandon sane diffs, which means separate commits for separate objectives.

Am Do., 21. Nov. 2019 um 21:48 Uhr schrieb Chris Muller <[hidden email]>:
So it turns out that good versioning tools do not need to be slow
and resource hungry. I guess it also shows that a small amount of
brilliant design goes a long way when it comes to performance.

Nonsense.  You haven't magically escaped the laws of software physics.  You were using github, which is run in a datacenter, right?  Dump enough into your git repository, and your use-cases will eventually start to slow down in performance.

I am curious how you're "using git" though because when I accessed a git project through Squeak, it was NOT fast, and it created a gigantic directory tree in my squeak directory which also slowed down my daily backup job tremendously.  The directory names were hugely long and it was problematic.

This is why I won't start actively using git until I can make a transparent MCGitRepository via their v4 API (GraphQL).  I haven't looked at the Schema yet, but I wouldn't be surprised if it, alone, is larger than the entire _implementation_ code of Monticello.  I'd say Avi's was a brilliant design, for sure.

 - Chris





Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

Tobias Pape

> On 22.11.2019, at 13:44, Jakob Reschke <[hidden email]> wrote:
>
> Indeed, Git has its scalability problems as well. That's why Microsoft is developing "VFS for Git"  https://vfsforgit.org/ to address these issues, so they can use it for the massive Windows code base without being blocked by Git. Compared to that code base and its number of concurrent developers, Squeak and its ancestry are tiny, there should be no problems at all. And yet we argue regularly about saving space and time by folding a few Monticello versions together.
>
> While the "laws of software physics" do apply to Git as well, Git still performs much better under their constraints than Monticello. I think people like to call that "more efficient". Monticello's abstract design may be nice, but its current approach to storage (which should be an implementation detail) is not. To make things worse, independent from Monticello, "how to store Smalltalk code in a file system" is another efficiency discussion as we can see in the opinions about the Tonel format.
>
> Git never stores two equal objects twice (in a single repository, of course). Monticello does so happily with 90%+ of the snapshot and ancestry every time you press Save.
>
> This technical shortcoming should be addressed. But it should not drive us to abandon sane diffs, which means separate commits for separate objectives.

What he says.
        -t

Reply | Threaded
Open this post in threaded view
|

Re: Small commits are [bad|good] (was: The Trunk: EToys-mt.368.mcz)

David T. Lewis
In reply to this post by Chris Muller-4
On Thu, Nov 21, 2019 at 02:47:31PM -0600, Chris Muller wrote:
> >
> > So it turns out that good versioning tools do not need to be slow
> > and resource hungry. I guess it also shows that a small amount of
> > brilliant design goes a long way when it comes to performance.
> >
>
> Nonsense.  You haven't magically escaped the laws of software physics.

I'll have to concede the point. The last time I tried to defy the laws of
physics, I was on a motorcyle and it did not end well ;-)


>  You
> were using github, which is run in a datacenter, right?  Dump enough into
> your git repository, and your use-cases will eventually start to slow down
> in performance.
>
> I am curious how you're "using git" though because when I accessed a git
> project through Squeak, it was NOT fast, and it created a gigantic
> directory tree in my squeak directory which also slowed down my daily
> backup job tremendously.  The directory names were hugely long and it was
> problematic.
>

I use /usr/bin/git from the command line when I want to do something, and
I use google to figure out what to do. For visualizing the branch history,
I use some sort of windows client (I forget what it is, I'm away from the
office). The company involved has a private github server, and I do everything
in a local repository, pushing and pulling to github as I go.

Dave


> This is why I won't start actively using git until I can make a transparent
> MCGitRepository via their v4 API (GraphQL).  I haven't looked at the Schema
> yet, but I wouldn't be surprised if it, alone, is larger than the entire
> _implementation_ code of Monticello.  I'd say Avi's was a brilliant design,
> for sure.
>
>  - Chris


12