The Trunk: Tools-mt.920.mcz

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

The Trunk: Tools-mt.920.mcz

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

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

Name: Tools-mt.920
Author: mt
Time: 29 November 2019, 11:40:09.779061 am
UUID: 2a38fb46-276b-3949-a8d1-f1ac037e257a
Ancestors: Tools-tpr.919

In inspector classes, make use of #setContents: (Kernel-mt.1284). Add a way to get/set the user-typed contents in the value pane, which is not the expression pane.

=============== Diff against Tools-tpr.919 ===============

Item was changed:
  ----- Method: DictionaryInspector>>removeSelection (in category 'menu') -----
  removeSelection
  selectionIndex = 0 ifTrue: [^ self changed: #flash].
  object removeKey: (keyArray at: selectionIndex - self numberOfFixedFields).
  selectionIndex := 0.
+ self setContents: ''.
- contents := ''.
  self calculateKeyArray.
  self changed: #inspectObject.
  self changed: #selectionIndex.
  self changed: #fieldList.
  self changed: #selection.!

Item was changed:
  StringHolder subclass: #Inspector
+ instanceVariableNames: 'object selectionIndex timeOfLastListUpdate selectionUpdateTime context expression shouldStyleValuePane contentsTyped'
- instanceVariableNames: 'object selectionIndex timeOfLastListUpdate selectionUpdateTime context expression shouldStyleValuePane'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Tools-Inspector'!
 
  !Inspector commentStamp: '<historical>' prior: 0!
  I represent a query path into the internal representation of an object. As a StringHolder, the string I represent is the value of the currently selected variable of the observed object.!

Item was added:
+ ----- Method: Inspector>>contentsTyped (in category 'accessing') -----
+ contentsTyped
+
+ ^ contentsTyped!

Item was added:
+ ----- Method: Inspector>>contentsTyped: (in category 'accessing') -----
+ contentsTyped: aStringOrText
+
+ contentsTyped := aStringOrText.!

Item was changed:
  ----- Method: Inspector>>modelWakeUpIn: (in category 'accessing') -----
  modelWakeUpIn: aWindow
  | newText |
  self updateListsAndCodeIn: aWindow.
  newText := self contentsIsString
  ifTrue: [newText := self selection]
  ifFalse: ["keep it short to reduce time to compute it"
  self selectionPrintString ].
+ self setContents: newText.!
- newText = contents ifFalse:
- [contents := newText.
- self changed: #contents]!

Item was changed:
  ----- Method: Inspector>>printStringErrorText (in category 'private') -----
  printStringErrorText
  | nm |
  nm := self selectionIndex < 3
  ifTrue: ['self']
+ ifFalse: [self selectedFieldName].
- ifFalse: [self selectedSlotName].
  ^ (nm
  ifNil: ['no selection']
  ifNotNil:
  [nm first isDigit
  ifTrue: ['<error in printString: evaluate "(self at: ' , nm , ') printString" to debug>']
  ifFalse: ['<error in printString: evaluate "' , nm , ' printString" to debug>'] ]) asText!

Item was added:
+ ----- Method: Inspector>>selectFieldNamed: (in category 'selecting') -----
+ selectFieldNamed: aString
+
+ self selectedFieldName = aString ifTrue: [^ self].
+ self toggleIndex: (self fieldList indexOf: aString).!

Item was added:
+ ----- Method: Inspector>>selectedFieldName (in category 'selecting') -----
+ selectedFieldName
+
+ ^ self fieldList at: self selectionIndex ifAbsent: []!

Item was removed:
- ----- Method: Inspector>>selectedSlotName (in category 'selecting') -----
- selectedSlotName
-
- ^ self fieldList at: self selectionIndex ifAbsent: []!

Item was added:
+ ----- Method: Inspector>>setContents: (in category 'initialize-release') -----
+ setContents: aStringOrText
+
+ super setContents: aStringOrText.
+ self contentsTyped: nil.!

Item was added:
+ ----- Method: Inspector>>setContentsTyped: (in category 'initialize-release') -----
+ setContentsTyped: aStringOrText
+ "Simulate typing."
+
+ self contentsTyped: aStringOrText.
+ self changed: #editString with: aStringOrText.!

Item was changed:
  ----- Method: Inspector>>stepAt:in: (in category 'stepping') -----
  stepAt: millisecondClockValue in: aWindow
  | newText |
 
  (Preferences smartUpdating and: [(millisecondClockValue - self timeOfLastListUpdate) > 8000]) "Not more often than once every 8 seconds"
  ifTrue:
  [self updateListsAndCodeIn: aWindow.
  timeOfLastListUpdate := millisecondClockValue].
 
  newText := self contentsIsString
  ifTrue: [self selection]
  ifFalse: ["keep it short to reduce time to compute it"
  self selectionPrintString ].
+ self setContents: newText.!
- newText = contents ifFalse:
- [contents := newText.
- self changed: #contents]!

Item was changed:
  ----- Method: Inspector>>toggleIndex: (in category 'selecting') -----
  toggleIndex: anInteger
  "The receiver has a list of variables of its inspected object. One of these
  is selected. If anInteger is the index of this variable, then deselect it.
  Otherwise, make the variable whose index is anInteger be the selected
  item."
 
+ | newText |
  selectionUpdateTime := 0.
  selectionIndex = anInteger
  ifTrue:
  ["same index, turn off selection"
  selectionIndex := 0.
+ newText := '']
- contents := '']
  ifFalse:
  ["different index, new selection"
  shouldStyleValuePane := false.
  selectionIndex := anInteger.
  self contentsIsString
+ ifTrue: [newText := self selection]
+ ifFalse: [newText := self selectionPrintString]].
+ self setContents: newText.
- ifTrue: [contents := self selection]
- ifFalse: [contents := self selectionPrintString]].
  self changed: #selection.
- self changed: #contents.
  self changed: #selectionIndex.!

Item was changed:
  ----- Method: Inspector>>typeValue: (in category 'selecting') -----
  typeValue: aTextOrString
 
  shouldStyleValuePane := true.
+ contentsTyped := aTextOrString.
+ self changed: #style.!
- self changed: #style!

Item was changed:
  ----- Method: Inspector>>update (in category 'accessing') -----
  update
  "Reshow contents, assuming selected value may have changed."
 
+ | newText |
  selectionIndex = 0
  ifFalse:
  [self contentsIsString
+ ifTrue: [newText := self selection]
+ ifFalse: [newText := self selectionPrintString].
+ self setContents: newText.
- ifTrue: [contents := self selection]
- ifFalse: [contents := self selectionPrintString].
- self changed: #contents.
  self changed: #selection.
  self changed: #selectionIndex]!

Item was changed:
  ----- Method: SetInspector>>removeSelection (in category 'menu') -----
  removeSelection
  (selectionIndex <= object class instSize) ifTrue: [^ self changed: #flash].
  object remove: self selection.
  selectionIndex := 0.
+ self setContents: ''.
- contents := ''.
  self changed: #inspectObject.
  self changed: #fieldList.
  self changed: #selection.
  self changed: #selectionIndex.!