[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

tool[jx8-android] Find method overwrites

This page implements a tool for testing methods of wrappers.
It search for overwritten methods in wrapper hierarchy.
If methods are found, it should be an error in builders or a hand made method.
NoteIn case of methods created by builder, it is not necessary/good to overwrite a method defined by superclass.

How to run this tool

  1. Run jx8-Android appU8
  2. Set the U8 Swiki testing tool to:
  3. Press [Run] button
  4. See the results in the Transcript

Implementation (of the tool)

"FileIn of code to search for overwrites"

(Behavior implements: #methodOverwrites) ifTrue: [
    self error: 'The tool is already installed'
]!

! Behavior methodsFor: #tools !
methodOverwrites
	" Return the collection of overwritten methods of the receiver (and subclasses). "

	| cls result |
	cls := self instanceClass.
	result := HashedSet new.
	self subclasses do: [:each|
		result addAll: each methodOverwrites
	].
	result
		addAll: cls basicMethodOverwrites;
		addAll: cls class basicMethodOverwrites;
		yourself.
	^result asArray! !

! Behavior methodsFor: #tools !
basicMethodOverwrites
	" Return the collection of methods implemented by subclasses that overwrites a method of the receiver. "

	^self selectors inject: #() into: [:total :selector|
		total , (self overwritesFor: selector)
	]! !

! Behavior methodsFor: #tools !
overwritesFor: selector
	" Return the collection of methods implemented by subclasses for selector. "

	^self allSubclasses inject: #() into: [:total :cls|
		(cls implements: selector)
		ifTrue: [ total add: (cls compiledMethodAt: selector) ].
		total
	]! !


Test of jx8-android API

"Searching for method overwrites in jx8-android API..."
| found knownGood knownInstGood knownClsGood |
self print: nil. "clear the Transcript after fileIn"
(Smalltalk includesKey: #JavaObject) ifFalse: [
    ^self print: 'Not running android'
].
found := JavaObject methodOverwrites.

knownGood := #().
knownInstGood := #().
knownClsGood := #( packagePrefix ).
found := found reject: [:each| knownGood includes: each selector ].
found := found reject: [:each|
  ((knownInstGood includes: each selector) and: [ each classField isMetaclass not ])
].
found := found reject: [:each|
  ((knownClsGood includes: each selector) and: [ each classField isMetaclass ])
].

found isEmpty ifTrue: [ self print: 'API is OK'. ^self ].
self print: 'Methods that needs attention/revision.'.
found do: [:each| self print: '  ',each ].