Some initial class reloading support. Not yet finished, just sketched out. jk_new_structure
authorvranyj1
Tue, 21 Feb 2012 11:29:41 +0000
branchjk_new_structure
changeset 1372 dea574a1b6b3
parent 1371 90a466f3d078
child 1373 4ead4b8163c0
Some initial class reloading support. Not yet finished, just sketched out.
src/GroovyCompiler.st
src/JavaClass.st
src/JavaClassContentRef2.st
src/JavaClassRef2.st
src/JavaClassRegistry.st
src/JavaClassReloader.st
src/JavaConstantPool.st
src/JavaField.st
src/JavaRef2.st
src/JavaStringRef2.st
src/JavaVM.st
src/Make.proto
src/Make.spec
src/abbrev.stc
src/bc.mak
src/libInit.cc
src/libjava.rc
--- a/src/GroovyCompiler.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/GroovyCompiler.st	Tue Feb 21 11:29:41 2012 +0000
@@ -72,6 +72,15 @@
 
 !GroovyCompiler class methodsFor:'compiler interface'!
 
+compile: source forClass: class inCategory: category notifying: requestor install: doInstall
+
+    "We allways compile whole class"
+
+    ^self compileClass: source.
+
+    "Created: / 21-02-2012 / 11:10:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 compileClass: source
     "Compiles a new Groovy class given the source code"
 
@@ -113,7 +122,7 @@
 
     GroovyClassLoader notNil ifTrue:[ ^ self ].
 
-    groovy_lang_GroovyClassLoader := Java classForName:'groovy.lang.GroovyClassLoader'.
+    groovy_lang_GroovyClassLoader := Java classForName:'stx.libjava.groovy.GroovyClassLoader'.
     GroovyClassLoader := groovy_lang_GroovyClassLoader newCleared.
     GroovyClassLoader
             perform: #'<init>(Ljava/lang/ClassLoader;)V'
--- a/src/JavaClass.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaClass.st	Tue Feb 21 11:29:41 2012 +0000
@@ -83,7 +83,7 @@
     "create the metaclass first"
 
     meta := Metaclass new.
-    meta setSuperclass:(self metaSuperclassForClassesLoadedBy: classLoader).
+    meta setSuperclass:self.
     meta instSize:(meta superclass instSize + nStatic).
 "/    meta setName:(aString , 'class') asSymbol.
 "/    meta setClassVariableString:''.
@@ -150,25 +150,7 @@
 
     "Created: / 15-04-1996 / 15:52:55 / cg"
     "Modified: / 03-01-1998 / 22:32:25 / cg"
-    "Modified: / 18-02-2012 / 20:27:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-metaSuperclassForClassesLoadedBy: classLoaderOrNil
-    "Returns a class to be used as meta superclass for
-     classes loaded by given classloader. Defaults to self.
-
-     Basically a hack for Groovy, but maybe usefull for other JVM
-     languages :-)"
-
-    classLoaderOrNil isNil ifTrue:[ ^ self ].
-
-    (classLoaderOrNil class name startsWith:'groovy/lang/GroovyClassLoader') ifTrue:[
-        ^ GroovyClass
-    ].
-
-    ^self
-
-    "Created: / 18-02-2012 / 20:24:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-02-2012 / 22:43:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 name:aString
@@ -1601,14 +1583,18 @@
     "Modified: / 5.11.1998 / 19:14:39 / cg"
 !
 
-setInterfaces:i
+setInterfaces: i
+
+    super setInterfaces: i.
     i size > 0 ifTrue:[
-	interfaces := i
-    ] ifFalse:[
-	interfaces := nil
+        i do:[:iface|
+            iface name = 'groovy/lang/GroovyObject' ifTrue:[
+                self class setSuperclass: GroovyClass.
+            ]
+        ]
     ]
 
-    "Modified: 7.4.1997 / 15:44:53 / cg"
+    "Created: / 20-02-2012 / 22:47:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setSource: aString
--- a/src/JavaClassContentRef2.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaClassContentRef2.st	Tue Feb 21 11:29:41 2012 +0000
@@ -165,13 +165,14 @@
     "Invalidate (means call invalidate) reference if it has something to do with given class (e.g Class named internalJavaClassName was unloaded).
      Return true, if reference was invalidated."
     
