All patches moved to their respective classes.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 05 May 2015 23:44:17 +0200
changeset 826 8e15449e384c
parent 825 daa2a57953af
child 827 1ffd52a19ff5
All patches moved to their respective classes.
Make.proto
bc.mak
jn_refactoring_custom.st
patches/Make.proto
patches/Make.spec
patches/bc.mak
patches/extensions.st
patches/jn_refactoring_custom_patches.st
patches/libInit.cc
--- a/Make.proto	Thu Feb 19 06:07:58 2015 +0000
+++ b/Make.proto	Tue May 05 23:44:17 2015 +0200
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/jn/refactoring_custom/patches -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libcomp -I$(INCLUDE_TOP)/stx/libjava -I$(INCLUDE_TOP)/stx/libjava/tools -I$(INCLUDE_TOP)/stx/libjavascript -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libview -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libwidg -I$(INCLUDE_TOP)/stx/libwidg2
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libcomp -I$(INCLUDE_TOP)/stx/libjava -I$(INCLUDE_TOP)/stx/libjava/tools -I$(INCLUDE_TOP)/stx/libjavascript -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libview -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libwidg -I$(INCLUDE_TOP)/stx/libwidg2
 
 
 # if you need any additional defines for embedded C code,
--- a/bc.mak	Thu Feb 19 06:07:58 2015 +0000
+++ b/bc.mak	Tue May 05 23:44:17 2015 +0200
@@ -35,7 +35,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\jn\refactoring_custom\patches -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libcomp -I$(INCLUDE_TOP)\stx\libjava -I$(INCLUDE_TOP)\stx\libjava\tools -I$(INCLUDE_TOP)\stx\libjavascript -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libview -I$(INCLUDE_TOP)\stx\libview2 -I$(INCLUDE_TOP)\stx\libwidg -I$(INCLUDE_TOP)\stx\libwidg2
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libcomp -I$(INCLUDE_TOP)\stx\libjava -I$(INCLUDE_TOP)\stx\libjava\tools -I$(INCLUDE_TOP)\stx\libjavascript -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libview -I$(INCLUDE_TOP)\stx\libview2 -I$(INCLUDE_TOP)\stx\libwidg -I$(INCLUDE_TOP)\stx\libwidg2
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
--- a/jn_refactoring_custom.st	Thu Feb 19 06:07:58 2015 +0000
+++ b/jn_refactoring_custom.st	Tue May 05 23:44:17 2015 +0200
@@ -53,7 +53,10 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
@@ -66,10 +69,7 @@
         #'stx:libview'    "WindowGroup - referenced by CustomCodeGeneratorOrRefactoring>>executeInContextWithWaitCursor:"
         #'stx:libwidg'    "DialogBox - referenced by CustomUserDialog>>initialize"
         #'stx:libwidg2'    "CheckBox - referenced by CustomDialog>>addCheckBoxOn:labeled:"
-        #'jn:refactoring_custom/patches'     
     )
-
-    "Modified: / 19-02-2015 / 06:05:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 subProjects
--- a/patches/Make.proto	Thu Feb 19 06:07:58 2015 +0000
+++ b/patches/Make.proto	Tue May 05 23:44:17 2015 +0200
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/browser -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libcomp
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
@@ -102,8 +102,6 @@
 # build all mandatory prerequisite packages (containing superclasses) for this package
 prereq:
 	cd $(TOP)/libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd $(TOP)/goodies/refactoryBrowser/changes && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd $(TOP)/goodies/refactoryBrowser/helpers && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 
 
 
@@ -125,7 +123,6 @@
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)CustomDummyClassPatches.$(O) CustomDummyClassPatches.$(H): CustomDummyClassPatches.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)jn_refactoring_custom_patches.$(O) jn_refactoring_custom_patches.$(H): jn_refactoring_custom_patches.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/AddClassChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/AddMethodChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/RefactoryChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/changes/RefactoryClassChange.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers/BrowserEnvironment.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers/RBAbstractClass.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers/RBMethod.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/patches/Make.spec	Thu Feb 19 06:07:58 2015 +0000
+++ b/patches/Make.spec	Tue May 05 23:44:17 2015 +0200
@@ -60,7 +60,6 @@
 COMMON_OBJS= \
     $(OUTDIR_SLASH)CustomDummyClassPatches.$(O) \
     $(OUTDIR_SLASH)jn_refactoring_custom_patches.$(O) \
