[squeak-dev] The Inbox: Tools-nice.956.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Fri Mar 6 09:16:36 UTC 2020


Hi Chistoph,
no problem, critic is welcome and must be exercized, I don't want to be a
sacred cow or abuse from notoriety!
As said in preamble, these are very superficial changes (sort of minimal)
to work around the lack of extensibility in current code base.

I had not enough time to review Tools-ct.900, and just salvaged this little
work in the inbox before throwing the image away.
This is more for nurturing thoughts.than competing with your own changes.


Le ven. 6 mars 2020 à 09:41, Thiede, Christoph <
Christoph.Thiede at student.hpi.uni-potsdam.de> a écrit :

> Hi Nicolas, thanks for your submission! :-)
>
>
> I took a short look at it. It's definitively an improvement compared to
> the state of the art!
>
> Actually, TBH I think that my proposal enables us to get completely rid of
> all the hard-coded indices stuff, whereas you collate this stuff a bit
> only. In contrast, an InspectorField will free us completely from that mess.
>
> I definitively like the idea of #extraInspectorFields! This way we can
> extend the inspector for a certain class without subclassing Inspector at
> all.
>
>
> However, both approaches have merging conflicts. Personally, I would
> suggest getting the InspectorField quickly reviewed and merging it into
> Trunk. After that, we could rewrite your approach of #extraInspectorFields
> to make it use InspectorField.
>
> (Please do not misunderstand me: I absolutely value your work and
> motivation to improve the inspector. I wish we can combine the best of our
> both approaches. And, to make it even more complicated, Chris mentioned
> some enhancements he wrote for the inspector fields in past, too ...)
>
>
> Happy Squeak! :-)
>
> Best,
>
> Christoph
> ------------------------------
> *Von:* Squeak-dev <squeak-dev-bounces at lists.squeakfoundation.org> im
> Auftrag von commits at source.squeak.org <commits at source.squeak.org>
> *Gesendet:* Freitag, 6. März 2020 00:13:35
> *An:* squeak-dev at lists.squeakfoundation.org
> *Betreff:* [squeak-dev] The Inbox: Tools-nice.956.mcz
>
> Nicolas Cellier uploaded a new version of Tools to project The Inbox:
> http://source.squeak.org/inbox/Tools-nice.956.mcz
>
> ==================== Summary ====================
>
> Name: Tools-nice.956
> Author: nice
> Time: 6 March 2020, 12:13:33.047985 am
> UUID: 68a4728a-05bb-4255-ba4a-211be07f2d24
> Ancestors: Tools-mt.955
>
> My own superficial refactoring of Inspector (June 2019), probably less
> deep than ct.
>
> Consider that the field list is decomposed into
> - fixedFields
> - variableFields
>
> The fixedFields include
> - baseFields: self, all inst var, the instance variables
> - extraFields: these are fields to be performed (message selectors) - ask
> object class for #extraInspectorFields
>
> The variableFields are the keys (index)  for collections, or can be
> composite for a Context
>
> With those simple rules, selection index handling is still a bit
> convoluted. But we have enough genericity so as to encapsulate uggliness in
> superclass, and let the subclasses concentrate on the contents.
>
> =============== Diff against Tools-mt.955 ===============
>
> Item was removed:
> - ----- Method: ContextInspector>>fieldList (in category 'accessing') -----
> - fieldList
> -        "Answer the base field list plus an abbreviated list of indices."
> -        | tempNames stackIndices |
> -        tempNames := object tempNames collect:[:t| '[',t,']'].
> -        stackIndices := (object numTemps + 1 to: object stackPtr)
> collect: [:i| i printString].
> -        ^self baseFieldList, tempNames, stackIndices!
>
> Item was removed:
> - ----- Method: ContextInspector>>selection (in category 'accessing') -----
> - selection
> -        "The receiver has a list of variables of its inspected object.
> -        One of these is selected. Answer the value of the selected
> variable."
> -        | basicIndex |
> -        selectionIndex = 0 ifTrue: [^ ''].
> -        selectionIndex = 1 ifTrue: [^ object].
> -        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo:
> 20000].
> -        selectionIndex - 2 <= object class instSize ifTrue:
> -                [^object instVarAt: selectionIndex - 2].
> -        basicIndex := selectionIndex - 2 - object class instSize.
> -        basicIndex <= object numTemps ifTrue:
> -                [^object debuggerMap namedTempAt: basicIndex in: object].
> -        basicIndex <= object stackPtr ifTrue:
> -                [^object at: basicIndex].
> -        ^nil
> - !
>
> Item was added:
> + ----- Method: ContextInspector>>variableFieldList (in category
> 'accessing') -----
> + variableFieldList
> +        "Separate the temps from the rest of the stack"
> +        | tempNames stackIndices |
> +        tempNames := object tempNames collect:[:t| '[',t,']'].
> +        stackIndices := (object numTemps + 1 to: object stackPtr)
> collect: [:i| i printString].
> +        ^tempNames, stackIndices!
>
> Item was added:
> + ----- Method: ContextInspector>>variableFieldSelection: (in category
> 'accessing') -----
> + variableFieldSelection: rank
> +        rank <= object numTemps ifTrue:
> +                [^object debuggerMap namedTempAt: rank in: object].
> +        rank <= object stackPtr ifTrue:
> +                [^object at: rank].
> +        ^nil
> + !
>
> Item was removed:
> - ----- Method: DictionaryInspector>>fieldList (in category 'accessing')
> -----
> - fieldList
> -        ^ self baseFieldList
> -                , (keyArray collect: [:key | key printString])!
>
> Item was removed:
> - ----- Method: DictionaryInspector>>numberOfFixedFields (in category
> 'private') -----
> - numberOfFixedFields
> -        ^ 2 + object class instSize!
>
> Item was removed:
> - ----- Method: DictionaryInspector>>selection (in category 'selecting')
> -----
> - selection
> -
> -        selectionIndex <= (self numberOfFixedFields) ifTrue: [^ super
> selection].
> -        ^ object at: (keyArray at: selectionIndex - self
> numberOfFixedFields) ifAbsent:[nil]!
>
> Item was added:
> + ----- Method: DictionaryInspector>>variableFieldList (in category
> 'accessing') -----
> + variableFieldList
> +        ^ keyArray collect: [:key | key printString]!
>
> Item was added:
> + ----- Method: DictionaryInspector>>variableFieldSelection: (in category
> 'selecting') -----
> + variableFieldSelection: rank
> +        ^ object at: (keyArray at: rank) ifAbsent:[nil]!
>
> Item was added:
> + ----- Method: Float>>extraInspectorFields (in category
> '*Tools-Inspector') -----
> + extraInspectorFields
> +        ^super extraInspectorFields , #(signBit exponent significand
> successor predecessor)!
>
> Item was changed:
>   ----- Method: Inspector>>baseFieldList (in category 'accessing') -----
>   baseFieldList
>          "Answer an Array consisting of 'self'
>          and the instance variable names of the inspected object."
>
>          ^ (Array with: 'self' with: 'all inst vars')
>                          , object class allInstVarNames!
>
> Item was changed:
>   ----- Method: Inspector>>copyName (in category 'menu commands') -----
>   copyName
>          "Copy the name of the current variable, so the user can paste it
> into the
>          window below and work with is. If collection, do (xxx at: 1)."
>          | sel aClass variableNames |
> +        selectionIndex <= 2
> -        self selectionUnmodifiable
>                  ifTrue: [^ self changed: #flash].
>          aClass := self object class.
>          variableNames := aClass allInstVarNames.
> +        (aClass isVariable and: [selectionIndex > self
> numberOfFixedFields])
> -        (aClass isVariable and: [selectionIndex > (variableNames size +
> 2)])
>                  ifTrue: [sel := '(self basicAt: ' , (selectionIndex -
> (variableNames size + 2)) asString , ')']
> +                ifFalse: [selectionIndex - 2 <= variableNames size
> +                        ifTrue: [sel := variableNames at: selectionIndex
> - 2]
> +                        ifFalse: [sel := '(self ' , (self fieldList at:
> selectionIndex) , ')']].
> -                ifFalse: [sel := variableNames at: selectionIndex - 2].
>          (self selection isKindOf: Collection)
>                  ifTrue: [sel := '(' , sel , ' at: 1)'].
>          Clipboard clipboardText: sel asText!
>
> Item was changed:
>   ----- Method: Inspector>>defsOfSelection (in category 'menu commands')
> -----
>   defsOfSelection
>          "Open a browser on all defining references to the selected
> instance variable, if that's what currently selected. "
> +        | sel |
> +        self hasAnInstanceVariableSelected ifFalse: [^ self changed:
> #flash].
> +        sel := object class allInstVarNames at: self selectionIndex - 2.
> +        self systemNavigation browseAllStoresInto: sel from: object class!
> -        | aClass sel |
> -
> -        self selectionUnmodifiable ifTrue: [^ self changed: #flash].
> -        (aClass := self object class) isVariable ifTrue: [^ self changed:
> #flash].
> -
> -        sel := aClass allInstVarNames at: self selectionIndex - 2.
> -        self systemNavigation  browseAllStoresInto: sel from: aClass!
>
> Item was added:
> + ----- Method: Inspector>>extraFieldList (in category 'accessing') -----
> + extraFieldList
> +        "Answer an Array of optional messages to be sent to object."
> +
> +        ^ (object respondsTo: #extraInspectorFields)
> +                ifTrue: [object extraInspectorFields]
> +                ifFalse: [Array empty]!
>
> Item was changed:
>   ----- Method: Inspector>>fieldList (in category 'accessing') -----
>   fieldList
>          "Answer the base field list plus an abbreviated list of indices."
>
> +        ^ self fixedFieldList , self variableFieldList!
> -        object class isVariable ifFalse: [^ self baseFieldList].
> -        ^ self baseFieldList ,
> -                (object basicSize <= (self i1 + self i2)
> -                        ifTrue: [(1 to: object basicSize)
> -                                                collect: [:i | i
> printString]]
> -                        ifFalse: [(1 to: self i1) , (object
> basicSize-(self i2-1) to: object basicSize)
> -                                                collect: [:i | i
> printString]])!
>
> Item was added:
> + ----- Method: Inspector>>fixedFieldList (in category 'accessing') -----
> + fixedFieldList
> +        "Answer an Array consisting of all the fixed fields, including
> extra."
> +
> +        ^ self baseFieldList , self extraFieldList!
>
> Item was added:
> + ----- Method: Inspector>>fixedFieldSelection (in category 'selecting')
> -----
> + fixedFieldSelection
> +        "Selection when the selectionIndex is inside the fixedFieldList"
> +        selectionIndex = 0 ifTrue: [^ ''].
> +        selectionIndex = 1 ifTrue: [^ object].
> +        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo:
> 20000].
> +        (selectionIndex - 2) <= object class instSize
> +                ifTrue: [^ object instVarAt: selectionIndex - 2].
> +        ^object perform: (self fieldList at: selectionIndex)!
>
> Item was added:
> + ----- Method: Inspector>>hasAnInstanceVariableSelected (in category
> 'selecting') -----
> + hasAnInstanceVariableSelected
> +        ^selectionIndex between: 3 and: 2 + object class instSize!
>
> Item was added:
> + ----- Method: Inspector>>numberOfFixedFields (in category 'accessing')
> -----
> + numberOfFixedFields
> +        ^ 2 + object class instSize + self extraFieldList size!
>
> Item was changed:
>   ----- Method: Inspector>>referencesToSelection (in category 'menu
> commands') -----
>   referencesToSelection
> +        "Open a browser on all references to the selected instance
> variable, if that's what currently selected."
> +        | sel |
> +        self hasAnInstanceVariableSelected ifFalse: [^ self changed:
> #flash].
> +        sel := object class allInstVarNames at: self selectionIndex - 2.
> +        self systemNavigation browseAllAccessesTo: sel from: object class!
> -        "Open a browser on all references to the selected instance
> variable, if that's what currently selected.  1/25/96 sw"
> -        | aClass sel |
> -
> -        self selectionUnmodifiable ifTrue: [^ self changed: #flash].
> -        (aClass := self object class) isVariable ifTrue: [^ self changed:
> #flash].
> -
> -        sel := aClass allInstVarNames at: self selectionIndex - 2.
> -        self systemNavigation   browseAllAccessesTo: sel from: aClass!
>
> Item was changed:
>   ----- Method: Inspector>>replaceSelectionValue: (in category
> 'selecting') -----
>   replaceSelectionValue: anObject
>          "The receiver has a list of variables of its inspected object.
> One of these
>          is selected. The value of the selected variable is set to the
> value,
>          anObject."
>          | basicIndex si instVarIndex |
>          selectionIndex <= 2 ifTrue: [
>                  self toggleIndex: (si := selectionIndex).
>                  self toggleIndex: si.
>                  ^ object].
>          instVarIndex := selectionIndex - 2.
>          instVarIndex > object class instSize
>                  ifFalse: [^ object instVarAt: instVarIndex put: anObject].
> +        basicIndex := selectionIndex - self numberOfFixedFields.
> +        (object class isVariable and: [basicIndex between: 1 and: object
> basicSize])
> +                ifTrue: [self error: 'Cannot replace selection'].
> -        object class isVariable or: [self error: 'Cannot replace
> selection'].
> -        basicIndex := selectionIndex - 2 - object class instSize.
>          (object basicSize <= (self i1 + self i2)  or: [basicIndex <= self
> i1])
>                  ifTrue: [^object basicAt: basicIndex put: anObject]
>                  ifFalse: [^object basicAt: object basicSize - (self i1 +
> self i2) + basicIndex
>                                          put: anObject]!
>
> Item was changed:
>   ----- Method: Inspector>>selection (in category 'selecting') -----
>   selection
>          "The receiver has a list of variables of its inspected object.
>          One of these is selected. Answer the value of the selected
> variable."
> +        | index |
> +        index := selectionIndex - self numberOfFixedFields.
> +        index <= 0
> +                ifTrue: [^self fixedFieldSelection]
> +                ifFalse: [^self variableFieldSelection: index] !
> -        | basicIndex |
> -        selectionIndex = 0 ifTrue: [^ ''].
> -        selectionIndex = 1 ifTrue: [^ object].
> -        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo:
> 20000].
> -        (selectionIndex - 2) <= object class instSize
> -                ifTrue: [^ object instVarAt: selectionIndex - 2].
> -        basicIndex := selectionIndex - 2 - object class instSize.
> -        (object basicSize <= (self i1 + self i2)  or: [basicIndex <= self
> i1])
> -                ifTrue: [^ object basicAt: basicIndex]
> -                ifFalse: [^ object basicAt: object basicSize - (self i1 +
> self i2) + basicIndex]!
>
> Item was changed:
>   ----- Method: Inspector>>selectionUnmodifiable (in category 'selecting')
> -----
>   selectionUnmodifiable
>          "Answer if the current selected variable is modifiable via
> acceptance in the code pane.  For most inspectors, no selection and a
> selection of 'self' (selectionIndex = 1) and 'all inst vars'
> (selectionIndex = 2) are unmodifiable"
>
> +        ^ selectionIndex <= 2 or: [selectionIndex between: 3 + object
> class instSize and: self numberOfFixedFields]!
> -        ^ selectionIndex <= 2!
>
> Item was added:
> + ----- Method: Inspector>>variableFieldList (in category 'accessing')
> -----
> + variableFieldList
> +        "Answer an abbreviated list of indices for variable classes."
> +
> +        object class isVariable ifFalse: [^Array empty].
> +        ^(object basicSize <= (self i1 + self i2)
> +                        ifTrue: [(1 to: object basicSize)
> +                                                collect: [:i | i
> printString]]
> +                        ifFalse: [(1 to: self i1) , (object
> basicSize-(self i2-1) to: object basicSize)
> +                                                collect: [:i | i
> printString]])!
>
> Item was added:
> + ----- Method: Inspector>>variableFieldSelection: (in category
> 'selecting') -----
> + variableFieldSelection: rank
> +        "The receiver has a list of variables fields
> +        Answer the variable field at given rank."
> +        (object basicSize <= (self i1 + self i2)  or: [rank <= self i1])
> +                ifTrue: [^ object basicAt: rank]
> +                ifFalse: [^ object basicAt: object basicSize - (self i1 +
> self i2) + rank]!
>
> Item was added:
> + ----- Method: Integer>>extraInspectorFields (in category
> '*Tools-inspector') -----
> + extraInspectorFields
> +        ^super extraInspectorFields , #(hex highBitOfMagnitude)!
>
> Item was added:
> + ----- Method: Object>>extraInspectorFields (in category
> '*Tools-inspecting') -----
> + extraInspectorFields
> +        "Answer a list of fields to be performed for inspectors"
> +        ^#(identityHash)!
>
> Item was removed:
> - ----- Method: OrderedCollectionInspector>>fieldList (in category
> 'accessing') -----
> - fieldList
> -        object ifNil: [ ^ OrderedCollection new].
> -        ^ self baseFieldList ,
> -                (self objectSize <= (self i1 + self i2)
> -                        ifTrue: [(1 to: self objectSize)
> -                                                collect: [:i | i
> printString]]
> -                        ifFalse: [(1 to: self i1) , (self objectSize -
> (self i2-1) to: self objectSize)
> -                                                collect: [:i | i
> printString]])
> - "
> - OrderedCollection new inspect
> - (OrderedCollection newFrom: #(3 5 7 123)) inspect
> - (OrderedCollection newFrom: (1 to: 1000)) inspect
> - "!
>
> Item was added:
> + ----- Method: OrderedCollectionInspector>>removeSelection (in category
> 'menu commands') -----
> + removeSelection
> +        selectionIndex <= self numberOfFixedFields ifTrue: [^ self
> changed: #flash].
> +        object removeAt: self selectedObjectIndex.
> +        selectionIndex := 0.
> +        contents := ''.
> +        self changed: #inspectObject.
> +        self changed: #fieldList.
> +        self changed: #selection.
> +        self changed: #selectionIndex.!
>
> Item was changed:
>   ----- Method: OrderedCollectionInspector>>replaceSelectionValue: (in
> category 'selecting') -----
>   replaceSelectionValue: anObject
>          "The receiver has a list of variables of its inspected object.
> One of these
>          is selected. The value of the selected variable is set to the
> value, anObject."
>
> +        selectionIndex <= self numberOfFixedFields
> -        (selectionIndex - 2) <= object class instSize
>                  ifTrue: [^ super replaceSelectionValue: anObject].
>          object at: self selectedObjectIndex put: anObject!
>
> Item was changed:
>   ----- Method: OrderedCollectionInspector>>selectedObjectIndex (in
> category 'selecting') -----
>   selectedObjectIndex
>          "Answer the index of the inspectee's collection that the current
> selection refers to."
>
>          | basicIndex |
> +        basicIndex := selectionIndex - self numberOfFixedFields.
> +        ^ (self objectSize <= (self i1 + self i2)  or: [basicIndex <=
> self i1])
> -        basicIndex := selectionIndex - 2 - object class instSize.
> -        ^ (object size <= (self i1 + self i2)  or: [basicIndex <= self
> i1])
>                  ifTrue: [basicIndex]
> +                ifFalse: [self objectSize - (self i1 + self i2) +
> basicIndex]!
> -                ifFalse: [object size - (self i1 + self i2) + basicIndex]!
>
> Item was removed:
> - ----- Method: OrderedCollectionInspector>>selection (in category
> 'selecting') -----
> - selection
> -        "The receiver has a list of variables of its inspected object.
> -        One of these is selected. Answer the value of the selected
> variable."
> -
> -        (selectionIndex - 2) <= object class instSize
> -                ifTrue: [^ super selection].
> -        ^ object at: self selectedObjectIndex!
>
> Item was added:
> + ----- Method: OrderedCollectionInspector>>variableFieldList (in category
> 'accessing') -----
> + variableFieldList
> +        object ifNil: [ ^ OrderedCollection new].
> +        ^(self objectSize <= (self i1 + self i2)
> +                        ifTrue: [(1 to: self objectSize)
> +                                                collect: [:i | i
> printString]]
> +                        ifFalse: [(1 to: self i1) , (self objectSize -
> (self i2-1) to: self objectSize)
> +                                                collect: [:i | i
> printString]])
> + "
> + OrderedCollection new inspect
> + (OrderedCollection newFrom: #(3 5 7 123)) inspect
> + (OrderedCollection newFrom: (1 to: 1000)) inspect
> + "!
>
> Item was added:
> + ----- Method: OrderedCollectionInspector>>variableFieldSelection: (in
> category 'selecting') -----
> + variableFieldSelection: rank
> +        "The receiver has a list of variables of its inspected object.
> +        One of these is selected. Answer the value of the selected
> variable."
> +
> +        | index |
> +        index := (object size <= (self i1 + self i2)  or: [rank <= self
> i1])
> +                ifTrue: [rank]
> +                ifFalse: [object size - (self i1 + self i2) + rank].
> +        ^object at: index!
>
> Item was removed:
> - ----- Method: SetInspector>>fieldList (in category 'accessing') -----
> - fieldList
> -        object
> -                ifNil: [^ Set new].
> -        ^ self baseFieldList
> -                , (object array
> -                                withIndexCollect: [:each :i | each
> ifNotNil: [i printString]])
> -                  select: [:each | each notNil]!
>
> Item was changed:
>   ----- Method: SetInspector>>removeSelection (in category 'menu') -----
>   removeSelection
> +        selectionIndex <= self numberOfFixedFields ifTrue: [^ self
> changed: #flash].
> -        (selectionIndex <= object class instSize) ifTrue: [^ self
> changed: #flash].
>          object remove: self selection.
>          selectionIndex := 0.
> +        contents := ''.
> -        self setContents: ''.
>          self changed: #inspectObject.
>          self changed: #fieldList.
>          self changed: #selection.
>          self changed: #selectionIndex.!
>
> Item was removed:
> - ----- Method: SetInspector>>selection (in category 'selecting') -----
> - selection
> -        selectionIndex = 0 ifTrue: [^ ''].
> -        selectionIndex = 1 ifTrue: [^ object].
> -        selectionIndex = 2 ifTrue: [^ object longPrintString].
> -        (selectionIndex - 2) <= object class instSize
> -                ifTrue: [^ object instVarAt: selectionIndex - 2].
> -
> -        ^ object array at: self arrayIndexForSelection ifAbsent: [ String
> empty ]!
>
> Item was added:
> + ----- Method: SetInspector>>variableFieldList (in category 'accessing')
> -----
> + variableFieldList
> +        object ifNil: [^ Set new].
> +        ^ (object array
> +                                withIndexCollect: [:each :i | each
> ifNotNil: [i printString]])
> +                  select: [:each | each notNil]!
>
> Item was added:
> + ----- Method: SetInspector>>variableFieldSelection: (in category
> 'selecting') -----
> + variableFieldSelection: rank
> +        "Note: the index is decoded from selected field name, because I
> am un-ordered"
> +        ^ object array at: self arrayIndexForSelection ifAbsent: [ String
> empty ]!
>
> Item was removed:
> - ----- Method: WeakSetInspector>>fieldList (in category 'accessing') -----
> - fieldList
> -        | slotIndices |
> -        object ifNil: [^ Set new].
> -
> -        "Implementation note: do not use objectArray withIndexCollect: as
> super
> -        because this might collect indices in a WeakArray, leading to
> constantly changing fieldList
> -        as explained at http://bugs.squeak.org/view.php?id=6812"
> -
> -        slotIndices := (Array new: object size) writeStream.
> -        object array withIndexDo: [:each :i |
> -                (each notNil and: [each ~= flagObject]) ifTrue:
> [slotIndices nextPut: i printString]].
> -
> -        ^ self baseFieldList
> -                , slotIndices contents!
>
> Item was added:
> + ----- Method: WeakSetInspector>>variableFielsList (in category
> 'accessing') -----
> + variableFielsList
> +        | slotIndices |
> +        object ifNil: [^ Set new].
> +
> +        "Implementation note: do not use objectArray withIndexCollect: as
> super
> +        because this might collect indices in a WeakArray, leading to
> constantly changing fieldList
> +        as explained at http://bugs.squeak.org/view.php?id=6812"
> +
> +        slotIndices := (Array new: object size) writeStream.
> +        object array withIndexDo: [:each :i |
> +                (each notNil and: [each ~= flagObject]) ifTrue:
> [slotIndices nextPut: i printString]].
> +
> +        ^  slotIndices contents!
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20200306/951cbc3e/attachment-0001.html>


More information about the Squeak-dev mailing list