| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439 | Smalltalk createPackage: 'Helios-Helpers'!Object subclass: #HLClassifier	instanceVariableNames: 'next method'	package: 'Helios-Helpers'!!HLClassifier commentStamp!I am an abstract class implementing a link in a `chain of responsibility` pattern.Subclasses are in charge of classifying a method according to multiple strategies.!!HLClassifier methodsFor: 'accessing'!method	^ method!method: anObject	method := anObject.	self next		ifNotNil: [ :nextLink | nextLink method: anObject ]!next	^ next!next: anObject	next := anObject! !!HLClassifier methodsFor: 'private'!doClassify	self subclassResponsibility! !!HLClassifier methodsFor: 'protocol'!classify	self next ifNil: [ ^ false ].		^ self doClassify		ifTrue: [ true ]		ifFalse: [ self next classify ]! !HLClassifier subclass: #HLAccessorClassifier	instanceVariableNames: ''	package: 'Helios-Helpers'!!HLAccessorClassifier commentStamp!I am a classifier checking the method selector matches an instance variable name.!!HLAccessorClassifier methodsFor: 'private'!doClassify	| names selector |		names := method methodClass allInstanceVariableNames.	selector := method selector.		(selector last = ':')		ifTrue: [ "selector might be a setter"			selector := selector allButLast ].		(names includes: selector)		ifFalse: [ ^ false ].			method protocol: 'accessing'.	^ true.! !HLClassifier subclass: #HLImplementorClassifier	instanceVariableNames: ''	package: 'Helios-Helpers'!!HLImplementorClassifier commentStamp!I am a classifier checking the other implementations of the same selector and choose the protocol the most populated.!!HLImplementorClassifier methodsFor: 'private'!doClassify	| currentClass |	currentClass := method methodClass.		[ currentClass superclass isNil ] whileFalse: [		currentClass := currentClass superclass.		(currentClass includesSelector: method selector)			ifTrue: [ 				method protocol: (currentClass >> method selector) protocol.				^ true ]].		^ false.! !HLClassifier subclass: #HLPrefixClassifier	instanceVariableNames: 'prefixMapping'	package: 'Helios-Helpers'!!HLPrefixClassifier commentStamp!I am classifier checking the method selector to know if it begins with a known prefix.!!HLPrefixClassifier methodsFor: 'initialization'!buildPrefixDictionary	prefixMapping := Dictionary new.	prefixMapping 		at: 'test' put: 'tests';	 	at: 'bench' put: 'benchmarking';	 	at: 'copy' put: 'copying';		at: 'initialize' put: 'initialization';		at: 'accept' put: 'visitor';		at: 'visit' put: 'visitor';		at: 'signal' put: 'signalling';		at: 'parse' put: 'parsing';		at: 'add' put: 'adding';		at: 'is' put: 'testing';		at: 'as' put: 'converting';		at: 'new' put: 'instance creation'.!initialize	super initialize.	self buildPrefixDictionary! !!HLPrefixClassifier methodsFor: 'private'!doClassify	prefixMapping keysAndValuesDo: [ :prefix :protocol |		(method selector beginsWith: prefix)			ifTrue: [				method protocol: protocol.				^ true ]].	^ false.! !HLClassifier subclass: #HLSuperclassClassifier	instanceVariableNames: ''	package: 'Helios-Helpers'!!HLSuperclassClassifier commentStamp!I am a classifier checking the superclass chain to find a matching selector.!!HLSuperclassClassifier methodsFor: 'private'!doClassify	| protocolBag methods protocolToUse counter |		protocolBag := Dictionary new.	methods := HLReferencesModel new implementorsOf: method selector.	methods		ifEmpty: [ ^ false ]		ifNotEmpty: [			methods 				do: [ :aMethod || protocol |					protocol := aMethod method protocol.					(method methodClass = aMethod methodClass)						ifFalse: [						((protocol first = '*') or: [ protocol = method defaultProtocol ])							ifFalse: [ 								protocolBag 									at: protocol 									put: (protocolBag at: protocol ifAbsent: [ 0 ]) + 1 ] ] ] ].				protocolBag ifEmpty: [ ^ false ].	protocolToUse := nil.	counter := 0.	protocolBag keysAndValuesDo: [ :key :value | value > counter 		ifTrue: [			counter := value.			protocolToUse := key ] ].	method protocol: protocolToUse.	^ true! !Object subclass: #HLGenerationOutput	instanceVariableNames: 'sourceCodes protocol targetClass'	package: 'Helios-Helpers'!!HLGenerationOutput commentStamp!I am a simple data object used to store the result of a generation process.!!HLGenerationOutput methodsFor: 'accessing'!protocol	^ protocol!protocol: aString	protocol := aString!sourceCodes	^ sourceCodes!sourceCodes: aCollection	sourceCodes := aCollection!targetClass	^ targetClass!targetClass: aClass	targetClass := aClass! !!HLGenerationOutput methodsFor: 'initialization'!initialize	super initialize.		sourceCodes := OrderedCollection new! !!HLGenerationOutput methodsFor: 'protocol'!addSourceCode: aString	sourceCodes add: aString!compile	sourceCodes do: [ :methodSourceCode |		(targetClass includesSelector: methodSourceCode selector)			ifFalse: [ 				targetClass 					compile: methodSourceCode sourceCode					protocol: protocol ] ]! !Object subclass: #HLMethodClassifier	instanceVariableNames: 'firstClassifier'	package: 'Helios-Helpers'!!HLMethodClassifier commentStamp!I am in charge of categorizing methods following this strategy:- is it an accessor?- is it overriding a superclass method?- is it starting with a know prefix?- how are categorized the other implementations?!!HLMethodClassifier methodsFor: 'initialization'!initialize	super initialize.		self setupClassifiers!setupClassifiers	self addClassifier: HLImplementorClassifier new.	self addClassifier: HLPrefixClassifier new.	self addClassifier: HLSuperclassClassifier new.	self addClassifier: HLAccessorClassifier new! !!HLMethodClassifier methodsFor: 'private'!addClassifier: aClassifier	aClassifier next: firstClassifier.	firstClassifier := aClassifier! !!HLMethodClassifier methodsFor: 'protocol'!classify: aMethod	firstClassifier		method: aMethod;		classify!classifyAll: aCollectionOfMethods	aCollectionOfMethods do: [ :method |		self classify: method ]! !Object subclass: #HLMethodGenerator	instanceVariableNames: 'output'	package: 'Helios-Helpers'!!HLMethodGenerator commentStamp!I am the abstract super class of the method generators.My main method is `generate` which produce an `output` object!!HLMethodGenerator methodsFor: 'accessing'!class: aClass	output targetClass: aClass!output	^ output! !!HLMethodGenerator methodsFor: 'initialization'!initialize	super initialize.		output := HLGenerationOutput new! !!HLMethodGenerator methodsFor: 'protocol'!generate	output targetClass ifNil: [ self error: 'class should not be nil'].! !HLMethodGenerator subclass: #HLAccessorsGenerator	instanceVariableNames: ''	package: 'Helios-Helpers'!!HLAccessorsGenerator commentStamp!I am a generator used to compile the getters/setters of a class!!HLAccessorsGenerator methodsFor: 'double-dispatch'!accessorProtocolForObject	output protocol: 'accessing'!accessorsForObject	| sources |		sources := OrderedCollection new.	output targetClass instanceVariableNames sorted do: [ :each | 		sources 			add: (self getterFor: each);			add: (self setterFor: each) ].	output sourceCodes: sources! !!HLAccessorsGenerator methodsFor: 'private'!getterFor: anInstanceVariable	^ HLMethodSourceCode new		selector:anInstanceVariable;		sourceCode: (String streamContents: [ :stream |		stream << anInstanceVariable.		stream cr tab.		stream << '^ ' << anInstanceVariable ])!setterFor: anInstanceVariable	^ HLMethodSourceCode new		selector: anInstanceVariable, ':';		sourceCode: (String streamContents: [ :stream |		stream << anInstanceVariable << ': anObject'.		stream cr tab.		stream << anInstanceVariable << ' := anObject' ])! !!HLAccessorsGenerator methodsFor: 'protocol'!generate	super generate.		output targetClass 		accessorsSourceCodesWith: self;		accessorProtocolWith: self! !HLMethodGenerator subclass: #HLInitializeGenerator	instanceVariableNames: ''	package: 'Helios-Helpers'!!HLInitializeGenerator commentStamp!I am used to double-dispatch the `initialize` method(s) generation.Usage:    ^ HLInitializeGenerator new        class: aClass;        generate;        outputI am a disposable object!!HLInitializeGenerator methodsFor: 'double-dispatch'!initializeForObject	output addSourceCode: self initializeMethodForObject!initializeProtocolForObject	output protocol: 'initialization'! !!HLInitializeGenerator methodsFor: 'private'!generateInitializeCodeForObject		^ String streamContents: [ :str || instVars size |		instVars := output targetClass instanceVariableNames sorted.		size := instVars size.		str << 'initialize'.		str cr tab << 'super initialize.';cr.		str cr tab.		instVars withIndexDo: [ :name :index |			index ~= 1 ifTrue: [ str cr tab ].			str << name << ' := nil'.			index ~= size ifTrue: [ str << '.' ] ] ].!initializeMethodForObject		^ HLMethodSourceCode new		selector: 'initialize';		sourceCode: self generateInitializeCodeForObject;		yourself! !!HLInitializeGenerator methodsFor: 'protocol'!generate	super generate.		output targetClass 		initializeSourceCodesWith: self;		initializeProtocolWith: self! !Object subclass: #HLMethodSourceCode	instanceVariableNames: 'selector sourceCode'	package: 'Helios-Helpers'!!HLMethodSourceCode commentStamp!I am a simple data object keeping track of the information about a method that will be compiled at the end of the generation process!!HLMethodSourceCode methodsFor: 'accessing'!selector	^ selector!selector: aSelector	selector := aSelector!sourceCode	^ sourceCode!sourceCode: aString	sourceCode := aString! !
 |