-    $(OUTDIR_SLASH)extensions.$(O) \
 
 
 
--- a/patches/bc.mak	Thu Feb 19 06:07:58 2015 +0000
+++ b/patches/bc.mak	Tue May 05 23:44:17 2015 +0200
@@ -35,7 +35,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\browser -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libcomp
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\libbasic
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
@@ -52,8 +52,6 @@
 # build all mandatory prerequisite packages (containing superclasses) for this package
 prereq:
 	pushd ..\..\..\stx\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\..\stx\goodies\refactoryBrowser\changes & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\..\stx\goodies\refactoryBrowser\helpers & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 
 
 
@@ -72,7 +70,6 @@
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)CustomDummyClassPatches.$(O) CustomDummyClassPatches.$(H): CustomDummyClassPatches.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)jn_refactoring_custom_patches.$(O) jn_refactoring_custom_patches.$(H): jn_refactoring_custom_patches.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\AddClassChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\AddMethodChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\RefactoryChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\changes\RefactoryClassChange.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers\BrowserEnvironment.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers\RBAbstractClass.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers\RBMethod.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/patches/extensions.st	Thu Feb 19 06:07:58 2015 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,395 +0,0 @@
-"{ Package: 'jn:refactoring_custom/patches' }"!
-
-!AddClassChange methodsFor:'private'!
-
-fillOutDefinition
-        | parseTree receiver arguments argumensBySelectorParts |
-        parseTree := RBParser parseExpression: definition
-                                onError: [:str :pos | ^self parseDefinitionError].
-        parseTree isMessage ifFalse: [^self parseDefinitionError].
-        (self isValidSubclassCreationMessage: parseTree) 
-                ifFalse: [^self parseDefinitionError].
-        receiver := parseTree receiver.
-        superclassName := receiver isVariable 
-                                ifTrue: [receiver name asSymbol]
-                                ifFalse: [receiver value].
-        arguments := parseTree arguments.
-        className := arguments first value.
-        instanceVariableString := (arguments at: 2) value asString.
-        classVariableString := (arguments at: 3) value asString.
-        poolDictionaryNames := self namesIn: (arguments at: 4) value.
-
-        argumensBySelectorParts := self argumensBySelectorPartsFromMessage: parseTree.
-        (argumensBySelectorParts includesKey: #privateIn:) ifTrue: [
-            | argument |
-
-            argument := argumensBySelectorParts at: #privateIn:.
-            argument isVariable ifTrue: [ 
-                self privateInClassName: argument name asSymbol
-            ] ifFalse: [ 
-                self privateInClassName: argument value asSymbol
-            ].
-            className := (self privateInClassName, '::', className) asSymbol.
-            category := #''. "Inherited by owner - privateInClassName"
-        ] ifFalse: [ 
-            category := arguments size < 5 
-                                ifTrue: [#Unknown]
-                                ifFalse: [(arguments at: 5) value asSymbol]
-        ].
-
-    "Modified: / 25-01-2015 / 12:32:44 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!AddClassChange methodsFor:'testing'!
-
-isValidMessageName: aMessageNode 
-
-    ^ #(
-        #subclass:instanceVariableNames:classVariableNames:poolDictionaries: 
-        #subclass:instanceVariableNames:classVariableNames:poolDictionaries:category: 
-        #subclass:instanceVariableNames:classVariableNames:poolDictionaries:privateIn:
-        #variableByteSubclass:classVariableNames:poolDictionaries: 
-        #variableByteSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: 
-        #variableSubclass:instanceVariableNames:classVariableNames:poolDictionaries: 
-        #variableSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:
-    ) 
-    includes: aMessageNode selector
-
-    "Modified (format): / 16-11-2014 / 12:35:29 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!AddClassChange methodsFor:'testing'!
-
-isValidSubclassCreationMessage: aMessageNode
-        | argumensBySelectorParts |
-
-        (aMessageNode receiver isVariable or: [aMessageNode receiver isLiteral]) 
-                ifFalse: [^false].
-
-        (self isValidMessageName: aMessageNode) ifFalse: [^false].
-
-        "Each argument should be literal except for privateIn:"
-        argumensBySelectorParts := self argumensBySelectorPartsFromMessage: aMessageNode.
-        argumensBySelectorParts keysAndValuesDo: [ :name :value |
-            value isLiteral ifFalse: [
-                name = #privateIn: ifFalse: [ 
-                    ^ false
-                ]
-            ]
-        ].
-
-        ^ true.
-
-    "Modified: / 16-11-2014 / 15:32:47 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!AddClassChange methodsFor:'private'!
-
-primitiveExecute
-
-    package notNil ifTrue:[
-        Class packageQuerySignal 
-            answer:package
-            do:[
-                ^ self definingSuperclass subclassDefinerClass 
-                    evaluate: definition
-                    notifying: self controller
-                    logged: true
-            ]
-    ].
-
-    ^ self definingSuperclass subclassDefinerClass 
-                evaluate: definition
-                notifying: self controller
-                logged: true
-
-    "Modified: / 08-10-2014 / 20:10:02 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!AddMethodChange methodsFor:'converting'!
-
-asUndoOperation
-        ^(self changeClass includesSelector: self selector) 
-                ifTrue: 
-                        [| oldProtocol oldPackage |
-                        oldProtocol := BrowserEnvironment new whichProtocolIncludes: self selector
-                                                in: self changeClass.
-                        oldProtocol isNil ifTrue: [oldProtocol := #accessing].
-                        oldPackage := (self changeClass compiledMethodAt: self selector) package.
-                        (AddMethodChange 
-                                compile: (self methodSourceFor: self selector)
-                                in: self changeClass
-                                classified: oldProtocol) 
-                                package: oldPackage;
-                                yourself]
-                ifFalse: [RemoveMethodChange remove: selector from: self changeClass]
-
-    "Modified: / 16-11-2014 / 17:13:09 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!BrowserEnvironment methodsFor:'accessing'!
-
-whichCategoryIncludes: aClassName
-        (Smalltalk dialectName = 'SmalltalkX') ifTrue:[
-            | class |
-
-            class := Smalltalk at:aClassName asSymbol.
-            class isNil ifTrue: [ ^ nil ].
-            ^ class category
-        ].
-        ^RefactoryBrowserPlatformSupport systemOrganization categoryOfElement: aClassName
-
-    "Modified: / 05-11-2014 / 21:26:45 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBAbstractClass methodsFor:'accessing'!
-
-categories
-    "Return a collection of the method-categories known in the receiver class.
-     This does NOT include the metaclasses categories or the superclass categories.
-     The returned collection is not sorted by any order."               
-
-    | categories |
-
-    categories := Set new.
-    self selectors do:[:selector |
-        categories add: (self methodFor: selector) category
-    ].
-    ^ categories
-
-    "Created: / 14-11-2014 / 20:25:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 19-11-2014 / 18:46:47 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBAbstractClass methodsFor:'method accessing'!
-
-compile: aString classified: aSymbolCollection 
-        | change method |
-        change := model 
-                                compile: aString
-                                in: self
-                                classified: aSymbolCollection.
-        method := RBMethod 
-                                for: self
-                                source: aString
-                                selector: change selector.
-        method category: aSymbolCollection.
-        self addMethod: method
-
-    "Modified: / 06-10-2014 / 22:38:27 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBAbstractClass methodsFor:'method accessing'!
-
-compileTree: aBRMethodNode classified: aSymbolCollection 
-        | method source |
-        source := aBRMethodNode formattedCode.
-        model 
-                compile: source
-                in: self
-                classified: aSymbolCollection.
-        method := RBMethod 
-                                for: self
-                                source: source
-                                selector: aBRMethodNode selector.
-        method category: aSymbolCollection.
-"       method parseTree: aBRMethodNode."
-        self addMethod: method
-
-    "Modified: / 06-10-2014 / 22:37:13 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBAbstractClass methodsFor:'method accessing'!
-
-compileTree: aBRMethodNode usingSource:newSource classified: aSymbolCollection 
-        | method source |
-
-        source := newSource.
-        model 
-                compile: source
-                in: self
-                classified: aSymbolCollection.
-        method := RBMethod 
-                                for: self
-                                source: newSource
-                                selector: aBRMethodNode selector.
-        method category: aSymbolCollection.
-"       method parseTree: aBRMethodNode."
-        self addMethod: method
-
-    "Modified: / 06-10-2014 / 22:38:57 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBAbstractClass methodsFor:'testing'!
-
-isAbstract
-    "Returns true if this class is abstract otherwise returns false."
-    | isAbstract |
-
-    "Ability to set that this class is abstract or not insead of guessing.
-    Also store the value just in the metaclass instance."
-    isAbstract := self theMetaclass objectAttributeAt: #isAbstract.
-    isAbstract notNil ifTrue: [ 
-        ^ isAbstract
-    ].
-
-    (self whichSelectorsReferToSymbol: #subclassResponsibility) isEmpty 
-        ifFalse: [^true].
-    model allReferencesToClass: self do: [:each | ^false].
-    "The guess that Im abstract if no ones references my class
-    is probably wrong here, but I wont change it, because it can
-    break some dependency"
-    ^true
-
-    "Modified (format): / 14-12-2014 / 17:41:27 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBAbstractClass methodsFor:'accessing'!
-
-name: aName 
-    "Sets the class name"
-
-    name := aName asSymbol
-
-    "Modified: / 19-11-2014 / 21:14:04 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBMethod methodsFor:'accessing'!
-
-category
-    "Returns in which category/protocol does the method belongs within a class"
-
-    | category |
-
-    category := self objectAttributeAt: #category.  
-
-    category isNil ifTrue: [  
-        | compiledMethod |
-
-        compiledMethod := self method.
-        compiledMethod notNil ifTrue:[
-            ^ compiledMethod category.
-        ].
-
-        ^ 'as yet unclassified'
-    ].
-
-    ^ category
-
-    "Created: / 17-02-2012 / 00:06:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified (comment): / 06-10-2014 / 07:55:28 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBMethod methodsFor:'accessing'!
-
-info
-    "Returns an 'info object' that can answer various
-     questions like 'what selectors method sends',
-     names if temporaries etc.
-
-     Actally, 'info object' is instance of Parser"
-
-    info isNil ifTrue:[
-        info := Parser 
-            parseMethod: self source
-            in:nil
-            ignoreErrors:true
-            ignoreWarnings:true
-    ].
-    ^info
-
-    "Created: / 16-02-2012 / 16:33:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 04-10-2014 / 10:13:01 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBMethod methodsFor:'accessing'!
-
-method
-    "Returns Method instance which is present or retrived from real class"
-
-    (compiledMethod isNil and: [ class notNil ]) ifTrue:[
-        | realClass selector |
-
-        realClass := class realClass.
-        selector := self selector.
-
-        "Do not try to retrieve method when its not possible"
-        (realClass notNil and: [ selector notNil ]) ifTrue: [
-            compiledMethod := realClass compiledMethodAt: selector.
-        ]
-    ].
-    ^compiledMethod
-
-    "Modified: / 17-02-2012 / 00:07:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-11-2014 / 16:38:38 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBMethod methodsFor:'accessing'!
-
-package
-    "see Method >> package ( same purpose, but for model method )"
-    | package |
-
-    package := self objectAttributeAt: #package.
-
-    package isNil ifTrue: [ 
-        | method |
-
-        method := self method.
-
-        method isNil ifTrue: [
-            package := PackageId noProjectID
-        ] ifFalse: [
-            package := method package
-        ]
-    ].
-
-    ^ package
-
-    "Created: / 17-02-2012 / 00:41:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-11-2014 / 16:34:27 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RBMethod methodsFor:'accessing'!
-
-selector
-    (selector isNil and: [ source notEmptyOrNil ]) ifTrue:[
-        selector := (Parser parseMethodSpecification: source) selector.
-    ].
-    ^selector
-
-    "Modified: / 16-02-2012 / 16:51:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 26-12-2014 / 13:24:32 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!RefactoryClassChange methodsFor:'accessing'!
-
-changeClass
-        | theClass |
-
-        "/ cg: handle anonymous classes
-        theClass := Smalltalk at: self changeClassName ifAbsent: [nil].
-        theClass isNil ifTrue:[
-            theClass := class.
-            theClass isNil ifTrue:[ 
-                self model notNil ifTrue: [ 
-                    ^ isMeta ifTrue: [
-                        self model metaclassNamed: self changeClassName  
-                    ] ifFalse: [
-                        self model classNamed: self changeClassName  
-                    ]
-                ].
-                ^ nil 
-            ].
-        ].
-        ^isMeta ifTrue: [theClass class] ifFalse: [theClass]
-
-    "Modified: / 08-11-2014 / 14:05:05 / Jakub Nesveda <nesvejak@fit.cvut.cz>"
-! !
-
-!jn_refactoring_custom_patches class methodsFor:'documentation'!
-
-extensionsVersion_HG
-
-    ^ '$Changeset: <not expanded> $'
-! !
--- a/patches/jn_refactoring_custom_patches.st	Thu Feb 19 06:07:58 2015 +0000
+++ b/patches/jn_refactoring_custom_patches.st	Tue May 05 23:44:17 2015 +0200
@@ -34,8 +34,6 @@
      by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:goodies/refactoryBrowser/changes'    "AddClassChange - extended"
-        #'stx:goodies/refactoryBrowser/helpers'    "BrowserEnvironment - extended"
         #'stx:libbasic'    "LibraryDefinition - superclass of jn_refactoring_custom_patches"
     )
 !
@@ -43,14 +41,14 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:goodies/refactoryBrowser/browser'    "RefactoryBrowserPlatformSupport - referenced by BrowserEnvironment>>whichCategoryIncludes:"
-        #'stx:goodies/refactoryBrowser/parser'    "RBParser - referenced by AddClassChange>>fillOutDefinition"
-        #'stx:libcomp'    "Parser - referenced by RBMethod>>info"
     )
 !
 
