JavaClassRegistry.st
branchcvs_MAIN
changeset 3360 1a8899091305
parent 3324 a58245c0e83a
child 3386 ddcff50a1fdc
--- a/JavaClassRegistry.st	Fri Feb 14 14:27:26 2014 +0100
+++ b/JavaClassRegistry.st	Wed Jan 28 03:12:08 2015 +0100
@@ -1,9 +1,9 @@
 "
- COPYRIGHT (c) 1996-2011 by Claus Gittinger
+ COPYRIGHT (c) 1996-2015 by Claus Gittinger
 
  New code and modifications done at SWING Research Group [1]:
 
- COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
+ COPYRIGHT (c) 2010-2015 by Jan Vrany, Jan Kurs and Marcel Hlopko
                             SWING Research Group, Czech Technical University in Prague
 
  This software is furnished under a license and may be used
@@ -20,8 +20,8 @@
 "
 "{ Package: 'stx:libjava' }"
 
-Object subclass:#JavaClassRegistry
-	instanceVariableNames:'vm loaders notifier'
+JavaClassEnvironment subclass:#JavaClassRegistry
+	instanceVariableNames:'vm loaders notifier lock'
 	classVariableNames:''
 	poolDictionaries:'JavaVMData'
 	category:'Languages-Java-Support'
@@ -31,11 +31,11 @@
 
 copyright
 "
- COPYRIGHT (c) 1996-2011 by Claus Gittinger
+ COPYRIGHT (c) 1996-2015 by Claus Gittinger
 
  New code and modifications done at SWING Research Group [1]:
 
- COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
+ COPYRIGHT (c) 2010-2015 by Jan Vrany, Jan Kurs and Marcel Hlopko
                             SWING Research Group, Czech Technical University in Prague
 
  This software is furnished under a license and may be used
@@ -78,7 +78,7 @@
 
 !JavaClassRegistry methodsFor:'accessing'!
 
-classForName: className loader: classLoader ifAbsent: aBlock 
+classForName: className loader: classLoader ifAbsent: aBlock
     "Get class loaded by given classLoader from registry or evaluate aBlock if class is not yet registered"
 
     | classes class |
@@ -104,34 +104,43 @@
     "Created: / 23-10-2011 / 11:40:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-classForName: className loader: classLoader ifAbsentPut: block 
+classForName: className loader: classLoader ifAbsentPut: block
     "Get class loaded by classLoader from registry. if absent block is evaluated and resulting class in registered in registry, "
-    
-    | class |
+
+    | class synchronizer |
+
     self assert: (className includes: $.) not.
