Please refer to the attached changesets for the review. I split up the original change set into two parts, improved the documentation, and fixed the handling of trait wrappers.

I'm also attaching a third changeset that you can use to explore the behavior of the TestRunner for coverage testing with traits.

If you don't have any objections, I am planning to merge this next week. :-)

Best,
Christoph

=============== Summary {Traits-eventualUsers.3.cs} ===============

Change Set:        Traits-eventualUsers
Date:            29 September 2022
Author:            Christoph Thiede

Adds new accessors to Traits for accessing all direct and indirect users of a trait or a trait's method:

* TraitDescription allUsers, TraitDescription eventualUsers
* CompiledMethod eventualUsers, CompiledMethod eventualOriginalTraitMethod
* MethodReference eventualUsers, MethodReference eventualUserReferences

Also includes tests.

=============== Diff ===============

CompiledMethod>>eventualOriginalTraitMethod {*Traits-NanoKernel} · ct 9/29/2022 10:53
+ eventualOriginalTraitMethod
+     "Answer the eventual original trait method for the receiver that is not a trait method itself, or nil if none."
+     ^ self originalTraitMethod ifNotNil: [:method |
+         method eventualOriginalTraitMethod ifNil: [method]]


CompiledMethod>>eventualUsers {*Traits-NanoKernel} · TraitTest 9/9/2022 23:37
+ eventualUsers
+
+     ^ self methodClass eventualUsersForSelector: self selector


CompiledMethod>>isTraitMethod {*Traits-testing} · ct 9/22/2022 16:01 (changed)
isTraitMethod
+     "Answer a Boolean indicating whether the receiver is derived (i.e., copied) from a Trait.
+     
+     Note: For testing whether a method *belongs* to a trait, send [aCompiledMethod methodClass isTrait] instead."

    ^ self originalTraitMethod notNil

MethodReference>>eventualUserReferences {*Traits-NanoKernel} · ct 9/9/2022 22:12
+ eventualUserReferences
+
+     ^ self eventualUsers collect: [:classDescription |
+         (classDescription >> self selector) methodReference]


MethodReference>>eventualUsers {*Traits-NanoKernel} · ct 9/9/2022 20:11
+ eventualUsers
+
+     ^ self compiledMethod eventualUsers


TraitDescription>>allUsers {accessing} · ct 9/9/2022 23:06
+ allUsers
+     "Answer all ClassDescriptions that directly or indirectly (i.e., through a path of other traits) use the receiver."
+
+     ^ self users gather: [:classDescription |
+         classDescription isTrait
+             ifTrue: [classDescription allUsers copyWithFirst: classDescription]
+             ifFalse: [{classDescription}]]


TraitDescription>>eventualUsers {accessing} · ct 9/9/2022 23:07
+ eventualUsers
+     "Answer all non-trait ClassDescriptions that directly or indirectly (i.e., through a path of other traits) use the receiver."
+
+     ^ self users gather: [:classDescription |
+         classDescription isTrait
+             ifTrue: [classDescription eventualUsers]
+             ifFalse: [{classDescription}]]


TraitDescription>>eventualUsersForSelector: {accessing} · ct 9/29/2022 10:52
+ eventualUsersForSelector: aSymbol
+     "Answer all eventual users that use the receiver's implementation for aSymbol, i.e., exclude all users that redefine that message."
+
+     | originalMethod |
+     originalMethod := self >> aSymbol.
+     ^ self eventualUsers select: [:classDescription |
+         | userMethod |
+         (userMethod := classDescription compiledMethodAt: aSymbol ifAbsent: []) notNil and:
+             [userMethod eventualOriginalTraitMethod == originalMethod]]