@@ -84,24 +82,6 @@
      A correponding method with real names must be present in my concrete subclasses"
 
     ^ #(
-        RBAbstractClass compile:classified:
-        RBAbstractClass compileTree:classified:
-        RBAbstractClass compileTree:usingSource:classified:
-        RBMethod category
-        RBMethod info
-        RBMethod method
-        AddClassChange primitiveExecute
-        RBMethod package
-        AddMethodChange asUndoOperation
-        BrowserEnvironment whichCategoryIncludes:
-        RefactoryClassChange changeClass
-        RBAbstractClass categories
-        AddClassChange fillOutDefinition
-        AddClassChange isValidMessageName:
-        AddClassChange isValidSubclassCreationMessage:
-        RBAbstractClass name:
-        RBAbstractClass isAbstract
-        RBMethod selector
     )
 ! !
 
--- a/patches/libInit.cc	Thu Feb 19 06:07:58 2015 +0000
+++ b/patches/libInit.cc	Tue May 05 23:44:17 2015 +0200
@@ -30,6 +30,6 @@
 _CustomDummyClassPatches_Init(pass,__pRT__,snd);
 _jn_137refactoring_137custom_137patches_Init(pass,__pRT__,snd);
 
-_jn_137refactoring_137custom_137patches_extensions_Init(pass,__pRT__,snd);
+
 __END_PACKAGE__();
 }