-     "if class is already registered with the same cl, just return it"
-    class := self classNamed: className loader: classLoader.
-    class notNil ifTrue: [ ^ class ].
-    "if java vm is booted, nil class loader means system class loader, lets check it too"
-    (vm notNil and:[vm booted and: [classLoader isNil]]) ifTrue: [
-        class := self classNamed: className loader: vm systemClassLoader. 
-        class notNil ifTrue: [^class]
+
+    "/ Temporary workaround for race-condition when multiple threads are
+    "/ loading same class. Note that ClassLoader.loadClass() / loadClassInternal()
+    "/ is itself sychronized so we have to synchronize iff and only iff
+    "/ we're loading for primordial class loader. If we synchronize
+    "/ even on non-primordial loaders, we risk a deadlock. Very hacky...
+
+    synchronizer := classLoader isNil
+                        ifTrue:[ [:whatToDo | lock critical: whatToDo ] ]
+                        ifFalse:[ [:whatToDo | whatToDo value ] ].
+
+    synchronizer value:[
+        "If class is already registered with the same cl, just return it"
+        class := self classNamed: className loader: classLoader.
+        class isNil ifTrue:[
+            "Otherwise evaluate block"
+            class := block value.
+            (class notNil and:[classLoader isNil]) ifTrue: [ self registerClass: class ].
+        ].
     ].
-     "otherwise evaluate block"
-    class := block value.
-    class notNil ifTrue: [
-    self registerClass: class.].
-    ^ class.
+    ^ class
 
     "Created: / 21-10-2011 / 12:00:30 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
     "Created: / 23-10-2011 / 11:36:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 02-11-2011 / 17:29:20 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified (format): / 24-01-2013 / 11:19:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-08-2014 / 01:23:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 classNamed: className
 
-    "Return a class for given classname loaded by 'current classloader' or 
+    "Return a class for given classname loaded by 'current classloader' or
      nil if not yet loaded"
 
     ^self classNamed: className loader: JavaClassReader classLoaderQuerySignal query
@@ -141,7 +150,7 @@
 
 classNamed: className loader: classLoader
 
-    "Return a class for given classname loaded by given classloader or 
+    "Return a class for given classname loaded by given classloader or
      nil if not yet loaded"
 
     ^self classForName: className loader: classLoader ifAbsent:[nil].
@@ -151,9 +160,10 @@
 
 classes
 
-    ^Iterator on:[:whatToDo|self classesDo: whatToDo]
+    ^Iterator on:[:whatToDo|self allClassesDo: whatToDo]
 
     "Created: / 23-10-2011 / 20:14:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 09-04-2014 / 18:43:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 systemPackage: syspkg
@@ -201,9 +211,9 @@
 
 !JavaClassRegistry methodsFor:'class loading'!
 
-loadFile: aFilename 
+loadFile: aFilename
     "reads a class from aFilename, installs and returns it."
-    
+
     | aClass |
 
     self breakPoint: #mh.
@@ -217,19 +227,19 @@
     "Modified: / 23-10-2011 / 11:55:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-loadStream: javaClassDataStream loader: aJavaClassLoader 
+loadStream: javaClassDataStream loader: aJavaClassLoader
     "reads a class from aStream and returns it.
      The JavaClass is installed as global.
      If new classes are required to be loaded, aClassLoader is
      asked to do it."
-    
+
     | javaClass |
 
     self breakPoint: #mh.
     self breakPoint: #jv.
     javaClass := JavaClassReader readStream: javaClassDataStream loader: aJavaClassLoader.
     javaClass isNil ifTrue: [
-            Logger 
+            Logger
                 log: 'JavaClassReader was not able to read given data stream'
                 severity: #warn
                 facility: #JVM.
@@ -246,15 +256,15 @@
 
 !JavaClassRegistry methodsFor:'enumerating'!
 
-classesDo: aBlock
+allClassesDo: aBlock
 
     loaders do:[:classes|
         classes do:[:class|
             aBlock value: class
-        ]        
+        ]
     ]
 
-    "Created: / 23-10-2011 / 20:13:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 09-04-2014 / 18:43:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaClassRegistry methodsFor:'helpers'!
@@ -264,7 +274,7 @@
 loaders at: aJavaClassLoader put: Dictionary new.
 !
 
-getClassesDefinedBy:classLoader 
+getClassesDefinedBy:classLoader
     ^loaders at: classLoader ifAbsent: [nil].
 ! !
 
@@ -272,25 +282,27 @@
 
 flush
 
+    notifier stopAndRemoveAll.
     self initialize.
 
-    "Modified: / 30-10-2011 / 12:06:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 30-11-2013 / 07:03:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 initialize
     loaders := WeakIdentityDictionary new.
     loaders at: nil put: Dictionary new.
-    notifier := BackgroundQueueProcessingJob 
+    notifier := BackgroundQueueProcessingJob
                     named: 'Java class registry notifier'
                     on:[:typeAndClass|Smalltalk changed: typeAndClass first with: typeAndClass second].
     notifier priority: Processor userBackgroundPriority - 1.
+    lock := RecursionLock new.
 
-    "Modified: / 08-02-2013 / 00:58:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 22-11-2013 / 11:08:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setVM: aJavaVM
 
-    "Now, aJavaVM == JavaVM (i.e, the class JavaVM 
+    "Now, aJavaVM == JavaVM (i.e, the class JavaVM
     itself, not its instance)"
 
     vm := aJavaVM.
@@ -304,39 +316,39 @@
 registerClass: newClass
     | classes oldClass |
 
