The Inbox: Tools-ct.935.mcz

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

The Inbox: Tools-ct.935.mcz

commits-2
Christoph Thiede uploaded a new version of Tools to project The Inbox:
http://source.squeak.org/inbox/Tools-ct.935.mcz

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

Name: Tools-ct.935
Author: ct
Time: 20 January 2020, 4:31:15.448972 pm
UUID: 00d7a637-e3ae-dd42-abaf-8aa2523cf17e
Ancestors: Tools-mt.929

MessageTrace: Improves display of parent/child messages by using unified message labels everywhere.

=============== Diff against Tools-mt.929 ===============

Item was changed:
  ----- Method: MessageSet>>initializeMessageList: (in category 'private') -----
  initializeMessageList: anArray
  "Initialize my messageList from the given list of MethodReference or string objects.  NB: special handling for uniclasses.
  Do /not/ replace the elements of anArray if they are already MethodReferences, so as to allow users to construct richer systems, such as differencers between existing and edited versions of code."
  messageList := OrderedCollection new.
  anArray do:
  [:each | each isMethodReference
  ifTrue: [messageList addLast: each]
  ifFalse:
  [ MessageSet
  parse: each
  toClassAndSelector:
  [ : class : sel | class ifNotNil: [ messageList addLast: (MethodReference class: class selector: sel) ] ] ] ].
  "Unify labels if wanted."
  self class useUnifiedMessageLabels ifTrue:
  [ messageList withIndexDo:
+ [ : each : index |
+ each stringVersion: (self indentionPrefixOfSize: (self indentionsIn: each stringVersion)) , (self unifiedMessageLabelFor: each) ] ].
- [ : each : index | | cls |
- cls := each actualClass.
- each stringVersion:
- (self indentionPrefixOfSize: (self indentionsIn: each stringVersion))
- , (cls
- ifNil: [each asString]
- ifNotNil:
- [cls isUniClass
- ifTrue: [cls typicalInstanceName, ' ', each selector]
- ifFalse:
- [ cls name , ' ' , each selector , ' {'
- , ((cls organization categoryOfElement: each selector) ifNil: ['']) , '}'
- , ' {', cls category, '}' ] ]) ] ].
  messageListIndex := messageList isEmpty ifTrue: [0] ifFalse: [1].
  contents := String empty!

Item was added:
+ ----- Method: MessageSet>>unifiedMessageLabelFor: (in category 'private') -----
+ unifiedMessageLabelFor: aMethodReference
+
+ | class selector |
+ class := aMethodReference actualClass.
+ selector := aMethodReference selector.
+ class ifNil: [^ aMethodReference asString].
+ class isUniClass
+ ifTrue: [^ class typicalInstanceName, ' ', selector].
+ ^ '{1} {2} \{{3}\} \{{4}\}' format: {
+ class.
+ selector.
+ class organization categoryOfElement: selector.
+ class category }!

Item was changed:
  ----- Method: MessageTrace>>addChildMessages:autoSelectString: (in category 'building') -----
  addChildMessages: methodReferences autoSelectString: aString
  | currentIndentionLevel addables selectables selectableString newAnchor |
  selectableString := aString keywords
  ifEmpty: [ String empty ]
  ifNotEmptyDo: [ : keywords |
  "we can probably do something more precise here; perhaps recombining the extracted keywords into a single selector? Then again all usages of this method seem to already enforce use of a selector"
  aString ].
  [ (messageListIndex between: 1 and: autoSelectStrings size) ]
  whileFalse: [ autoSelectStrings add: selectableString ].
  currentIndentionLevel := self currentIndentionLevel.
  "Don't add mulitple copies of the same method, if a method is already in the list we will merely select it."
  addables := methodReferences reject: [ : each | messageList includes: each ].
  addables do:
  [ : each |
+ each stringVersion: (self indentionPrefixOfSize: currentIndentionLevel + 1)
+ , (self class useUnifiedMessageLabels
+ ifTrue: [self unifiedMessageLabelFor: each]
+ ifFalse: [each asStringOrText]).
- each stringVersion: (self indentionPrefixOfSize: currentIndentionLevel + 1) , each asStringOrText.
  messageList
  add: each
  afterIndex: self messageListIndex.
  autoSelectStrings
  add: nil
  afterIndex: self messageListIndex.
  messageSelections
  add: false
  afterIndex: self messageListIndex ].
  selectables :=
  addables copy
  addAll: (methodReferences select: [ : each | messageList includes: each ]) ;
  yourself.
  self deselectAll.
  anchorIndex := nil.
  selectables do:
  [ : each |
  self
  messageAt: (newAnchor := messageList indexOf: each)
  beSelected: true.
  anchorIndex ifNil: [ anchorIndex := newAnchor ] ].
  self changed: #messageList.
  "Select the first child method."
  self messageListIndex:
  (selectables size > 0
  ifTrue: [ messageList indexOf: selectables last ]
  ifFalse: [ messageList ifEmpty: [ 0 ] ifNotEmpty: [ 1 ] ])!

Item was changed:
  ----- Method: MessageTrace>>addParentMessages:autoSelectString: (in category 'building') -----
  addParentMessages: methodReferences autoSelectString: aString
  | currentIndentionLevel addables selectables |
  addables := methodReferences reject: [ : each | messageList includes: each ].
  "we may need to process aString here in a similar manner to that in #addChildMessages:autoSelectString:"
  selectables := addables copy
  addAll: (methodReferences select: [ : each | messageList includes: each ]) ;
  yourself.
  currentIndentionLevel := self currentIndentionLevel.
  (currentIndentionLevel = 0 and: [ addables notEmpty ]) ifTrue:
  [ self indentEverything.
  currentIndentionLevel := 1 ].
  addables do:
  [ : each |
+ each stringVersion: (self indentionPrefixOfSize: currentIndentionLevel - 1)
+ , (self class useUnifiedMessageLabels
+ ifTrue: [self unifiedMessageLabelFor: each]
+ ifFalse: [each asStringOrText]).
- each stringVersion: (self indentionPrefixOfSize: currentIndentionLevel - 1) , each asStringOrText.
  messageList
  add: each
  afterIndex: self messageListIndex - 1.
  autoSelectStrings
  add: aString
  afterIndex: self messageListIndex - 1.
  messageSelections
  add: false
  afterIndex: self messageListIndex - 1 ].
  self deselectAll.
  selectables do:
  [ : each | | messageIndex |
  messageIndex := messageList indexOf: each.
  self
  messageAt: messageIndex
  beSelected: true.
  autoSelectStrings
  at: messageIndex
  put: aString ].
  self changed: #messageList.
  anchorIndex := messageListIndex.
  selectables size > 0 ifTrue:
  [ self messageListIndex: (messageList indexOf: selectables first) ]!