-    (self classRef invalidateForClass: internalJavaClassName) 
-        ifTrue: 
-            [ self invalidate.
-            ^ true ].
+    (self classRef invalidateForClass: internalJavaClassName) ifTrue: [ 
+        self invalidate.
+        ^ true 
+    ].
     ^ false.
 
     "Modified: / 12-05-2011 / 18:40:34 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Modified (format): / 21-02-2012 / 10:21:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaClassContentRef2 class methodsFor:'documentation'!
--- a/src/JavaClassRef2.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaClassRef2.st	Tue Feb 21 11:29:41 2012 +0000
@@ -221,17 +221,19 @@
 !JavaClassRef2 methodsFor:'resolving'!
 
 invalidateForClass: internalJavaClassName 
-    "Invalidate (means call invalidate) reference if it has something to do with given class (e.g Class named internalJavaClassName was unloaded).
-     Return true, if reference was invalidated."
+    "Invalidates receiver iff it refers (even indirectly)
+     to a class ref that has been resolved to given class.
+     Returns true, if the receiver has been invalidated,
+     false otherwise"
     
-    self name = internalJavaClassName 
-        ifTrue: 
-            [ 
-            self invalidate.
-            ^ true ].
+    self name = internalJavaClassName ifTrue: [ 
+        self invalidate.
+        ^ true 
+    ].
     ^ false.
 
     "Modified: / 23-05-2011 / 15:21:20 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Modified (format): / 21-02-2012 / 10:21:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 resolve
--- a/src/JavaClassRegistry.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaClassRegistry.st	Tue Feb 21 11:29:41 2012 +0000
@@ -250,36 +250,40 @@
 
 !JavaClassRegistry methodsFor:'registering'!
 