-    ((newClass name == #'$do$It$') 
-        and:[newClass superclass name == #'groovy/lang/Script']) ifTrue:[
+    ((newClass binaryName == #'$do$It$')
+        and:[newClass superclass binaryName == #'groovy/lang/Script']) ifTrue:[
         "/ Mhhh...Groovy do-it. No need to register this!!
         ^ self
     ].
 
 
-    self assert: (newClass name includes: $.) not.
+    self assert: (newClass binaryName includes: $.) not.
     loaders keysAndValuesDo:[:loader :classesPerLoader|
-
-        (classesPerLoader includesKey: newClass name) ifTrue:[
+        (classesPerLoader includesKey: newClass binaryName) ifTrue:[
             loader == newClass classLoader ifTrue:[
-                (oldClass := classesPerLoader at: newClass name) ~~ newClass ifTrue:[
+                (oldClass := classesPerLoader at: newClass binaryName) ~~ newClass ifTrue:[
                     "Class already exists, reload & reinstall"
 
                     | reloadedClass |
+
+                    self registerClassRedefined: oldClass.  
                     reloadedClass := JavaClassReloader reload: oldClass with: newClass.
                     "/OK, full reload, not just method dictionary update"
                     reloadedClass ~~ oldClass ifTrue:[
+                        "/ Remove old class from classloader...
+                        self unregisterClassInClassLoader: oldClass.  
+                        "/ ...from reflection cache....
+                        JavaVM reflection removeJavaClassObjectForClass: oldClass.                 
+
                         classesPerLoader
-                            at: newClass name 
+                            at: newClass binaryName
                             put: reloadedClass.
+                        self registerClassInClassLoader: reloadedClass.  
                         self registerClassInSmalltalk: reloadedClass notify: false.
                     ].
-                    "Transfer all possible problems from old class to new class"
-                    JavaCompilerProblemRegistry notNil ifTrue:[
-                        | problems |
-
-                        problems := JavaCompilerProblemRegistry problemsFor: newClass.
-                        JavaCompilerProblemRegistry problemsFor: reloadedClass put: problems.
-                    ].
                     Smalltalk changed: #classDefinition with: reloadedClass.
-                    ^self.             
+                    ^self.
                 ].
             ].
         ].
@@ -346,78 +358,28 @@
     classes isNil ifTrue:[
         classes := loaders at: newClass classLoader put: Dictionary new.
     ].
-    classes at: newClass name  put: newClass.
-    self registerClassInSmalltalk: newClass notify: true.
+    classes at: newClass binaryName  put: newClass.
+    newClass isJavaClass ifTrue:[
+        self registerClassInClassLoader: newClass.
+        "/ Register class in system dictionary so it can be browsed
+        "/ by system browser
+        self registerClassInSmalltalk: newClass notify: true.
+
+        "/ Also register builtin classes in JavaVMData
+        newClass isBuiltInClass ifTrue:[
+            self assert: newClass classLoader isNil. "/must be loaded by primordial CL...
+            self registerBuiltIn: newClass.
+        ].
+    ].
+    "/ There may be classes already loaded with compile errors.
+    "/ Try to recompile all erroneous classes that depends on this one...
+    JavaCompiler notNil ifTrue:[
+       JavaCompiler recompileErroneousClassesReferringTo: newClass ignoring: newClass.
+    ].
 
     "Created: / 23-10-2011 / 11:53:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 02-11-2011 / 18:40:52 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified: / 29-08-2013 / 01:03:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-registerClassInSmalltalk: javaclass notify: doNotify
-    "Registers class in Smalltalk system dictionary and
-     notifies system, so the class become visible by
-     Smalltalk"
-
-    | nameComponents accessor nsName ns  |
-
-    javaclass isSynthetic ifTrue:[ ^ self ].
-    nameComponents := javaclass name asCollectionOfSubstringsSeparatedBy:$/.
-    nameComponents size > 1 ifTrue:[
-        javaclass setCategory:((nameComponents asStringWith:$/ from:1 to:(nameComponents size - 1))
-                            replaceAll:$/ with:$. ).
-    ] ifFalse:[
-        javaclass setCategory:#'(default)'
-    ].
-
-    nameComponents size > 1 ifTrue:[
-        javaclass setPackage:((nameComponents copyButLast:1) asStringWith:$/) asSymbol
-    ] ifFalse:[
-        javaclass setPackage:#'java/(default)'
-    ].
-
-    "/ break up the package and create nameSpaces
-    "/ for each package component.
-    "/ This allows java.foo.bar to be visible in ST/X
-    "/ under the name JAVA::java::foo::bar
-
-    accessor := javaclass"JavaClassAccessor fullName: aString".    
-    nsName := javaclass topNameSpaceName.
-    ns := Smalltalk at: nsName.
-    ns isNil ifTrue:[
-        JavaPackage name:nsName.
-        ns := Smalltalk at: nsName
-    ].
-
-    nameComponents size > 1 ifTrue:[
-        | s |
-
-        s := '' writeStream.
-
-        s nextPutAll: nsName.       
-        nameComponents from:1 to:(nameComponents size - 1) do:[:aPart |
-            s nextPutAll:'::'.
-            s nextPutAll:aPart
-        ].
-        Metaclass confirmationQuerySignal answer:false do:[
-            Class withoutUpdatingChangesDo:[
-                ns := JavaPackage fullName:(s contents).
-            ]
-        ]
-    ].
-
-    ns isNameSpace ifTrue:[
-        ns at:nameComponents last asSymbol put:accessor.
-        javaclass setEnvironment: ns.
-    ].
-
-
-    doNotify ifTrue:[
-        notifier add:(Array with: #newClass with: javaclass).
-    ].
-
-    "Created: / 04-04-2012 / 10:01:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 03-09-2013 / 00:41:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-08-2014 / 15:19:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 registerClasses: classes
@@ -440,44 +402,45 @@
 !
 
 unregisterClass: oldClass
-    | classes |
-
-    self assert: (oldClass name includes: $.) not.
-    self unregisterClassInSmalltalk: oldClass notify: true.
-    classes := loaders at: oldClass classLoader ifAbsent: nil.
-    classes notNil ifTrue:[
-        classes removeKey: oldClass name.
-    ].
+    ^ self unregisterClass: oldClass ignoring: Set new.
 
     "Created: / 04-04-2012 / 02:43:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-10-2014 / 12:12:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-unregisterClassInSmalltalk: javaclass notify: doNotify
-    "Unregisters given class from Smalltalk system dictionary
-     so the class is no longer visible from Smalltalk"
-
-    | ns |
+unregisterClass: oldClass ignoring: ignoredClasses
+    | classes |
 
-    javaclass isSynthetic ifTrue:[ ^ self ].
-    ns := javaclass nameSpace.
-
-    ns isNameSpace ifTrue:[
-        "/Hmmm hmm, how to remove class from a namespace?.
-        "/ns at:nameComponents last asSymbol put:nil
+    classes := loaders at: oldClass classLoader ifAbsent: nil.
+    classes notNil ifTrue:[
+        "/ Check if the class is there, it could be removed meanwhile...
+        (classes includesKey: oldClass binaryName) ifTrue:[
+            "/ Now, invalidate references and unload all dependent clases
+            "/ (JavaClassReloader will unload them by recursively call #unregisterClass:
+            JavaClassReloader unload: oldClass ignoring: ignoredClasses.
+            "/ Now remove it from class registry...
+            classes removeKey: oldClass binaryName.
+            "/ ...from class loader...
+            self unregisterClassInClassLoader: oldClass.  
+            "/ ...from reflection cache....
+            JavaVM reflection removeJavaClassObjectForClass: oldClass.
+            "/ ...and from Smalltalk dictionary
+            self unregisterClassInSmalltalk: oldClass notify: true.
+        ]
     ].
 
-    doNotify ifTrue:[
-        notifier add:(Array with: #classRemove with: javaclass).
-    ].
-
-    "Created: / 04-04-2012 / 10:01:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 03-09-2013 / 00:41:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 10-10-2014 / 12:12:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-unregisterClassLoader: aJavaClassLoader 
-    loaders removeKey: aJavaClassLoader ifAbsent: nil.
+unregisterClassLoader: aJavaClassLoader
+    | classes |
+
+    classes := loaders at: aJavaClassLoader ifAbsent:[ ^ self ].
+    self unregisterClasses: classes values.
+    loaders removeKey: aJavaClassLoader.
 
     "Created: / 16-12-2012 / 16:39:45 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
+    "Modified: / 17-10-2013 / 10:37:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 unregisterClasses: classes
@@ -486,10 +449,180 @@
     "Created: / 02-01-2013 / 17:01:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!JavaClassRegistry methodsFor:'registering-private'!
+
+registerBuiltIn: class
+    | nm |
+
+    nm := class binaryName.
+    nm = #'java/lang/Object' ifTrue:[
+        _java_lang_Object_CLASS := class.
+        ^self.
+    ].
+    nm = #'java/lang/System' ifTrue:[
+        _java_lang_System_CLASS := class.
+        ^self.
+    ].
+    nm = #'java/lang/Class' ifTrue:[
+        _java_lang_Class_CLASS := class.
+        "/ Force load of other reflective classes. This saves us a nil check in
+        "/ JavaMirror>>createMethod...
+        #(#'java/lang/reflect/Constructor'  #'java/lang/reflect/Method' #'java/lang/reflect/Field') do:[:e|
+            vm classForName: e definedBy: nil.
+        ].
+        ^self.
+    ].
+    nm = #'java/lang/reflect/Constructor' ifTrue:[
+        _java_lang_reflect_Constructor_CLASS := class.
+    ].
+    nm = #'java/lang/reflect/Method' ifTrue:[
+        _java_lang_reflect_Method_CLASS := class.
+    ].
+    nm = #'java/lang/reflect/Field' ifTrue:[
+        _java_lang_reflect_Field_CLASS := class.
+    ].
+
+    "Created: / 22-05-2013 / 20:40:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 18-12-2013 / 13:03:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+registerClassInClassLoader: class
+    "Registers class in it's classloader"
+
+    "/ OpenJDK java.class.ClassLoader keeps list of all loaded classes
+    "/ in a field `classes`. This method adds the class to the list.
+    "/ For classes loaded by primordial class loader, `class classLoader1
+    "/ returns nil.
+    class classLoader notNil ifTrue:[
+        class classLoader perform: #'addClass(Ljava/lang/Class;)V' with: (JavaVM reflection javaClassObjectForClass: class).  
+    ].
+
+    "Created: / 11-08-2014 / 01:37:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+registerClassInSmalltalk: javaclass notify: doNotify
+    "Registers class in Smalltalk system dictionary and
+     notifies system, so the class become visible by
+     Smalltalk"
+
+    | nameComponents accessor nsName nsNameAsSymbol ns  |
+
+    javaclass isSynthetic ifTrue:[ ^ self ].
+    nameComponents := javaclass binaryName asCollectionOfSubstringsSeparatedBy:$/.
+    nameComponents size > 1 ifTrue:[
+        javaclass setCategory:((nameComponents asStringWith:$/ from:1 to:(nameComponents size - 1))
+                            replaceAll:$/ with:$. ).
+    ] ifFalse:[
+        javaclass setCategory:#'(default)'
+    ].
+
+    nameComponents size > 1 ifTrue:[
+        javaclass setPackage:((nameComponents copyButLast:1) asStringWith:$/) asSymbol
+    ] ifFalse:[
+        javaclass setPackage:#'java/(default)'
+    ].
+
+    "/ break up the package and create nameSpaces
+    "/ for each package component.
+    "/ This allows java.foo.bar to be visible in ST/X
+    "/ under the name JAVA::java::foo::bar
+
+    accessor := javaclass"JavaClassAccessor fullName: aString".
+    nsName := javaclass nameSpaceName.
+    nsNameAsSymbol := nsName asSymbolIfInterned.
+    (nsNameAsSymbol isNil or:[(ns := Smalltalk at: nsNameAsSymbol) isNil]) ifTrue:[
+        Metaclass confirmationQuerySignal answer:false do:[
+            Class withoutUpdatingChangesDo:[
+                ns := JavaPackage fullName:(nsName contents).
+            ].
+        ].
+    ].
+    ns isNameSpace ifTrue:[
+        ns at:nameComponents last asSymbol put:accessor.
+        javaclass setEnvironment: ns.
+        javaclass setName: (nsName , '::' , nameComponents last) asSymbol
+    ] ifFalse:[
+        self breakPoint: #jv
+    ].
+
+    doNotify ifTrue:[
+        notifier add:(Array with: #newClass with: javaclass).
+    ].
+
+    "Created: / 04-04-2012 / 10:01:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 08-10-2013 / 19:27:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+registerClassRedefined: class
+    "Class has been redefined, so we have to invalidate
+     caches in coresponding java.lang.Class. Luckily enough,
+     thee seem to be support for this - all we have to is to
+     increase class redefinition count."
+
+    | classObject classObjectRedefinitionCountIndex classObjectRedefinitionCount |
+
+    classObject := JavaVM reflection javaClassObjectForClass: class.
+    classObjectRedefinitionCountIndex := classObject class instVarIndexFor: #classRedefinedCount.
+    classObjectRedefinitionCount := classObject instVarAt:classObjectRedefinitionCountIndex.
+    classObjectRedefinitionCount := classObjectRedefinitionCount + 1.
+    classObject instVarAt:classObjectRedefinitionCountIndex put: classObjectRedefinitionCount.
+
+    "Created: / 15-08-2014 / 15:09:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+unregisterClassInClassLoader: class
+    "Unregisters class from it's classloader"
+
+    "/ OpenJDK java.class.ClassLoader keeps list of all loaded classes
+    "/ in a field `classes`. This method removes the class from the list.
+    "/ This happens for instance when class is unloaded or reloaded.
+    "/ For classes loaded by primordial class loader, `class classLoader1
+    "/ returns nil.
+    class classLoader notNil ifTrue:[
+        (class classLoader instVarNamed: #classes) 
+            perform: #'remove(Ljava/lang/Object;)Z' 
+            with: (JavaVM reflection javaClassObjectForClass: class).
+    ].
+
+    "Created: / 11-08-2014 / 01:38:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+unregisterClassInSmalltalk: javaclass notify: doNotify
+    "Unregisters given class from Smalltalk system dictionary
+     so the class is no longer visible from Smalltalk"
+
+    | nameInSmalltalk nameInSmalltalkSymbol nameSpace |
+
+    "/ Must wait here - if classes are added and removed too fast,
+    "/ a race condition occur in stx:libbasic code (something is
+    "/ nilled menawhile and event handler does not handle this case.
+    "/ This can happen for example when running tests...
+    notifier waitUntilProcessed.
+
+    javaclass isSynthetic ifTrue:[ ^ self ].
+    nameSpace := javaclass nameSpace.
+    nameInSmalltalk := javaclass nameInSmalltalk.
+    nameInSmalltalkSymbol := nameInSmalltalk asSymbolIfInterned.
+    nameInSmalltalkSymbol notNil ifTrue:[
+        Smalltalk removeKey: nameInSmalltalkSymbol
+    ].
+    doNotify ifTrue:[
+        notifier add:(Array with: #classRemove with: javaclass).
+    ].
+
+    [ nameSpace notNil and:[nameSpace ~~ JAVA and:[nameSpace allClasses size == 0]]] whileTrue:[
+        Smalltalk removeClass: nameSpace.
+        nameSpace := nameSpace nameSpace.
+    ].
+
+    "Created: / 04-04-2012 / 10:01:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 17-10-2013 / 10:50:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaClassRegistry class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libjava/JavaClassRegistry.st,v 1.5 2013-09-06 00:41:22 vrany Exp $'
+    ^ '$Header: /cvs/stx/stx/libjava/JavaClassRegistry.st,v 1.6 2015-01-28 02:10:50 vrany Exp $'
 !
 
 version_SVN