Temporary commit. method resolving fixed jk_new_structure
authorvranyj1
Wed, 10 Aug 2011 22:22:53 +0000
branchjk_new_structure
changeset 905 d03d9e05c581
parent 904 0403a07748ea
child 906 fea23aa2b228
Temporary commit. method resolving fixed
src/JavaClass.st
src/JavaProcess.st
src/JavaResolver.st
src/JavaTestCaseProxy.st
src/JavaVM.st
src/TestletTestCaseProxy.st
src/extensions.st
src/stx_libjava.st
--- a/src/JavaClass.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/JavaClass.st	Wed Aug 10 22:22:53 2011 +0000
@@ -1475,23 +1475,25 @@
 !
 
 lookupMethodFor:selector
-    |method cls sel|
+    |method cls sel queue |
 
     sel := selector asSymbolIfInterned.
     sel notNil ifTrue:[
-        cls := self.
-        [cls ~= JavaObject] whileTrue:[
+        queue := OrderedCollection with: self.
+        [ queue isEmpty ] whileFalse:[
+            cls := queue removeFirst.
             method := cls compiledMethodAt:sel.
             method notNil ifTrue:[ ^ method ].
-            cls := cls isInterface 
-                        ifFalse: [cls superclass]
-                        ifTrue:  [cls superinterface].
+            queue addAll: cls interfaces.
+            cls isInterface ifFalse:[
+                cls superclass ~~ JavaObject ifTrue:[queue add: cls superclass]
+            ]
         ].
     ].
-    cls ifNotNil:[^super lookupMethodFor: selector].
+    "/cls ifNotNil:[^super lookupMethodFor: selector].
     ^ nil
 
-    "Modified: / 17-03-2011 / 13:52:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 22:40:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 performStatic:selector
--- a/src/JavaProcess.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/JavaProcess.st	Wed Aug 10 22:22:53 2011 +0000
@@ -187,94 +187,108 @@
 value
     |procName|
 
-    Object abortSignal handle:
-            [:ex | 
+    Object abortSignal 
+        handle:[:ex | 
             procName := javaProcess name.
-            (procName startsWith:'JAVA-AWT-EventQueue') 
-                ifTrue:
-                    [ ('JAVA [info]: thread ' , procName , ' aborted - restarting process.') 
-                        infoPrintCR.
-                    ex restart. ]
-                ifFalse:
-                    [ (javaProcess == (Smalltalk at:#'JavaVM:JavaScreenUpdaterThread') 
-                        or:[ javaProcess == (Smalltalk at:#'JavaVM:JavaEventQueueThread') ]) 
-                            ifTrue:
-                                [ ('JAVA [info]: thread ' , procName , ' aborted - restarting process.') 
-                                    infoPrintCR.
-                                ex restart ]
-                            ifFalse:[ ('JAVA [info]: thread ' , procName , ' aborted.') infoPrintCR. ] ]. ]
-        do:
-            [ 
-            [ JavaVM javaExceptionSignal handle:
-                    [:ex | 
-                    |exClass|
+            (procName startsWith:'JAVA-AWT-EventQueue') ifTrue:[
+                ('JAVA [info]: thread ' , procName , ' aborted - restarting process.') 
+                    infoPrintCR.
+                ex restart.
+            ] ifFalse:[
+                (javaProcess == (Smalltalk at:#'JavaVM:JavaScreenUpdaterThread') 
+                    or:[javaProcess == (Smalltalk at:#'JavaVM:JavaEventQueueThread')]) 
+                        ifTrue:[
+                            ('JAVA [info]: thread ' , procName , ' aborted - restarting process.') 
+                                infoPrintCR.
+                            ex restart
+                        ]
+                        ifFalse:[('JAVA [info]: thread ' , procName , ' aborted.') infoPrintCR.]
+            ].
+        ]
+        do:[
+            [
+                JavaVM javaExceptionSignal 
+                    handle:[:ex | 
+                        |exClass|
 
-                    procName := javaProcess name.
-                    exClass := ex parameter class.
-                    exClass == (Java at:'java.lang.ThreadDeath') 
-                        ifTrue:[ ('JAVA: thread ' , procName , ' terminated') infoPrintCR. ]
-                        ifFalse:
-                            [ Transcript 
+                        procName := javaProcess name.
+                        exClass := ex parameter class.
+                        exClass == (Java at:'java.lang.ThreadDeath') ifTrue:[
+                            ('JAVA: thread ' , procName , ' terminated') infoPrintCR.
+                        ] ifFalse:[
+                            Transcript 
                                 showCR:('JAVA: thread ''' , procName , ''' terminated with exception: ' 
-                                        , exClass name). ].
-                    ex return. ]
-                do:
-                    [ Object messageNotUnderstoodSignal handle:
-                            [:ex | 
-                            |
-                            "/ remap doesNotUnderstand with nil-receiver to
-                            "/ a nullPointerException ...
-                             con m|
+                                        , exClass name).
+                        ].
+                        ex return.
+                    ]
+                    do:[
+                        Object messageNotUnderstoodSignal 
+                            handle:[:ex | 
+                                |
+                                "/ remap doesNotUnderstand with nil-receiver to
+                                "/ a nullPointerException ...
+                                 con m|
 
-                            con := ex suspendedContext.
-                            con receiver isNil 
-                                ifTrue:
-                                    [ ((m := con sender method) notNil and:[ m isJavaMethod ]) 
-                                        ifTrue:
-                                            [ JavaVM throwNullPointerException.
-                                            AbortSignal raise.
-                                            "/ ex proceed.
-                                             ] ].
-                            ex reject. ]
-                        do:
-                            [ "/ Transcript showCR:(Timestamp now printString , 'start thread: ', stProcess name).
-                            javaThreadObject perform:#'run()V'.
-                            (Smalltalk at:#'JavaVM:ThreadTrace') == true 
-                                ifTrue:[ ('JAVA: thread ' , javaProcess name , ' terminated') infoPrintCR. ].
-                            javaThreadObject perform:#'exit()V'.
-                            (Smalltalk at:#'JavaVM:ThreadTrace') == true 
-                                ifTrue:[ ('JAVA: after exit of thread ' , javaProcess name) infoPrintCR. ] ] ] ] ensure:
-                        [ |monitors|
+                                con := ex suspendedContext.
+                                con receiver isNil ifTrue:[
+                                    ((m := con sender method) notNil and:[m isJavaMethod]) ifTrue:[
+                                        JavaVM throwNullPointerException.
+                                        AbortSignal raise.
+                                        
+                                        "/ ex proceed.
+                                    ]
+                                ].
+                                ex reject.
+                            ]
+                            do:[
+                                "/ Transcript showCR:(Timestamp now printString , 'start thread: ', stProcess name).
+                                javaThreadObject perform:#'run()V'.
+                                (Smalltalk at:#'JavaVM:ThreadTrace') == true ifTrue:[
+                                    ('JAVA: thread ' , javaProcess name , ' terminated') infoPrintCR.
+                                ].
+                                javaThreadObject perform:#'exit()V'.
+                                (Smalltalk at:#'JavaVM:ThreadTrace') == true ifTrue:[
+                                    ('JAVA: after exit of thread ' , javaProcess name) infoPrintCR.
+                                ]
+                            ]
+                    ]
+            ] ensure:[
+                |monitors|
 
-                        monitors := (Smalltalk at:#'JavaVM:EnteredMonitorsPerProcess') 
-                                    at:javaProcess
-                                    ifAbsent:nil.
-                        monitors notNil 
-                            ifTrue:
-                                [ monitors do:
-                                        [:obj | 
-                                        |mon|
+                monitors := (Smalltalk at:#'JavaVM:EnteredMonitorsPerProcess') 
+                            at:javaProcess
+                            ifAbsent:nil.
+                monitors notNil ifTrue:[
+                    monitors do:[:obj | 
+                        |mon|
 
-                                        mon := JavaVM monitorFor:obj.
-                                        mon notNil 
-                                            ifTrue:
-                                                [ mon owningProcess == javaProcess 
-                                                    ifTrue:
-                                                        [ ('JAVA: release monitor owned by dying thread: ' , javaProcess name) 
-                                                            infoPrintCR.
-                                                        mon exit ]. ]. ].
-                                (Smalltalk at:#'JavaVM:EnteredMonitorsPerProcess') removeKey:javaProcess.
-                                javaProcess == (Smalltalk at:#'JavaVM:JavaScreenUpdaterThread') 
-                                    ifTrue:[ Smalltalk at:#'JavaVM:JavaScreenUpdaterThread' put:nil. ].
-                                javaProcess == (Smalltalk at:#'JavaVM:JavaEventQueueThread') 
-                                    ifTrue:[ Smalltalk at:#'JavaVM:JavaEventQueueThread' put:nil. ].
-                                
+                        mon := JavaVM monitorFor:obj.
+                        mon notNil ifTrue:[
+                            mon owningProcess == javaProcess ifTrue:[
+                                ('JAVA: release monitor owned by dying thread: ' , javaProcess name) 
+                                    infoPrintCR.
+                                self breakPoint: #jv.
+                                mon exit
+                            ].
+                        ].
+                    ].
+                    (Smalltalk at:#'JavaVM:EnteredMonitorsPerProcess') removeKey:javaProcess.
+                    javaProcess == (Smalltalk at:#'JavaVM:JavaScreenUpdaterThread') ifTrue:[
+                        Smalltalk at:#'JavaVM:JavaScreenUpdaterThread' put:nil.
+                    ].
+                    javaProcess == (Smalltalk at:#'JavaVM:JavaEventQueueThread') ifTrue:[
+                        Smalltalk at:#'JavaVM:JavaEventQueueThread' put:nil.
+                    ].
+                    
 "/                                    screenUpdaterClass := Java at:'sun.awt.ScreenUpdater'.    
 "/                                    screenUpdaterClass notNil ifTrue:[
 "/                                        screenUpdaterClass instVarNamed:'updater' put:nil.
 "/                                    ].
-                                 ].
-                        Java threads removeKey:javaThreadObject ifAbsent:[]. ] ]
+                ].
+                Java threads removeKey:javaThreadObject ifAbsent:[].
+            ]
+        ]
 
     "Created: / 15-12-2010 / 11:06:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
--- a/src/JavaResolver.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/JavaResolver.st	Wed Aug 10 22:22:53 2011 +0000
@@ -613,7 +613,7 @@
      (ยง5.4.4) to D, method resolution throws an IllegalAccessError."
     result := class lookupMethodByNameAndType: aJavaMethodRef nameAndType.
     result ifNil: [ self throwNoSuchMethodError ].
-    (result isAbstract and: [ class isAbstract not ]) 
+    (result isAbstract and:[result javaClass isInterface not and:[ class isAbstract not ]]) 
         ifTrue: [ self throwAbstractMethodError ].
     (self 
         checkPermissionsForMethod: result
@@ -629,7 +629,7 @@
 
     "Created: / 11-04-2011 / 19:45:34 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
     "Modified: / 14-04-2011 / 00:01:34 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified: / 11-06-2011 / 17:45:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 22:44:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 resolveStaticMethodIndentifiedByRef: aJavaMethodRef 
--- a/src/JavaTestCaseProxy.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/JavaTestCaseProxy.st	Wed Aug 10 22:22:53 2011 +0000
@@ -149,6 +149,13 @@
 
 shouldFork:aBoolean
     shouldFork := aBoolean.
+!
+
+sunitName
+
+    ^javaClassName
+
+    "Created: / 10-08-2011 / 21:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaTestCaseProxy class methodsFor:'private'!
--- a/src/JavaVM.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/JavaVM.st	Wed Aug 10 22:22:53 2011 +0000
@@ -3100,7 +3100,8 @@
                 "/ on the fly, release any monitor
                 method isSynchronized ifTrue:[
                     method isStatic ifTrue:[
-                        monitorObject := method javaClass
+                        self assert: srchCon receiver == method javaClass.
+                        monitorObject := method javaClass.
                     ] ifFalse:[
                         monitorObject := srchCon receiver
                     ].
@@ -3150,7 +3151,7 @@
 
     "Created: / 07-01-1998 / 15:28:22 / cg"
     "Modified: / 24-12-1999 / 02:33:25 / cg"
-    "Modified: / 04-03-2011 / 00:07:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 20:23:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 throwExceptionClassName:aJavaExceptionClassName withMessage:someMessage
@@ -3347,47 +3348,50 @@
 
     "/ should always be bytes
     bytes class isBytes ifFalse:[
-	self halt.
+        self halt.
     ].
     stream == Stdin ifTrue:[
-	stream := StdinReplacementFileQuerySignal raiseRequest.
-	stream isNil ifTrue:[
-	    ^ -1 "/ 0  EOF
-	]
+        stream := StdinReplacementFileQuerySignal raiseRequest.
+        stream isNil ifTrue:[
+            ^ -1 "/ 0  EOF
+        ]
     ].
 
     FileIOTrace ifTrue:[
-	('JAVA: read ' , count printString , ' bytes from ' , stream pathName) infoPrintCR.
+        ('JAVA: read ' , count printString , ' bytes from ' , stream pathName) infoPrintCR.
     ].
 
     stream isPositionable ifFalse:[
-	"/ mhmh - some kind of socket or pipe
-
-	stream readWait.
-    ].
+        "/ mhmh - some kind of socket or pipe
+
+        stream readWait.
+    ].
+
+    count == 0 ifTrue:[^0].
 
     Stream readErrorSignal handle:[:ex |
-	nRead := -1
+        nRead := -1
     ] do:[
-	nRead := stream nextAvailableBytes:count into:bytes startingAt:offset+1.
+        nRead := stream nextAvailableBytes:count into:bytes startingAt:offset+1.
     ].
     nRead == 0 ifTrue:[
-	stream atEnd ifTrue:[
-	    FileIOTrace ifTrue:[
-		('JAVA: at EOF ' , nRead printString) infoPrintCR.
-	    ].
-	    ^ -1
-	].
+        stream atEnd ifTrue:[
+            FileIOTrace ifTrue:[
+                ('JAVA: at EOF ' , nRead printString) infoPrintCR.
+            ].
+            ^ -1
+        ].
     ].
     count ~~ nRead ifTrue:[
-	FileIOTrace ifTrue:[
-	    ('JAVA: only got ' , nRead printString) infoPrintCR.
-	]
+        FileIOTrace ifTrue:[
+            ('JAVA: only got ' , nRead printString) infoPrintCR.
+        ]
     ].
     ^ nRead
 
-    "Created: / 4.2.1998 / 15:20:00 / cg"
-    "Modified: / 10.11.1998 / 19:56:47 / cg"
+    "Created: / 04-02-1998 / 15:20:00 / cg"
+    "Modified: / 10-11-1998 / 19:56:47 / cg"
+    "Modified: / 10-08-2011 / 21:35:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 anyStream_writeBytes:nativeContext
@@ -3535,8 +3539,14 @@
             ^self throwFileNotFoundException: 'File is not readable'    
         ].
         stream := fn readStream.
-    ] ifFalse:[
-        (fn exists and:[fn isWritable not]) ifTrue:[
+    ] ifFalse:[    
+        fn exists ifTrue:[
+            ^self throwFileNotFoundException: 'File does not exist'
+        ].
+        fn isDirectory ifTrue:[
+             ^self throwFileNotFoundException: 'File is directory'
+        ].
+        fn isWritable ifFalse:[
             ^self throwFileNotFoundException: 'File does not writable'    
         ].
         forAppend ifTrue:[
@@ -3559,7 +3569,7 @@
 
     "Created: / 07-04-1998 / 19:14:09 / cg"
     "Modified: / 04-01-1999 / 14:34:42 / cg"
-    "Modified: / 10-08-2011 / 18:59:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 21:45:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileStreamForReading:name
@@ -3948,9 +3958,10 @@
 
     <javanative: 'java/io/FileInputStream' name: 'readBytes'>
 
-        ^ self anyStream_readBytes:nativeContext
-
-    "Modified: / 4.2.1998 / 15:23:08 / cg"
+    ^ self anyStream_readBytes:nativeContext
+
+    "Modified: / 04-02-1998 / 15:23:08 / cg"
+    "Modified (format): / 10-08-2011 / 21:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 _java_io_FileOutputStream_close0: nativeContext
@@ -4111,7 +4122,82 @@
 
     <javanative: 'java/io/RandomAccessFile' name: 'initIDs'>
 
-    ^ UnimplementedNativeMethodSignal raise
+    "Nothing to do"
+
+    "Modified: / 10-08-2011 / 21:49:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+_java_io_RandomAccessFile_open: nativeContext
+
+    <javanative: 'java/io/RandomAccessFile' name: 'open'>
+
+        |fs fd name dir stream fileNo answer readonly|
+
+    readonly := false.
+
+    fs := nativeContext receiver.
+    fd := fs instVarNamed:'fd'.
+    (fd instVarNamed:'fd') ~~ 0 ifTrue:[
+	self halt:'file already open'.
+	self internalError:'file already open'.
+	^ self.
+    ].
+
+    name := nativeContext argAt:1.
+    name := Java as_ST_String:name.
+    name := self fixFilename:name.
+
+    FileOpenTrace ifTrue:[
+	('JAVA: opening ' , name) infoPrintCR.
+    ].
+
+    dir := name asFilename directory pathName.
+
+    (PermittedDirectories notNil
+    and:[PermittedDirectories includes:dir]) ifFalse:[
+	FileOpenConfirmation ifTrue:[
+	    answer := Dialog 
+		    confirmWithCancel:('JAVA Security check\\Opening ''' , name , ''' for read/write.\Grant permission ?') withCRs
+			       labels:#('no' 'grant' 'readonly')
+			       values:#(false true #readonly)
+			      default:3.
+	    answer == false ifTrue:[
+		self throwIOExceptionWithMessage:('no permission to open ' , name , ' for writing').
+		^ self
+	    ].
+	    readonly := (answer == #readonly).
+
+	    readonly ifFalse:[
+		(self confirm:('JAVA Security check\\Always permit writes in this directory (''' , dir , ''') ?') withCRs)
+		ifTrue:[
+		    PermittedDirectories isNil ifTrue:[
+			PermittedDirectories := Set new
+		    ].
+		    PermittedDirectories add:dir.
+		]
+	    ]
+	]
+    ].
+
+    readonly ifTrue:[
+	stream := name asFilename readStream.
+    ] ifFalse:[
+	stream := name asFilename readWriteStream.
+    ].
+    stream isNil ifTrue:[
+	self throwIOExceptionWithMessage:('cannot open ' , name , ' for writing').
+    ].
+
+    fileNo := self addOpenFile:stream.
+
+    FileOpenTrace ifTrue:[
+	('JAVA: opened ' , name , ' as FD ' , fileNo printString , ' for writing') infoPrintCR.
+    ].
+
+    fd instVarNamed:'fd' put:fileNo.
+
+    "Created: / 4.2.1998 / 00:14:48 / cg"
+    "Modified: / 12.11.1998 / 21:29:46 / cg"
 !
 
 _java_io_UnixFileSystem_canonicalize0: aJavaContext
@@ -4565,22 +4651,20 @@
 
         "get a classes loader"
     
-    |jClass cls loader|
+    |jClass cls clc loader |
 
     jClass := aJavaContext receiver.
     cls := self reflection classForJavaClassObject:jClass.
     loader := cls classLoader.
-"/    loader isNil ifTrue:[
-"/        loader := (Java classForName:'java/lang/ClassLoader') 
-"/                    perform:#'getSystemClassLoader()Ljava/lang/ClassLoader;'.
-"/        
-"/    ('JAVA: getClassLoader - ' , loader printString) infoPrintCR.
-"/    ].
+    loader isNil ifTrue:[
+        cls := (Java at:'java/lang/ClassLoader').
+        clc notNil ifTrue:[loader := clc instVarNamed: #scl].
+    ].
     ^ loader
 
     "Created: / 25-10-2010 / 22:49:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 28-01-2011 / 15:18:54 / Marcel Hlopko <hlopik@gmail.com>"
-    "Modified: / 08-08-2011 / 10:09:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 23:02:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 _java_lang_Class_getComponentType: nativeContext
@@ -5285,6 +5369,15 @@
     "Created: / 12.11.1998 / 18:56:06 / cg"
 !
 
+_java_lang_Shutdown_halt0: nativeContext
+
+    <javanative: 'java/lang/Shutdown' name: 'halt0'>
+
+    "Intentionally left empty!!!!!!"
+
+    "Modified: / 10-08-2011 / 22:20:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 _java_lang_StrictMath_cbrt: nativeContext
 
     <javanative: 'java/lang/StrictMath' name: 'cbrt'>
@@ -9857,76 +9950,6 @@
     "Created: / 4.2.1998 / 13:27:58 / cg"
 !
 
-_RandomAccessFile_open:nativeContext
-    |fs fd name dir stream fileNo answer readonly|
-
-    readonly := false.
-
-    fs := nativeContext receiver.
-    fd := fs instVarNamed:'fd'.
-    (fd instVarNamed:'fd') ~~ 0 ifTrue:[
-	self halt:'file already open'.
-	self internalError:'file already open'.
-	^ self.
-    ].
-
-    name := nativeContext argAt:1.
-    name := Java as_ST_String:name.
-    name := self fixFilename:name.
-
-    FileOpenTrace ifTrue:[
-	('JAVA: opening ' , name) infoPrintCR.
-    ].
-
-    dir := name asFilename directory pathName.
-
-    (PermittedDirectories notNil
-    and:[PermittedDirectories includes:dir]) ifFalse:[
-	FileOpenConfirmation ifTrue:[
-	    answer := Dialog 
-		    confirmWithCancel:('JAVA Security check\\Opening ''' , name , ''' for read/write.\Grant permission ?') withCRs
-			       labels:#('no' 'grant' 'readonly')
-			       values:#(false true #readonly)
-			      default:3.
-	    answer == false ifTrue:[
-		self throwIOExceptionWithMessage:('no permission to open ' , name , ' for writing').
-		^ self
-	    ].
-	    readonly := (answer == #readonly).
-
-	    readonly ifFalse:[
-		(self confirm:('JAVA Security check\\Always permit writes in this directory (''' , dir , ''') ?') withCRs)
-		ifTrue:[
-		    PermittedDirectories isNil ifTrue:[
-			PermittedDirectories := Set new
-		    ].
-		    PermittedDirectories add:dir.
-		]
-	    ]
-	]
-    ].
-
-    readonly ifTrue:[
-	stream := name asFilename readStream.
-    ] ifFalse:[
-	stream := name asFilename readWriteStream.
-    ].
-    stream isNil ifTrue:[
-	self throwIOExceptionWithMessage:('cannot open ' , name , ' for writing').
-    ].
-
-    fileNo := self addOpenFile:stream.
-
-    FileOpenTrace ifTrue:[
-	('JAVA: opened ' , name , ' as FD ' , fileNo printString , ' for writing') infoPrintCR.
-    ].
-
-    fd instVarNamed:'fd' put:fileNo.
-
-    "Created: / 4.2.1998 / 00:14:48 / cg"
-    "Modified: / 12.11.1998 / 21:29:46 / cg"
-!
-
 _RandomAccessFile_read:nativeContext
     |file byte|
 
@@ -13795,6 +13818,76 @@
     ^ self commonOpen:nativeContext forAppend:true
 
     "Modified: / 7.4.1998 / 19:13:42 / cg"
+!
+
+_RandomAccessFile_open:nativeContext
+    |fs fd name dir stream fileNo answer readonly|
+
+    readonly := false.
+
+    fs := nativeContext receiver.
+    fd := fs instVarNamed:'fd'.
+    (fd instVarNamed:'fd') ~~ 0 ifTrue:[
+	self halt:'file already open'.
+	self internalError:'file already open'.
+	^ self.
+    ].
+
+    name := nativeContext argAt:1.
+    name := Java as_ST_String:name.
+    name := self fixFilename:name.
+
+    FileOpenTrace ifTrue:[
+	('JAVA: opening ' , name) infoPrintCR.
+    ].
+
+    dir := name asFilename directory pathName.
+
+    (PermittedDirectories notNil
+    and:[PermittedDirectories includes:dir]) ifFalse:[
+	FileOpenConfirmation ifTrue:[
+	    answer := Dialog 
+		    confirmWithCancel:('JAVA Security check\\Opening ''' , name , ''' for read/write.\Grant permission ?') withCRs
+			       labels:#('no' 'grant' 'readonly')
+			       values:#(false true #readonly)
+			      default:3.
+	    answer == false ifTrue:[
+		self throwIOExceptionWithMessage:('no permission to open ' , name , ' for writing').
+		^ self
+	    ].
+	    readonly := (answer == #readonly).
+
+	    readonly ifFalse:[
+		(self confirm:('JAVA Security check\\Always permit writes in this directory (''' , dir , ''') ?') withCRs)
+		ifTrue:[
+		    PermittedDirectories isNil ifTrue:[
+			PermittedDirectories := Set new
+		    ].
+		    PermittedDirectories add:dir.
+		]
+	    ]
+	]
+    ].
+
+    readonly ifTrue:[
+	stream := name asFilename readStream.
+    ] ifFalse:[
+	stream := name asFilename readWriteStream.
+    ].
+    stream isNil ifTrue:[
+	self throwIOExceptionWithMessage:('cannot open ' , name , ' for writing').
+    ].
+
+    fileNo := self addOpenFile:stream.
+
+    FileOpenTrace ifTrue:[
+	('JAVA: opened ' , name , ' as FD ' , fileNo printString , ' for writing') infoPrintCR.
+    ].
+
+    fd instVarNamed:'fd' put:fileNo.
+
+    "Created: / 4.2.1998 / 00:14:48 / cg"
+    "Modified: / 12.11.1998 / 21:29:46 / cg"
 ! !
 
 !JavaVM class methodsFor:'native - sun.management'!
@@ -14901,12 +14994,12 @@
 !
 
 _MONITORENTER:someObject
-    |mon thisProcess|
+    |mon thisProcess objString |
 
     someObject isNil ifTrue:[
-	self throwNullPointerException.
-	self halt.
-	^ self
+        self throwNullPointerException.
+        self halt.
+        ^ self
     ].
 
     self syncMonitorCache.
@@ -14918,26 +15011,33 @@
     mon := self monitorFor:someObject.
 
     MonitorTrace ifTrue:[
-	('====> entering monitor for ' , someObject displayString , ' in ' , thisProcess name , ' ...') printCR.
+        someObject isJavaClass ifTrue:[
+            objString := someObject name
+        ] ifFalse:[
+            objString := someObject class name , '@' , someObject identityHash printString.
+        ].
+
+        ('====> entering monitor for ' , objString , ' in ' , thisProcess name , ' ...') printCR.
     ].
     mon enter.
     MonitorTrace ifTrue:[
-	('====> entered it in ' , thisProcess name , ' ...') printCR.
+        ('====> entered it in ' , thisProcess name , ' ...') printCR.
     ].
 
     (self enteredMonitorsOfProcess:thisProcess) add:someObject.
 
-    "Created: / 8.1.1999 / 14:23:10 / cg"
-    "Modified: / 8.1.1999 / 18:47:26 / cg"
+    "Created: / 08-01-1999 / 14:23:10 / cg"
+    "Modified: / 08-01-1999 / 18:47:26 / cg"
+    "Modified: / 10-08-2011 / 20:19:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 _MONITOREXIT:someObject
-    |mon thisProcess wasBlocked lastMon|
+    |mon thisProcess wasBlocked lastMon objString |
 
     someObject isNil ifTrue:[
-	self throwNullPointerException.
-	self halt.
-	^ self
+        self throwNullPointerException.
+        self halt.
+        ^ self
     ].
 
     self syncMonitorCache.
@@ -14947,26 +15047,33 @@
     mon := self monitorFor:someObject.
 
     MonitorTrace ifTrue:[
-	('====> leaving monitor for ' , someObject displayString , ' in ' , thisProcess name , ' ...') printCR.
+        someObject isJavaClass ifTrue:[
+            objString := someObject name
+        ] ifFalse:[
+            objString := someObject class name , '@' , someObject identityHash printString.
+        ].
+
+        ('====> leaving monitor for ' , objString , ' in ' , thisProcess name , ' ...') printCR.
     ].
     mon exit.
     MonitorTrace ifTrue:[
-	('====> left it in ' , thisProcess name , ' ...') printCR.
+        ('====> left it in ' , thisProcess name , ' ...') printCR.
     ].
 
     lastMon := (self enteredMonitorsOfProcess:thisProcess) removeLast.
     lastMon ~~ someObject ifTrue:[
-	self halt:'oops - monitor enter/exit nesting wrong'
+        self halt:'oops - monitor enter/exit nesting wrong'
     ].
 
     wasBlocked := OperatingSystem blockInterrupts.
     mon count == 0 ifTrue:[
-	LeftMonitorObject := someObject
+        LeftMonitorObject := someObject
     ].
     wasBlocked ifFalse:[ OperatingSystem unblockInterrupts ]
 
-    "Created: / 8.1.1999 / 14:23:19 / cg"
-    "Modified: / 8.1.1999 / 18:47:08 / cg"
+    "Created: / 08-01-1999 / 14:23:19 / cg"
+    "Modified: / 08-01-1999 / 18:47:08 / cg"
+    "Modified: / 10-08-2011 / 20:20:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 _MULTINEW2: classRef _: dim1 
--- a/src/TestletTestCaseProxy.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/TestletTestCaseProxy.st	Wed Aug 10 22:22:53 2011 +0000
@@ -259,11 +259,11 @@
     type == 1 ifTrue:[
         ^Filename newTemporaryDirectory.  
     ] ifFalse:[type == 2 ifTrue:[
-        ^self error:'DIR_SRC not yet implemented'
+        ^JavaTestsResource classpathForMauve anyOne asFilename directory / 'src'
     ] ifFalse:[type == 3 ifTrue:[
         ^self error:'DIR_RES not yet implemented'
     ] ifFalse:[type == 4 ifTrue:[
-        ^self error:'DIR_BLD not yet implemented'
+        ^JavaTestsResource classpathForMauve anyOne asFilename
     ] ifFalse:[
         ^self error:'Unknown type code'
     ]]]].
--- a/src/extensions.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/extensions.st	Wed Aug 10 22:22:53 2011 +0000
@@ -736,6 +736,15 @@
 
     "Created: / 06-02-2011 / 15:16:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
+!SignedIntegerArray class methodsFor:'accessing-java'!
+
+javaArrayClass
+
+    ^JavaArray javaArrayClassFor: SignedIntegerArray
+
+    "Created: / 11-06-2011 / 23:42:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 22:47:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
 !SignedIntegerArray class methodsFor:'accessing'!
 
 javaComponentClass
@@ -834,6 +843,15 @@
 ! !
 !WordArray class methodsFor:'accessing-java'!
 
+javaArrayClass
+
+    ^JavaArray javaArrayClassFor: WordArray
+
+    "Created: / 11-06-2011 / 23:42:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-08-2011 / 22:46:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+!WordArray class methodsFor:'accessing-java'!
+
 javaComponentClass
 
     ^Short
--- a/src/stx_libjava.st	Wed Aug 10 19:12:21 2011 +0000
+++ b/src/stx_libjava.st	Wed Aug 10 22:22:53 2011 +0000
@@ -493,7 +493,7 @@
     "Return a SVN revision number of myself.
      This number is updated after a commit"
 
-    ^ "$SVN-Revision:"'1245'"$"
+    ^ "$SVN-Revision:"'1248'"$"
 ! !
 
 !stx_libjava class methodsFor:'file generation'!