-registerClass: aJavaClass
-    | classes |
+registerClass: newClass
+    | classes oldClass |
+
+    self assert: (newClass name includes: $.) not.
+    loaders keysAndValuesDo:[:loader :classesPerLoader|
 
-    self assert: (aJavaClass name includes: $.) not.
-    loaders keysAndValuesDo:[:loader :classes|
-
-        (classes includesKey: aJavaClass name) ifTrue:[
-            loader == aJavaClass classLoader ifTrue:[
-                (classes at: aJavaClass name) ~~ aJavaClass ifTrue:[
-                    self breakPoint:#jv info: 'Trying to register class twice!!'
+        (classesPerLoader includesKey: newClass name) ifTrue:[
+            loader == newClass classLoader ifTrue:[
+                (oldClass := classesPerLoader at: newClass name) ~~ newClass ifTrue:[
+                    "Class already exists, reload & reinstall"
+                    classesPerLoader
+                        at: newClass name 
+                        put: (JavaClassReloader reload: oldClass with: newClass).
+                    ^self.                    
                 ].
             ] ifFalse:[
-                ((aJavaClass name == #Script1) 
-                    and:[aJavaClass superclass name == #'groovy/lang/Script']) ifFalse:[
+                ((newClass name == #Script1) 
+                    and:[newClass superclass name == #'groovy/lang/Script']) ifFalse:[
                         self breakPoint: #jv.
                     ]
             ]
         ]                        
     ].
 
-    classes := loaders at: aJavaClass classLoader ifAbsent: nil.
+    classes := loaders at: newClass classLoader ifAbsent: nil.
     classes isNil ifTrue:[
-        classes := loaders at: aJavaClass classLoader put: Dictionary new.
+        classes := loaders at: newClass classLoader put: Dictionary new.
     ].
-    classes at: aJavaClass name put: aJavaClass.
-    Smalltalk changed: #newClass with: aJavaClass.
+    classes at: newClass name put: newClass.
+    Smalltalk changed: #newClass with: 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: / 18-02-2012 / 22:43:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 20-02-2012 / 23:27:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaClassRegistry class methodsFor:'documentation'!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/src/JavaClassReloader.st	Tue Feb 21 11:29:41 2012 +0000
@@ -0,0 +1,330 @@
+"
+ COPYRIGHT (c) 1996-2011 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
+                            SWING Research Group, Czech Technical University in Prague
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+
+ [1] Code written at SWING Research Group contains a signature
+     of one of the above copright owners. For exact set of such code,
+     see the differences between this version and version stx:libjava
+     as of 1.9.2010
+"
+"{ Package: 'stx:libjava' }"
+
+Object subclass:#JavaClassReloader
+	instanceVariableNames:'oldClass newClass mustMigrateInstances mustMigrateClass
+		instFieldMapping staticFieldMapping'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Languages-Java-Support'
+!
+
+Object subclass:#FieldMapping
+	instanceVariableNames:'old new'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:JavaClassReloader
+!
+
+!JavaClassReloader class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1996-2011 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
+                            SWING Research Group, Czech Technical University in Prague
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+
+ [1] Code written at SWING Research Group contains a signature
+     of one of the above copright owners. For exact set of such code,
+     see the differences between this version and version stx:libjava
+     as of 1.9.2010
+
+"
+!
+
+documentation
+"
+    A main workhorse for reloading (updating) java classes
+    in running system.
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!JavaClassReloader class methodsFor:'reloading'!
+
+reload: oldClass with: newClass
+    ^ self new reload: oldClass with: newClass
+
+    "Created: / 20-02-2012 / 23:29:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaClassReloader methodsFor:'private'!
+
+invalidate
+
+    | anyInvalidated |
+
+    anyInvalidated := false.
+    JavaVM registry classesDo:[:class|
+        anyInvalidated := anyInvalidated | (self invalidateClass: class).
+    ].
+    anyInvalidated flushCaches.
+
+    "Created: / 21-02-2012 / 09:47:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+invalidateClass: javaClass
+
+    ^javaClass constantPool invalidateForClass: oldClass name
+
+    "Created: / 21-02-2012 / 09:58:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+migrate
+    "Possibly migrate instances and class. Return the class that should
+     be installed in registry afterwards"
+
+    mustMigrateInstances ifTrue:[
+        self migrateInstances.
+        mustMigrateClass ifTrue:[
+            self migrateClass
+        ].
+        ^newClass.
+    ].
+
+    mustMigrateClass ifTrue:[
+        self migrateClass.
+        ^newClass.
+    ].
+    self update.
+    ^oldClass.
+
+    "Created: / 20-02-2012 / 23:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+migrateClass
+
+    self error:'Not yet supported'
+
+    "Created: / 21-02-2012 / 11:04:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+migrateInstances
+
+    self error:'Not yet supported'
+
+    "Created: / 21-02-2012 / 11:04:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+prepare
+    "Analyze and prepare data for reloading" 
+
+    self prepareInstFieldMapping.
+    self prepareStaticFieldMapping.
+
+    "Created: / 20-02-2012 / 23:40:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+prepareFieldMap: fields
+    | map |
+
+    map := Dictionary new.
+    fields do:[ :field | map at: field name put: field ].
+    ^map
+
+    "Created: / 21-02-2012 / 09:42:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+prepareInstFieldMapping
+    "Scans both old and new class inst fields and create a mapping.
+     Sets mustMigrateInstances"
+
+    | newFields |
+
+    mustMigrateInstances := false.
+    instFieldMapping := Set new.
+    newFields := self prepareFieldMap: newClass fields.
+    oldClass fields do:[:old|
+        | new mapping |
+
+        new := newFields at: old name ifAbsent:[nil].
+        new notNil ifTrue:[ newFields removeKey: old name ].
+        mapping := FieldMapping old: old new: new.
+        mustMigrateInstances := mustMigrateInstances or:[mapping mustMigrate].
+        instFieldMapping add: mapping.
+    ].
+    "Remaining fields are new, i.e., does not exist in
+     old class. Add them to the mapping"
+    newFields do:[:new|
+        instFieldMapping add: (FieldMapping old: nil new: new).
+        mustMigrateInstances := true
+    ].
+
+    "Created: / 21-02-2012 / 09:32:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+prepareStaticFieldMapping
+    "Scans both old and new class inst fields and create a mapping.
+     Sets mustMigrateInstances"
+
+    | newFields |
+
+    mustMigrateClass := false.
+    staticFieldMapping := Set new.
+    newFields := self prepareFieldMap: newClass staticFields.
+    oldClass staticFields do:[:old|
+        | new mapping |
+
+        new := newFields at: old name ifAbsent:[nil].
+        new notNil ifTrue:[ newFields removeKey: old name ].
+        mapping := FieldMapping old: old new: new.
+        mustMigrateClass:= mustMigrateClass or:[mapping mustMigrate].
+        staticFieldMapping add: mapping.
+    ].
+    "Remaining fields are new, i.e., does not exist in
+     old class. Add them to the mapping"
+    newFields do:[:new|
+        staticFieldMapping add: (FieldMapping old: nil new: new).
+        mustMigrateClass:= true
+    ].
+
+    "Created: / 21-02-2012 / 09:45:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+update
+
+    "Brute force, copy instvars directly"
+    self assert: oldClass class instSize == newClass class instSize.
+
+    1 to: newClass class instSize do:[:i|
+        newClass instVarAt: i put: (oldClass instVarAt: i).
+    ].
+
+    "Created: / 21-02-2012 / 11:04:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaClassReloader methodsFor:'reloading'!
+
+reload
+
+    self prepare.
+    self invalidate.
+    ^self migrate.
+
+    "Created: / 20-02-2012 / 23:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+reload: oldClassA with: newClassA
+
+    oldClass := oldClassA.
+    newClass := newClassA.
+    ^ self reload.
+
+    "Created: / 20-02-2012 / 23:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaClassReloader::FieldMapping class methodsFor:'instance creation'!
+
+old: old new:new
+
+    ^self new old: old new: new.
+
+    "Created: / 21-02-2012 / 09:20:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaClassReloader::FieldMapping methodsFor:'accessing'!
+
+new
+    ^ new
+!
+
+new:something
+    new := something.
+!
+
+old
+    ^ old
+!
+
+old:something
+    old := something.
+!
+
+old:oldArg new:newArg 
+    old := oldArg.
+    new := newArg.
+! !
+
+!JavaClassReloader::FieldMapping methodsFor:'queries'!
+
+mustMigrate
+    "Returns true if the field must be migrated, false otherwise"
+
+    | oldD newD |
+
+    (old isNil or:[new isNil]) ifTrue:[ 
+        ^ true "Either one is missing, must migrate"
+    ].
+
+    old index ~~ new index ifTrue:[
+        ^true "Offsets changed, must migrate"
+    ].
+
+    oldD := old descriptor.
+    newD := new descriptor.
+
+    oldD = newD ifTrue:[
+        ^false"Same descriptor, the easy case"
+    ].
+
+    (oldD first == $L and: [newD first == $L]) ifTrue:[
+        ^false"Both object types, who cares about type safety in Smalltalk?"
+    ].
+
+    1 to: (oldD size min: newD size) do:[:i|
+        ((oldD at: i) == $L and: [ (newD at: i) == $L ]) ifTrue:[
+            ^false"Both object types, who cares about type safety in Smalltalk?"
+        ].
+        ((oldD at: i) ~~ $[ or: [ (newD at: i) ~~ $[ ]) ifTrue:[
+            ^true"Different primitive/array types, must migrate"
+        ].
+    ].
+
+    ^false
+
+    "Created: / 21-02-2012 / 10:57:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaClassReloader class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id$'
+! !
--- a/src/JavaConstantPool.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaConstantPool.st	Tue Feb 21 11:29:41 2012 +0000
@@ -53,29 +53,6 @@
 "
 ! !
 
-!JavaConstantPool class methodsFor:'initialization'!
-
-initialize
-    ConstantPools := OrderedCollection new: 1000.
-
-    "Modified: / 08-04-2011 / 17:28:07 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified: / 09-04-2011 / 09:25:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!JavaConstantPool class methodsFor:'instance creation'!
-
-new: size 
-    "return an initialized instance"
-    
-    ^ ConstantPools add: ((super new: size)
-                initialize;
-                yourself).
-
-    "Created: / 08-04-2011 / 16:56:18 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified: / 09-04-2011 / 09:24:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 11-04-2011 / 18:46:54 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-! !
-
 !JavaConstantPool class methodsFor:'accessing'!
 
 allConstantPools
@@ -175,15 +152,20 @@
     "Created: / 13-05-2011 / 09:05:34 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
 ! !
 
-!JavaConstantPool methodsFor:'initialization'!
+!JavaConstantPool methodsFor:'invalidation'!
 
-initialize
-    "Invoked when a new instance is created."
+invalidateForClass: slashedJavaClassName
+    "Invalidate all resolved references to given class.
+     Returns true if at least one ref has been invalidated,
+     false otherwise"
 
-    "/ please change as required (and remove this comment)
-    "/ owner := nil.
+    | anyInvalidated |
+    anyInvalidated := false.
+    self do:[:ref|anyInvalidated := anyInvalidated | (ref invalidateForClass: slashedJavaClassName)].
+    ^anyInvalidated
 
-    "/ super initialize.   -- commented since inherited method does nothing
+    "Created: / 08-04-2011 / 16:11:36 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Modified: / 21-02-2012 / 10:27:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaConstantPool methodsFor:'printing & storing'!
@@ -256,14 +238,6 @@
     "Created: / 13-05-2011 / 09:37:41 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
 !
 
-invalidateForClass: internalJavaClassName
-"go over all entries and call invalidateForClass on all references"
-
-self do: [:entry | entry isJavaRef ifTrue:[entry invalidateForClass: internalJavaClassName]].
-
-    "Created: / 08-04-2011 / 16:11:36 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-!
-
 updateClassRefsFrom:oldClass to:newClass
 owner == oldClass ifTrue:[
     self halt.
@@ -323,5 +297,3 @@
 version_SVN
     ^ '$Id$'
 ! !
-
-JavaConstantPool initialize!
--- a/src/JavaField.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaField.st	Tue Feb 21 11:29:41 2012 +0000
@@ -24,7 +24,7 @@
 	instanceVariableNames:'accessFlags class name descriptor signature index constantValue
 		annotations constantPool'
 	classVariableNames:'A_FINAL A_PRIVATE A_PROTECTED A_PUBLIC A_STATIC A_TRANSIENT
-		A_VOLATILE A_SMALLTALK A_SYBTHETIC A_ENUM FieldTypeClasses'
+		A_VOLATILE A_SMALLTALK A_SYNTHETIC A_ENUM FieldTypeClasses'
 	poolDictionaries:''
 	category:'Languages-Java-Reader-Support'
 !
@@ -65,7 +65,7 @@
     A_FINAL := 16r0010.
     A_VOLATILE := 16r0040.
     A_TRANSIENT := 16r0080.
-    A_SYBTHETIC := 16r1000.
+    A_SYNTHETIC := 16r1000.
     A_ENUM := 16r4000.
     FieldTypeClasses := (IdentityDictionary new)
                 at: #B put: JavaByte;
@@ -88,8 +88,9 @@
 
     "
      self initialize"
+
     "Modified: / 13-05-1998 / 14:44:43 / cg"
-    "Modified: / 10-08-2011 / 00:48:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-02-2012 / 09:28:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaField class methodsFor:'constants'!
@@ -166,6 +167,12 @@
     constantValue := aValue
 !
 
+descriptor
+    ^ descriptor
+
+    "Created: / 21-02-2012 / 11:13:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 ensureHasAnnotations
     annotations ifNil: [ annotations := JavaAnnotationContainer for:self ].
     ^ annotations
--- a/src/JavaRef2.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaRef2.st	Tue Feb 21 11:29:41 2012 +0000
@@ -211,12 +211,15 @@
 !
 
 invalidateForClass: internalJavaClassName 
-    "Invalidate (means call invalidate) reference if it has something to do with given class (e.g Class named internalJavaClassName was unloaded).
-     Return true, if reference was invalidated."
-    
+    "Invalidates receiver iff it refers (even indirectly)
+     to a class ref that has been resolved to given class.
+     Returns true, if the receiver has been invalidated,
+     false otherwise"
+
     ^ self subclassResponsibility.
 
     "Created: / 08-04-2011 / 15:59:57 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Modified (comment): / 21-02-2012 / 10:20:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 resolve
--- a/src/JavaStringRef2.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaStringRef2.st	Tue Feb 21 11:29:41 2012 +0000
@@ -93,10 +93,15 @@
 !
 
 invalidateForClass: internalJavaClassName
-   "am I really meaningful?"
-   self breakPoint:#mh.
+   "Invalidates receiver iff it refers (even indirectly)
+    to a class ref that has been resolved to given class.
+    Returns true, if the receiver has been invalidated,
+    false otherwise"
+
+    "Nothing to be done here"
 
     "Created: / 13-05-2011 / 17:22:34 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Modified: / 21-02-2012 / 10:21:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 name
--- a/src/JavaVM.st	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/JavaVM.st	Tue Feb 21 11:29:41 2012 +0000
@@ -5497,6 +5497,49 @@
     
     | className  b  off  len  pd  source  bs  cls |
     className := Java as_ST_String: (nativeContext argAt: 1).
+    "if name starts with java.* or package is signed by something else and we are not signed, throw security exception" 
+    "ClassLoadersTest>>testEyeOpeningClassLoaderLoadObject" 
+    "18.11. mh revised - they really test it against java., totally ignoring boot class path.. That surpsised me"
+    (className startsWith: 'java.') ifTrue: [
+        self throwSecurityExceptionWith: 'className=' , className
+    ].
+    cls := nil.
+    b := nativeContext argAt: 2.
+    off := nativeContext argAt: 3.
+    len := nativeContext argAt: 4.
+    pd := nativeContext argAt: 5.
+    source := Java as_ST_String: (nativeContext argAt: 6).
+    bs := (off = 0 and: [ len = b size ]) 
+        ifTrue: [ b readStream ] 
+        ifFalse: [ bs := (b copyFrom: off + 1 to: off + len) readStream ].
+    [
+        JavaClassReader classLoaderQuerySignal answer: nativeContext receiver
+            do: [ cls := JavaClassReader readStream: bs. ]
+    ] on: JavaClassReader invalidClassFormatSignal
+            do: [
+        :ex | 
+        self throwClassFormatError: ex description.
+        ^ nil.
+    ].
+    self assert: cls classLoader == nativeContext receiver.
+     "FIXME: What to do with source?"
+    self registry registerClass: cls.
+    "JavaClassReader classLoaderQuerySignal answer: nativeContext receiver
+        do: [ cls resolveAll. ]."
+    ^ self reflection javaClassObjectForClass: cls.
+
+    "Modified: / 08-12-2011 / 20:56:51 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Modified: / 20-02-2012 / 23:14:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+_java_lang_ClassLoader_defineClass1_OLD: nativeContext 
+    <javanative: 'java/lang/ClassLoader' name: 'defineClass1'>
+    "
+     private native Class defineClass1(String name, byte[] b, int off, int len,
+                                      ProtectionDomain pd, String source);"
+    
+    | className  b  off  len  pd  source  bs  cls |
+    className := Java as_ST_String: (nativeContext argAt: 1).
      "if name starts with java.* or package is signed by something else and we are not signed, throw security exception" "ClassLoadersTest>>testEyeOpeningClassLoaderLoadObject" "18.11. mh revised - they really test it against java., totally ignoring boot class path.. That surpsised me"
     (className startsWith: 'java.') ifTrue: [
         self throwSecurityExceptionWith: 'className=' , className
@@ -5532,6 +5575,7 @@
 
     "Modified: / 30-10-2011 / 21:46:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 08-12-2011 / 20:56:51 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+    "Created: / 20-02-2012 / 23:10:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 _java_lang_ClassLoader_findBootstrapClass: nativeContext 
@@ -14967,6 +15011,17 @@
     ^ self _WGraphics_pSetForeground:nativeContext
 ! !
 
+!JavaVM class methodsFor:'native - stx.libjava.groovy'!
+
+_stx_libjava_groovy_GroovyClassLoader_SystemClassCollector_getDefiningClassLoader: nativeContext
+
+    <javanative: 'stx/libjava/groovy/GroovyClassLoader$SystemClassCollector' name: 'getDefiningClassLoader()Lstx/libjava/groovy/GroovyClassLoader;'>
+
+    ^ SystemClassLoader
+
+    "Modified: / 20-02-2012 / 22:30:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaVM class methodsFor:'native - stx.libjava.tests'!
 
 _stx_libjava_tests_MonitorTests_abort: nativeContext
--- a/src/Make.proto	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/Make.proto	Tue Feb 21 11:29:41 2012 +0000
@@ -1,7 +1,7 @@
 # $Header$
 #
 # DO NOT EDIT
-# automagically generated from the projectDefinition: stx_libjava at 2012-02-18 23:17:47.809.
+# automagically generated from the projectDefinition: stx_libjava at 2012-02-21 11:23:47.629.
 #
 # Warning: once you modify this file, do not rerun
 # stmkmp or projectDefinition-build again - otherwise, your changes are lost.
@@ -157,6 +157,7 @@
 $(OUTDIR)JavaByte.$(O) JavaByte.$(H): JavaByte.st $(INCLUDE_TOP)/stx/libbasic/Integer.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaByteCodeProcessor.$(O) JavaByteCodeProcessor.$(H): JavaByteCodeProcessor.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaClassRegistry.$(O) JavaClassRegistry.$(H): JavaClassRegistry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)JavaClassReloader.$(O) JavaClassReloader.$(H): JavaClassReloader.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaConstantPool.$(O) JavaConstantPool.$(H): JavaConstantPool.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaConstants.$(O) JavaConstants.$(H): JavaConstants.st $(INCLUDE_TOP)/stx/libbasic/SharedPool.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaContext.$(O) JavaContext.$(H): JavaContext.st $(INCLUDE_TOP)/stx/libbasic/Context.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -230,7 +231,7 @@
 $(OUTDIR)JavaMethodDeclaratorNode.$(O) JavaMethodDeclaratorNode.$(H): JavaMethodDeclaratorNode.st $(INCLUDE_TOP)/stx/libjava/JavaNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaMethodDescriptor.$(O) JavaMethodDescriptor.$(H): JavaMethodDescriptor.st $(INCLUDE_TOP)/stx/libjava/JavaDescriptor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaMethodNode.$(O) JavaMethodNode.$(H): JavaMethodNode.st $(INCLUDE_TOP)/stx/libjava/JavaNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)JavaPetitParser.$(O) JavaPetitParser.$(H): JavaPetitParser.st $(INCLUDE_TOP)/squeak/petitparser/PPCompositeParser.$(H) $(INCLUDE_TOP)/squeak/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/squeak/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libjava/PPJavaNode.$(H) $(STCHDR)
+$(OUTDIR)JavaPetitParser.$(O) JavaPetitParser.$(H): JavaPetitParser.st $(INCLUDE_TOP)/squeak/petitparser/PPCompositeParser.$(H) $(INCLUDE_TOP)/squeak/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/squeak/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libjava/PPJavaNode.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)JavaStringRef2.$(O) JavaStringRef2.$(H): JavaStringRef2.st $(INCLUDE_TOP)/stx/libjava/JavaRef2.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaTypeNode.$(O) JavaTypeNode.$(H): JavaTypeNode.st $(INCLUDE_TOP)/stx/libjava/JavaNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaUnhandledExceptionError.$(O) JavaUnhandledExceptionError.$(H): JavaUnhandledExceptionError.st $(INCLUDE_TOP)/stx/libjava/JavaError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/src/Make.spec	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/Make.spec	Tue Feb 21 11:29:41 2012 +0000
@@ -1,7 +1,7 @@
 # $Header$
 #
 # DO NOT EDIT
-# automagically generated from the projectDefinition: stx_libjava at 2012-02-18 23:17:45.579.
+# automagically generated from the projectDefinition: stx_libjava at 2012-02-21 11:23:45.252.
 #
 # Warning: once you modify this file, do not rerun
 # stmkmp or projectDefinition-build again - otherwise, your changes are lost.
@@ -174,6 +174,7 @@
 	GroovyClass \
 	ProxyMethodJavaMethodInvocationNode \
 	ProxyMethodJavaTypeCheckNode \
+	JavaClassReloader \
 
 
 
@@ -303,6 +304,7 @@
     $(OUTDIR)GroovyClass.$(O) \
     $(OUTDIR)ProxyMethodJavaMethodInvocationNode.$(O) \
     $(OUTDIR)ProxyMethodJavaTypeCheckNode.$(O) \
+    $(OUTDIR)JavaClassReloader.$(O) \
     $(OUTDIR)extensions.$(O) \
 
 
--- a/src/abbrev.stc	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/abbrev.stc	Tue Feb 21 11:29:41 2012 +0000
@@ -140,7 +140,7 @@
 JavaByteCodeProcessorAdapter JavaByteCodeProcessorAdapter stx:libjava 'Languages-Java-Bytecode' 0
 JavaByteCodePreresolver JavaByteCodePreresolver stx:libjava 'Languages-Java-Bytecode' 0
 GroovyCompiler GroovyCompiler stx:libjava 'Languages-Groovy-Compiler' 0
-GroovyEvaluator GroovyEvaluator stx:libjava 'Languages-Groovy-Compiler' 0
+GroovyEvaluator GroovyEvaluator stx:libjava 'Languages-Java-Support' 0
 GroovyLanguage GroovyLanguage stx:libjava 'Languages-Groovy-Support' 1
 GroovySourceFileWriter GroovySourceFileWriter stx:libjava 'Languages-Groovy-Support' 0
 JavaLookup JavaLookup stx:libjava 'Languages-Java-Interop' 0
@@ -157,3 +157,4 @@
 GroovyClass GroovyClass stx:libjava 'Languages-Groovy-Classes' 0
 ProxyMethodJavaMethodInvocationNode ProxyMethodJavaMethodInvocationNode stx:libjava 'Languages-Java-Interop' 0
 ProxyMethodJavaTypeCheckNode ProxyMethodJavaTypeCheckNode stx:libjava 'Languages-Java-Interop' 0
+JavaClassReloader JavaClassReloader stx:libjava 'Languages-Java-Support' 0
--- a/src/bc.mak	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/bc.mak	Tue Feb 21 11:29:41 2012 +0000
@@ -1,7 +1,7 @@
 # $Header$
 #
 # DO NOT EDIT
-# automagically generated from the projectDefinition: stx_libjava at 2012-02-18 23:17:48.867.
+# automagically generated from the projectDefinition: stx_libjava at 2012-02-21 11:23:48.814.
 #
 # Warning: once you modify this file, do not rerun
 # stmkmp or projectDefinition-build again - otherwise, your changes are lost.
@@ -105,6 +105,7 @@
 $(OUTDIR)JavaByte.$(O) JavaByte.$(H): JavaByte.st $(INCLUDE_TOP)\stx\libbasic\Integer.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaByteCodeProcessor.$(O) JavaByteCodeProcessor.$(H): JavaByteCodeProcessor.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaClassRegistry.$(O) JavaClassRegistry.$(H): JavaClassRegistry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)JavaClassReloader.$(O) JavaClassReloader.$(H): JavaClassReloader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaConstantPool.$(O) JavaConstantPool.$(H): JavaConstantPool.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaConstants.$(O) JavaConstants.$(H): JavaConstants.st $(INCLUDE_TOP)\stx\libbasic\SharedPool.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaContext.$(O) JavaContext.$(H): JavaContext.st $(INCLUDE_TOP)\stx\libbasic\Context.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -178,7 +179,7 @@
 $(OUTDIR)JavaMethodDeclaratorNode.$(O) JavaMethodDeclaratorNode.$(H): JavaMethodDeclaratorNode.st $(INCLUDE_TOP)\stx\libjava\JavaNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaMethodDescriptor.$(O) JavaMethodDescriptor.$(H): JavaMethodDescriptor.st $(INCLUDE_TOP)\stx\libjava\JavaDescriptor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaMethodNode.$(O) JavaMethodNode.$(H): JavaMethodNode.st $(INCLUDE_TOP)\stx\libjava\JavaNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)JavaPetitParser.$(O) JavaPetitParser.$(H): JavaPetitParser.st $(INCLUDE_TOP)\squeak\petitparser\PPCompositeParser.$(H) $(INCLUDE_TOP)\squeak\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\squeak\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libjava\PPJavaNode.$(H) $(STCHDR)
+$(OUTDIR)JavaPetitParser.$(O) JavaPetitParser.$(H): JavaPetitParser.st $(INCLUDE_TOP)\squeak\petitparser\PPCompositeParser.$(H) $(INCLUDE_TOP)\squeak\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\squeak\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libjava\PPJavaNode.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)JavaStringRef2.$(O) JavaStringRef2.$(H): JavaStringRef2.st $(INCLUDE_TOP)\stx\libjava\JavaRef2.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaTypeNode.$(O) JavaTypeNode.$(H): JavaTypeNode.st $(INCLUDE_TOP)\stx\libjava\JavaNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaUnhandledExceptionError.$(O) JavaUnhandledExceptionError.$(H): JavaUnhandledExceptionError.st $(INCLUDE_TOP)\stx\libjava\JavaError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/src/libInit.cc	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/libInit.cc	Tue Feb 21 11:29:41 2012 +0000
@@ -41,6 +41,7 @@
 _JavaByte_Init(pass,__pRT__,snd);
 _JavaByteCodeProcessor_Init(pass,__pRT__,snd);
 _JavaClassRegistry_Init(pass,__pRT__,snd);
+_JavaClassReloader_Init(pass,__pRT__,snd);
 _JavaConstantPool_Init(pass,__pRT__,snd);
 _JavaConstants_Init(pass,__pRT__,snd);
 _JavaContext_Init(pass,__pRT__,snd);
--- a/src/libjava.rc	Sat Feb 18 23:55:36 2012 +0000
+++ b/src/libjava.rc	Tue Feb 21 11:29:41 2012 +0000
@@ -3,7 +3,7 @@
 // automagically generated from the projectDefinition: stx_libjava.
 //
 VS_VERSION_INFO VERSIONINFO
-  FILEVERSION     6,2,1716,1716
+  FILEVERSION     6,2,1725,1725
   PRODUCTVERSION  6,2,1,1
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
@@ -20,12 +20,12 @@
     BEGIN
       VALUE "CompanyName", "eXept Software AG\0"
       VALUE "FileDescription", "Smalltalk/X Class library (LIB)\0"
-      VALUE "FileVersion", "6.2.1716.1716\0"
+      VALUE "FileVersion", "6.2.1725.1725\0"
       VALUE "InternalName", "stx:libjava\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2011\nCopyright eXept Software AG 1998-2011\nCopyright Jan Vrany, Jan Kurs and Marcel Hlopko\b          SWING Research Group, Czech Technical University In Prague\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.1.1\0"
-      VALUE "ProductDate", "Sat, 18 Feb 2012 23:18:20 GMT\0"
+      VALUE "ProductDate", "Tue, 21 Feb 2012 11:24:33 GMT\0"
     END
 
   END