TraitTest>>testAllUsers {testing} · TraitTest 9/9/2022 23:17
+ testAllUsers
+     self assert: self t1 allUsers size = 4.
+     self assert: (self t1 allUsers includesAllOf: {self t4. self t5. self c2. self t6 }).
+     self assert: self t3 allUsers isEmpty.
+     self assert: self t5 allUsers size = 1.
+     self assert: self t5 allUsers anyOne = self c2.
+     self c2 uses: self t1 + self t5.
+     self assert: self t5 allUsers size = 1.
+     self assert: self t5 allUsers anyOne = self c2.
+     self c2 uses: self t2 asTraitComposition.
+     self assert: self t5 allUsers isEmpty


TraitTest>>testEventualUserReferences {testing} · TraitTest 9/9/2022 23:41
+ testEventualUserReferences
+     self assert: (self t1 >> #m11) methodReference eventualUserReferences isEmpty.
+     self assert: (self t1 >> #m12) methodReference eventualUserReferences isEmpty.
+     self assert: (self t2 >> #m21) methodReference eventualUserReferences isEmpty.
+     self assert: (self t3 >> #m31) methodReference eventualUserReferences isEmpty.
+     self assert: (self t5 >> #m11) methodReference eventualUserReferences isEmpty.
+     self assert: (self t5 >> #m12) methodReference eventualUserReferences size = 1.
+     self assert: (self t5 >> #m12) methodReference eventualUserReferences anyOne = (self c2 >> #m12) methodReference.
+     self assert: (self t5 >> #m21) methodReference eventualUserReferences size = 1.
+     self assert: (self t5 >> #m21) methodReference eventualUserReferences anyOne = (self c2 >> #m21) methodReference.
+     self assert: (self t5 >> #m51) methodReference eventualUserReferences size = 1.
+     self assert: (self t5 >> #m51) methodReference eventualUserReferences anyOne = (self c2 >> #m51) methodReference.


TraitTest>>testEventualUsers {testing} · TraitTest 9/9/2022 23:18
+ testEventualUsers
+     self assert: self t5 eventualUsers size = 1.
+     self assert: self t5 eventualUsers anyOne = self c2.
+     self assert: self t1 eventualUsers size = 1.
+     self assert: self t1 eventualUsers anyOne = self c2.
+     self assert: self t3 eventualUsers isEmpty.



=============== Summary {traits.2.cs} ===============

Change Set:        SUnit coverage for traits
Date:            29 September 2022
Author:            Christoph Thiede

Adds proper support for Traits to SUnit's test coverage. As the methods from a trait are copied to all its eventual users, all copies should be treated as a single coverable item to the TestRunner, just like a method from a superclass that is inherited by multiple subclasses.

Implementation:
* Exclude derived trait methods in TestRunner>>#addMethodsUnderTestIn:to:
* Include wrappers for all eventual users of each original trait method in TestRunner>>#collectCoverageFor: and synchronize them with their original method in TestCoverage>>#mark
* No dependency on Traits is introduced, SUnit can still be loaded and used if Traits is not loaded

Depends on Traits-eventualUsers.

=============== Diff ===============

CompiledMethod>>sunitIsTraitMethod {*SUnitGUI-testing} · ct 9/22/2022 16:16
+ sunitIsTraitMethod
+     "Wrapper for #isTraitMethod to avoid dependency on Traits."
+
+     ^ (self respondsTo: #isTraitMethod)
+         and: [self isTraitMethod]


Object>>sunitIsTrait {*SUnitGUI-testing} · ct 9/22/2022 16:18
+ sunitIsTrait
+     "Wrapper for #isTrait to avoid dependency on Traits."
+
+     ^ (self respondsTo: #isTrait)
+         and: [self isTrait]


TestCoverage>>mark {private} · ct 9/29/2022 11:03 (changed)
mark
-     hasRun := true
+     hasRun := true.
+     
+     self sunitIsTraitMethod ifTrue:
+         ["update original (shared) trait method"
+         | original |
+         original := self eventualOriginalTraitMethod methodReference compiledMethod.
+         (original respondsTo: #mark) ifTrue:
+             [original mark; uninstall]].


TestCoverage>>respondsTo: {private} · ct 9/9/2022 22:22
+ respondsTo: aMessage
+
+     ^ (self class canUnderstand: aMessage)
+         or: [method respondsTo: aMessage]


TestRunner>>addMethodsUnderTestIn:to: {actions} · ct 9/22/2022 16:17 (changed)
addMethodsUnderTestIn: packages to: methods
    packages
        do: [:package | package isNil
                ifFalse: [package methods
                        do: [:method | ((#(#packageNamesUnderTest #classNamesNotUnderTest ) includes: method methodSymbol)
-                                     or: [method compiledMethod isAbstract
-                                             or: [method compiledMethod hasLiteral: #ignoreForCoverage]])
+                                     or: [method compiledMethod isAbstract]
+                                     or: [method compiledMethod sunitIsTraitMethod "trait methods are derived from a method in a trait - only the original method is relevant for us"]
+                                     or: [method compiledMethod hasLiteral: #ignoreForCoverage])
                                ifFalse: [methods add: method]]]]

TestRunner>>collectCoverageFor: {actions} · ct 9/22/2022 16:09 (changed)
collectCoverageFor: methods
-     | wrappers suite |
-     wrappers := methods collect: [ :each | TestCoverage on: each ].
+     | allMethods wrappers suite |
+     "Methods in traits are copied to their users. Wrap these copies as well to catch all evaluations of the original trait method."
+     allMethods := methods
+         , ((methods select: [ :each | each actualClass isTrait ])
+             gather: [ :each | each eventualUserReferences ]).
+     wrappers := allMethods collect: [ :each | TestCoverage on: each ].
    suite := self
        reset;
        suiteAll.
    
    [ wrappers do: [ :each | each install ].
-     [ self runSuite: suite ] ensure: [ wrappers do: [ :each | each uninstall ] ] ] valueUnpreemptively.
-     wrappers := wrappers reject: [ :each | each hasRun ].
+     [ self runSuite: suite ] ensure: [ wrappers do: [ :each | each uninstall ] ] ]
+         valueUnpreemptively.
+     wrappers := wrappers reject: [ :each | each hasRun
+         or: [ each isTraitMethod "trait methods' wrappers update their original method wrapper automatically, see TestCoverage>>#mark" ] ].
+     
    wrappers isEmpty
        ifTrue:
            [ UIManager default inform: 'Congratulations. Your tests cover all code under analysis.' ]
        ifFalse:
            [ ToolSet
                browseMessageSet: (wrappers collect: [ :each | each reference ])
                name: 'Not Covered Code (' , (100 - (100 * wrappers size // methods size)) printString , '% Code Coverage)'
                autoSelect: nil ].
    self saveResultInHistory


---
Sent from Squeak Inbox Talk

On 2022-09-09T23:53:26+02:00, christoph.thiede@student.hpi.uni-potsdam.de wrote:

> =============== Summary ===============
>
> Change Set:????????TestCoverage-traits
> Date:????????????9 September 2022
> Author:????????????Christoph Thiede
>
> Adds proper support for trait methods to SUnit's test coverage collection.
>
> Details:
> * Adds #eventualUsers/#allUsers protocol on TraitDescription and MethodReference for browing users of a trait and its methods.
> * Tests the new traits protocol.
> * TestRunner: Excludes trait methods (i.e., methods copied from a trait) from test coverage methods. Installs extra wrappers for all eventual users of each method defined in a trait and synchronizes them via TestCoverage>>#mark.
> * Implements proper #repondsTo: on TestCoverage.
>
> =============== Diff ===============
>
> CompiledMethod>>eventualUsers {*Traits-NanoKernel} ? TraitTest 9/9/2022 23:37
> + eventualUsers
> +
> + ????^ self methodClass eventualUsersForSelector: self selector
>
> MethodReference>>eventualUserReferences {*Traits-NanoKernel} ? ct 9/9/2022 22:12
> + eventualUserReferences
> +
> + ????^ self eventualUsers collect: [:classDescription |
> + ????????(classDescription >> self selector) methodReference]
>
> MethodReference>>eventualUsers {*Traits-NanoKernel} ? ct 9/9/2022 20:11
> + eventualUsers
> +
> + ????^ self compiledMethod eventualUsers
>
> TestCoverage>>mark {private} ? ct 9/9/2022 22:22 (changed)
> mark
> - ????hasRun := true
> + ????hasRun := true.
> + ????
> + ????self isTraitMethod ifTrue:
> + ????????[| original |
> + ????????original := self originalTraitMethod methodReference compiledMethod.
> + ????????(original respondsTo: #mark) ifTrue:
> + ????????????[original mark; uninstall]].
>
> TestCoverage>>respondsTo: {private} ? ct 9/9/2022 22:22
> + respondsTo: aMessage
> +
> + ????^ (self class canUnderstand: aMessage)
> + ????????or: [method respondsTo: aMessage]
>
> TestRunner>>addMethodsUnderTestIn:to: {actions} ? ct 9/9/2022 22:16 (changed)
> addMethodsUnderTestIn: packages to: methods
> ????packages
> ????????do: [:package | package isNil
> ????????????????ifFalse: [package methods
> ????????????????????????do: [:method | ((#(#packageNamesUnderTest #classNamesNotUnderTest ) includes: method methodSymbol)
> - ????????????????????????????????????or: [method compiledMethod isAbstract
> - ????????????????????????????????????????????or: [method compiledMethod hasLiteral: #ignoreForCoverage]])
> + ????????????????????????????????????or: [method compiledMethod isAbstract]
> + ????????????????????????????????????or: [method compiledMethod isTraitMethod]
> + ????????????????????????????????????or: [method compiledMethod hasLiteral: #ignoreForCoverage])
> ????????????????????????????????ifFalse: [methods add: method]]]]
>
> TestRunner>>collectCoverageFor: {actions} ? ct 9/9/2022 23:00 (changed)
> collectCoverageFor: methods
> - ????| wrappers suite |
> - ????wrappers := methods collect: [ :each | TestCoverage on: each ].
> + ????| methodsWithTraits wrappers suite |
> + ????methodsWithTraits := methods , ((methods select: [ :each | each actualClass isTrait ]) gather: [ :each | each eventualUserReferences ]).
> + ????wrappers := methodsWithTraits collect: [ :each | TestCoverage on: each ].
> ????suite := self
> ????????reset;
> ????????suiteAll.
> ????
> ????[ wrappers do: [ :each | each install ].
> ????[ self runSuite: suite ] ensure: [ wrappers do: [ :each | each uninstall ] ] ] valueUnpreemptively.
> - ????wrappers := wrappers reject: [ :each | each hasRun ].
> + ????wrappers := wrappers reject: [ :each | each hasRun or: [ each isTraitMethod ] ].
> + ????
> ????wrappers isEmpty
> ????????ifTrue:
> ????????????[ UIManager default inform: 'Congratulations. Your tests cover all code under analysis.' ]
> ????????ifFalse:
> ????????????[ ToolSet
> ????????????????browseMessageSet: (wrappers collect: [ :each | each reference ])
> ????????????????name: 'Not Covered Code (' , (100 - (100 * wrappers size // methods size)) printString , '% Code Coverage)'
> ????????????????autoSelect: nil ].
> ????self saveResultInHistory
>
> TraitDescription>>allUsers {accessing} ? ct 9/9/2022 23:06
> + allUsers
> + ????"Answer all ClassDescriptions that directly or indirectly (i.e., through a path of other traits) use the receiver."
> +
> + ????^ self users gather: [:classDescription |
> + ????????classDescription isTrait
> + ????????????ifTrue: [classDescription allUsers copyWithFirst: classDescription]
> + ????????????ifFalse: [{classDescription}]]
>
> TraitDescription>>eventualUsers {accessing} ? ct 9/9/2022 23:07
> + eventualUsers
> + ????"Answer all non-trait ClassDescriptions that directly or indirectly (i.e., through a path of other traits) use the receiver."
> +
> + ????^ self users gather: [:classDescription |
> + ????????classDescription isTrait
> + ????????????ifTrue: [classDescription eventualUsers]
> + ????????????ifFalse: [{classDescription}]]
>
> TraitDescription>>eventualUsersForSelector: {accessing} ? TraitTest 9/9/2022 23:26
> + eventualUsersForSelector: aSymbol
> + ????"Answer all eventual users that use the implementation of for aSymbol of the receiver, i.e., exclude all users that override this message."
> +
> + ????| originalMethod |
> + ????originalMethod := self >> aSymbol.
> + ????^ self eventualUsers select: [:classDescription |
> + ????????| userMethod |
> + ????????(userMethod := classDescription compiledMethodAt: aSymbol ifAbsent: []) notNil and:
> + ????????????[userMethod originalTraitMethod == originalMethod]]
>
> TraitTest>>testAllUsers {testing} ? TraitTest 9/9/2022 23:17
> + testAllUsers
> + ????self assert: self t1 allUsers size = 4.
> + ????self assert: (self t1 allUsers includesAllOf: {self t4. self t5. self c2. self t6 }).
> + ????self assert: self t3 allUsers isEmpty.
> + ????self assert: self t5 allUsers size = 1.
> + ????self assert: self t5 allUsers anyOne = self c2.
> + ????self c2 uses: self t1 + self t5.
> + ????self assert: self t5 allUsers size = 1.
> + ????self assert: self t5 allUsers anyOne = self c2.
> + ????self c2 uses: self t2 asTraitComposition.
> + ????self assert: self t5 allUsers isEmpty
>
> TraitTest>>testEventualUserReferences {testing} ? TraitTest 9/9/2022 23:41
> + testEventualUserReferences
> + ????self assert: (self t1 >> #m11) methodReference eventualUserReferences isEmpty.
> + ????self assert: (self t1 >> #m12) methodReference eventualUserReferences isEmpty.
> + ????self assert: (self t2 >> #m21) methodReference eventualUserReferences isEmpty.
> + ????self assert: (self t3 >> #m31) methodReference eventualUserReferences isEmpty.
> + ????self assert: (self t5 >> #m11) methodReference eventualUserReferences isEmpty.
> + ????self assert: (self t5 >> #m12) methodReference eventualUserReferences size = 1.
> + ????self assert: (self t5 >> #m12) methodReference eventualUserReferences anyOne = (self c2 >> #m12) methodReference.
> + ????self assert: (self t5 >> #m21) methodReference eventualUserReferences size = 1.
> + ????self assert: (self t5 >> #m21) methodReference eventualUserReferences anyOne = (self c2 >> #m21) methodReference.
> + ????self assert: (self t5 >> #m51) methodReference eventualUserReferences size = 1.
> + ????self assert: (self t5 >> #m51) methodReference eventualUserReferences anyOne = (self c2 >> #m51) methodReference.
>
> TraitTest>>testEventualUsers {testing} ? TraitTest 9/9/2022 23:18
> + testEventualUsers
> + ????self assert: self t5 eventualUsers size = 1.
> + ????self assert: self t5 eventualUsers anyOne = self c2.
> + ????self assert: self t1 eventualUsers size = 1.
> + ????self assert: self t1 eventualUsers anyOne = self c2.
> + ????self assert: self t3 eventualUsers isEmpty.
>
> ["TestCoverage-traits.1.cs"]
>
> ---
> Sent from Squeak Inbox Talk
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20220909/f231201b/attachment.html>
> -------------- next part --------------
> A non-text attachment was scrubbed...
> Name: TestCoverage-traits.1.cs
> Type: application/octet-stream
> Size: 6396 bytes
> Desc: not available
> URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20220909/f231201b/attachment.obj>
>
>
["Traits-eventualUsers.3.cs"]
["SUnit coverage for traits.2.cs"]
["Traits-eventualUsers.3.cs"]
["SUnit coverage for traits.2.cs"]
["TraitCoverageExample.3.cs"]