JavaMethod.st
changeset 749 e898eaeff091
parent 748 da0840b7798c
child 750 d594c0664435
--- a/JavaMethod.st	Thu Sep 23 13:52:13 2010 +0000
+++ b/JavaMethod.st	Fri Aug 19 08:58:19 2011 +0000
@@ -1,6 +1,10 @@
 "
- COPYRIGHT (c) 1997 by eXept Software AG
-	      All Rights Reserved
+ COPYRIGHT (c) 1996-2011 by Claus Gittinger
+ COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
+                            SWING Research Group, Czech Technical University in Prague
+
+ Parts of the code written by Claus Gittinger are under following
+ license:
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -8,12 +12,38 @@
  be provided or otherwise made available to, or used by, any
  other person.  No title to or ownership of the software is
  hereby transferred.
+
+ Parts of the code written at SWING Reasearch Group [1] are MIT licensed:
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+
+ [1] Code written at SWING Research Group contain a signature
+     of one of the above copright owners.
 "
 "{ Package: 'stx:libjava' }"
 
 CompiledCode variableSubclass:#JavaMethod
-	instanceVariableNames:'accessFlags selector javaClass signature lineNumberTable
-		localVariableTable'
+	instanceVariableNames:'accessFlags selector javaClass descriptor signature lookupObject
+		lineNumberTable localVariableTable sourceLineNumber annotations'
 	classVariableNames:'AbstractMethodInvokationSignal SignatureTypeCodes
 		ForceByteCodeDisplay UnresolvedClassSignal A_PUBLIC A_PRIVATE
 		A_PROTECTED A_STATIC A_FINAL A_SYNCHRONIZED A_ABSTRACT A_NATIVE
@@ -27,8 +57,12 @@
 
 copyright
 "
- COPYRIGHT (c) 1997 by eXept Software AG
-	      All Rights Reserved
+ COPYRIGHT (c) 1996-2011 by Claus Gittinger
+ COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
+                            SWING Research Group, Czech Technical University in Prague
+
+ Parts of the code written by Claus Gittinger are under following
+ license:
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -36,8 +70,34 @@
  be provided or otherwise made available to, or used by, any
  other person.  No title to or ownership of the software is
  hereby transferred.
+
+ Parts of the code written at SWING Reasearch Group [1] are MIT licensed:
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+
+ [1] Code written at SWING Research Group contain a signature
+     of one of the above copright owners.
+
 "
-
 ! !
 
 !JavaMethod class methodsFor:'initialization'!
@@ -86,6 +146,7 @@
     SignatureTypeCodes at:$Z put:#boolean.
     SignatureTypeCodes at:$L put:#object.
     SignatureTypeCodes at:$[ put:#array.
+    SignatureTypeCodes at:$T put:#typevar.
 
     ForceByteCodeDisplay := false.
 
@@ -96,7 +157,15 @@
      ForceByteCodeDisplay := false.
     "
 
-    "Modified: / 16.10.1998 / 01:29:48 / cg"
+    "Modified: / 16-10-1998 / 01:29:48 / cg"
+    "Modified: / 13-08-2011 / 01:02:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+reinitialize
+
+    self flags:(self flags bitOr:Behavior flagJavaMethod).
+
+    "Created: / 14-12-2010 / 20:58:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaMethod class methodsFor:'instance creation'!
@@ -180,6 +249,33 @@
     "
 
     "Created: / 4.2.1998 / 00:22:54 / cg"
+!
+
+makeJavaMethod
+
+    self flags:((self flags 
+                 bitOr:Behavior flagJavaMethod)
+                 bitClear:Behavior flagMetaMethod)
+
+    "
+        JavaMethod makeJavaMethod
+        JavaMethod makeMetaMethod
+    "
+
+    "Created: / 23-02-2011 / 12:56:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+makeMetaMethod
+
+    self flags:((self flags 
+                 bitOr:Behavior flagMetaMethod)
+                 bitClear:Behavior flagJavaMethod)
+     "
+        JavaMethod makeJavaMethod
+        JavaMethod makeMetaMethod
+    "
+
+    "Created: / 23-02-2011 / 12:56:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaMethod class methodsFor:'signature parsing'!
@@ -220,33 +316,31 @@
     "Modified: / 8.1.1998 / 19:10:20 / cg"
 !
 
-argSignatureFromArgTypeArray:arr
-    |sig|
+argSignatureFromArgTypeArray:arr 
+    | sig |
 
     sig := ''.
-    arr do:[:el |
-	|jCLass|
-
-	jCLass := el.
-	jCLass isJavaClass ifFalse:[
-	    jCLass := JavaVM classForJavaClassObject:el
-	].
-	jCLass isJavaClass ifTrue:[
-	    sig := sig , jCLass typeName.
-	    sig := sig, ';'
-	] ifFalse:[
-	    self halt.
-	]
-    ].
+    arr do:
+            [:el | 
+            | jCLass |
+
+            jCLass := el.
+            jCLass isJavaClass 
+                ifFalse:[ jCLass := JavaVM reflection classForJavaClassObject:el ].
+            jCLass isJavaClass 
+                ifTrue:
+                    [ sig := sig , jCLass typeName.
+                    ]
+                ifFalse:[ self halt. ] ].
     ^ sig
 
     "
      self argSignatureFromArgTypeArray:
-	(Array 
-	    with:(JavaVM javaClassObjectForClass:(Java at:'com.sun.java.swing.JComponent')))
-    "
-
-    "Modified: / 13.2.1998 / 14:57:58 / cg"
+ (Array
+     with:(JavaVM javaClassObjectForClass:(Java at:'com.sun.java.swing.JComponent')))"
+
+    "Modified: / 13-02-1998 / 14:57:58 / cg"
+    "Modified: / 02-03-2011 / 22:49:24 / Marcel Hlopko <hlopik@gmail.com>"
 !
 
 argSpecFromSignature:aSignature withName:name
@@ -334,44 +428,63 @@
 fieldTypeFromStream:s in:aPackage
     "parse a fieldTypeSpec - see java doc"
 
-    |typeChar typeSym elType size className nm|
+    |typeChar typeSym elType size className nm out nangles |
 
     typeChar := s next.
 
     typeSym := SignatureTypeCodes at:typeChar ifAbsent:#unknown.
 
     typeSym == #unknown ifTrue:[
-	^ typeSym
+        ^ typeSym
     ].
-    typeSym == #object ifTrue:[
-	className := s upTo:$;.
-	"/ strip off default
-
-	nm := className.
-	aPackage notNil ifTrue:[
-	    (nm startsWith:aPackage) ifTrue:[
-		nm := nm copyFrom:(aPackage size + 2).
-	    ].
-	].
+    (typeSym == #object or: [typeSym == #typevar]) ifTrue:[
+        "Take care about type variables"
+        out := String new writeStream.
+        [ s peek ~~ $; and:[ s peek ~~ $< ] ] whileTrue:[
+            out nextPut: s next.
+        ].
+        className := out contents.
+        "Eat possible type variables"
+        (s peek == $<) ifTrue:[
+            nangles := 1. s next.
+            [  nangles ~~ 0 ] whileTrue:[
+                s peek == $< ifTrue:[nangles := nangles + 1].
+                s peek == $> ifTrue:[nangles := nangles - 1].
+                s next.
+            ]
+        ].
+        s peek ~~ $; ifTrue:[self error: 'Signature corrupted?'].
+        s next. "/eat ;
+
+
+        typeSym == #typevar ifTrue:[^className].
+        "/ strip off default
+        nm := className.
+        aPackage notNil ifTrue:[
+            (nm startsWith:aPackage) ifTrue:[
+                nm := nm copyFrom:(aPackage size + 2).
+            ].
+        ].
         
-	nm := nm copyReplaceAll:$/ with:$..
-	^ nm
+        nm := nm copyReplaceAll:$/ with:$..
+        ^ nm
     ].
 
     typeSym == #array ifTrue:[
-	s peek isDigit ifTrue:[
-	    size := Integer readFrom:s.
-	    elType := self fieldTypeFromStream:s in:aPackage.
-	    ^ elType , '[' , size printString , ']'
-	].
-	elType := self fieldTypeFromStream:s in:aPackage.
-	^ elType , '[]'
+        s peek isDigit ifTrue:[
+            size := Integer readFrom:s.
+            elType := self fieldTypeFromStream:s in:aPackage.
+            ^ elType , '[' , size printString , ']'
+        ].
+        elType := self fieldTypeFromStream:s in:aPackage.
+        ^ elType , '[]'
     ].
 
     ^ typeSym
 
-    "Created: / 18.3.1997 / 11:07:56 / cg"
-    "Modified: / 18.7.1998 / 22:57:06 / cg"
+    "Created: / 18-03-1997 / 11:07:56 / cg"
+    "Modified: / 18-07-1998 / 22:57:06 / cg"
+    "Modified: / 13-08-2011 / 01:05:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 numArgsFromSignature:aSignature
@@ -380,7 +493,8 @@
     |s|
 
     s := aSignature readStream.
-    s next ~~ $( ifTrue:[self halt].
+    (aSignature includes: $() ifFalse:[self error:'Invalid signature'].
+    [s next ~~ $(] whileTrue.
 
     ^ self numArgsFromStream:s.
 
@@ -388,7 +502,10 @@
      JavaMethod numArgsFromSignature:'(LObject;)V'
      JavaMethod numArgsFromSignature:'(BB)S'      
      JavaMethod numArgsFromSignature:'()V'      
+     JavaMethod numArgsFromSignature:'(Ljava/util/ArrayList<*>;)V'
     "
+
+    "Modified (comment): / 13-08-2011 / 00:59:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 numArgsFromStream:s
@@ -708,6 +825,13 @@
     "Modified: / 8.1.1998 / 19:09:31 / cg"
 ! !
 
+!JavaMethod methodsFor:'* As yet uncategorized *'!
+
+sends:symbol1 or:symbol2
+
+    ^false
+! !
+
 !JavaMethod methodsFor:'accessing'!
 
 accessFlags
@@ -718,8 +842,27 @@
     "Created: / 9.4.1998 / 17:49:44 / cg"
 !
 
+annotations
+    ^ annotations ifNil:[JavaMethodAnnotationContainer empty].
+
+    "Modified: / 03-03-2011 / 23:51:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+annotations:something
+    annotations := something.
+!
+
 argSignature
-    ^ self class argSigArrayFromSignature:signature
+    ^ self class argSigArrayFromSignature:descriptor
+!
+
+asByteCodeMethod
+
+    "JavaMethods are always bytecode methods"
+
+    ^self
+
+    "Created: / 18-07-2011 / 20:48:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 comment
@@ -760,6 +903,23 @@
     "Modified: 30.7.1997 / 16:27:55 / cg"
 !
 
+descriptor
+
+    ^ JavaDescriptor fromString: descriptor
+
+    "Created: / 16-04-1996 / 11:34:29 / cg"
+    "Modified: / 14-08-2011 / 19:32:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ensureHasAnnotations
+    annotations 
+        ifNil:[ annotations := JavaMethodAnnotationContainer for:self ].
+    ^ annotations
+
+    "Created: / 25-02-2011 / 16:02:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 28-02-2011 / 16:33:00 / Marcel Hlopko <hlopik@gmail.com>"
+!
+
 exceptionHandlerTable
     ^ nil
 
@@ -772,6 +932,22 @@
     "Created: / 16.10.1998 / 01:51:04 / cg"
 !
 
+firstInstructionLineNumber
+    ForceByteCodeDisplay == true ifTrue:[ ^ 1].
+    lineNumberTable notNil ifTrue:[ ^ lineNumberTable at:2].
+    ^ 0.
+
+    "Created: / 17-12-2010 / 17:02:46 / Jan Kurs <kurs.jan@post.cz>"
+    "Modified: / 08-01-2011 / 16:30:16 / Jan Kurs <kurs.jan@post.cz>"
+!
+
+getExceptionTable
+
+    ^ nil
+
+    "Created: / 04-02-2011 / 23:07:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 getSourcePosition
     ^ 1
 !
@@ -798,6 +974,18 @@
     "Created: 16.4.1996 / 14:55:44 / cg"
 !
 
+javaExceptionTable
+    ^ nil
+
+    "Created: / 04-06-2011 / 18:16:23 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+!
+
+javaNumArgs
+^ self argSignature size.
+
+    "Created: / 14-03-2011 / 15:50:58 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+!
+
 lineNumber
     lineNumberTable isNil ifTrue:[^ nil].
     ^ lineNumberTable at:2
@@ -807,10 +995,11 @@
 !
 
 lineNumberTable
+"/    lineNumberTable ifNil:[ lineNumberTable := Dictionary new.].
     ^ lineNumberTable
 
-    "Created: 16.4.1996 / 12:34:04 / cg"
-    "Modified: 16.4.1996 / 12:49:06 / cg"
+    "Created: / 16-04-1996 / 12:34:04 / cg"
+    "Modified: / 13-12-2010 / 11:06:40 / Jan Kurs <kurs.jan@post.cz>"
 !
 
 literalsDetect:aBlock ifNone:exceptionBlock
@@ -847,11 +1036,25 @@
     "
 !
 
+mclass
+    ^ self javaClass
+!
+
+mclass: anObject
+
+    javaClass := anObject
+
+    "Created: / 18-10-2010 / 19:01:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 methodArgAndVarNames
-    ^ ((1 to:self numArgs) collect:[:i | 'arg' , i printString])
+    ^ "((1 to:self numArgs) collect:[:i | 'arg' , i printString])"
+      self methodArgNames
       ,
-      ((1 to:self numVars) collect:[:i | 'local' , i printString])
-
+      "((1 to:self numVars) collect:[:i | 'local' , i printString])"
+      self methodVarNames
+
+    "Modified: / 23-11-2010 / 19:32:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 methodArgNames
@@ -859,34 +1062,72 @@
 
     nA := self numArgs.
     localVariableTable notNil ifTrue:[
-	^ (1 to:nA) collect:
-	    [:argIndex | 
-		|slot name|
-		"/ search for an entry with that index (slot),
-		"/ which has is valid at PC 0
-
-		self isStatic ifTrue:[
-		    slot := argIndex
-		] ifFalse:[
-		    slot := argIndex + 1
-		].
-		name := localVariableTable nameForSlot:slot atPC:0.
-		name isNil ifTrue:[
-		    'arg' , argIndex printString
-		] ifFalse:[
-		    name
-		].
-	    ]
+        ^ (1 to:nA) collect:
+            [:argIndex | 
+                |slot name|
+                "/ search for an entry with that index (slot),
+                "/ which has is valid at PC 0
+
+                self isStatic ifTrue:[
+                    slot := argIndex - 1
+                ] ifFalse:[
+                    slot := argIndex "/+ 1
+                ].
+                name := localVariableTable nameForSlot:slot atPC:0.
+                name isNil ifTrue:[
+                    'arg' , argIndex printString
+                ] ifFalse:[
+                    name
+                ].
+            ]
     ].
     ^ (1 to:nA) collect:[:i | 'arg' , i printString]
+
+    "Modified: / 23-11-2010 / 19:47:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+methodVarNames
+    |nV|
+
+    nV := self numVars.
+    localVariableTable notNil ifTrue:[
+        ^ (self numArgs + 1 to: self numArgs + nV) collect:
+            [:argIndex | 
+                |slot name|
+                "/ search for an entry with that index (slot),
+                "/ which has is valid at PC 0
+
+                self isStatic ifTrue:[
+                    slot := argIndex - 1
+                ] ifFalse:[
+                    slot := argIndex"/ + 1
+                ].
+                name := localVariableTable nameForSlot:slot atPC:0.
+                name isNil ifTrue:[
+                    'local' , argIndex printString
+                ] ifFalse:[
+                    name
+                ].
+            ]
+    ].
+    ^ (1 to:nV) collect:[:i | 'local' , i printString]
+
+    "Created: / 23-11-2010 / 19:28:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 name
-    ^ (selector copyWithoutLast:signature size) asSymbol
+    ^ (selector copyWithoutLast:descriptor size) asSymbol
 
     "Created: 16.4.1996 / 11:34:22 / cg"
 !
 
+nameSpaceName
+
+    ^''
+
+    "Created: / 18-10-2010 / 19:10:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 numLocals
     ^super numVars.
 "/    numLocals isNil ifTrue:[^ 0].
@@ -911,15 +1152,22 @@
     "Created: 30.7.1997 / 15:56:18 / cg"
 !
 
+previousVersionCode
+
+    ^nil
+
+    "Created: / 18-10-2010 / 20:15:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 retValSignature
-    ^ self class retValSpecFromSignature:signature in:nil
+    ^ self class retValSpecFromSignature:descriptor in:nil
 
     "Modified: / 8.1.1998 / 19:06:40 / cg"
 !
 
 returnType
     "/ ^ returnType
-    ^ self class typeFromSignature:signature in:nil.
+    ^ self class typeFromSignature:descriptor in:nil.
 
     "Modified: / 16.10.1998 / 00:17:43 / cg"
 !
@@ -983,7 +1231,8 @@
 returnsVoid
     ^ self returnType == #void
 
-    "Modified: / 16.10.1998 / 00:18:53 / cg"
+    "Modified: / 16-10-1998 / 00:18:53 / cg"
+    "Modified: / 22-03-2011 / 12:27:02 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
 !
 
 selector
@@ -997,148 +1246,29 @@
     "Modified: / 16.10.1998 / 13:41:06 / cg"
 !
 
-setAccessFlags:flags
-    accessFlags := flags.
-
-    "Created: 16.4.1996 / 11:34:14 / cg"
-!
-
-setCode:codeBytes maxStack:max_stack maxLocals:max_locals u1:unknown1 u2:unknown2
-"/    javaByteCode := codeBytes.
-    byteCode := codeBytes.
-    "/ numStack := max_stack.
-    "/ numLocals := max_locals.
-    super numberOfVars:max_locals.
-    super stackSize:max_stack.
-
-"/    self displayString printNL.
-"/    '   nStack: ' print. numStack print. 
-"/    ' nLocal: ' print. numLocals print. 
-"/    ' u1: ' print. unknown1 print.
-"/    ' u2: ' print. unknown2 printNL.
-
-    "Modified: 1.8.1997 / 00:08:32 / cg"
-!
-
-setJavaClass:aJavaClass
-    javaClass := aJavaClass
-
-    "Modified: 16.4.1996 / 12:36:27 / cg"
-    "Created: 16.4.1996 / 15:28:15 / cg"
-!
-
-setLineNumberTable:anArrayOfPCtoLineAssociations
-    "since this uses up lots of memory, compress it"
-
-    |allBytes allWords idx|
-
-    allBytes := allWords := true.
-
-    anArrayOfPCtoLineAssociations do:[:assoc |
-	assoc key > 255 ifTrue:[
-	    allBytes := false.
-	    assoc key > 16rFFFF ifTrue:[
-		allWords := false.
-	    ].
-	].
-	assoc value > 255 ifTrue:[
-	    allBytes := false.
-	    assoc value > 16rFFFF ifTrue:[
-		allWords := false
-	    ].
-	].
-    ].
-    allBytes ifTrue:[
-	lineNumberTable := ByteArray new:(anArrayOfPCtoLineAssociations size * 2).
-    ] ifFalse:[
-	allWords ifTrue:[
-	    lineNumberTable := WordArray new:(anArrayOfPCtoLineAssociations size * 2).
-	] ifFalse:[
-	    lineNumberTable := Array new:(anArrayOfPCtoLineAssociations size * 2).
-	]
-    ].
-
-    idx := 1.
-    anArrayOfPCtoLineAssociations do:[:assoc |
-	lineNumberTable at:idx   put:assoc key.
-	lineNumberTable at:idx+1 put:assoc value.
-	idx := idx + 2.
-    ].
-
-    "Created: 16.4.1996 / 12:34:04 / cg"
-    "Modified: 16.4.1996 / 12:49:06 / cg"
-!
-
-setLocalVariableTable:anArray
-     localVariableTable := anArray.
-!
-
-setName:nameString signature:signatureString
-    selector := (nameString , signatureString) asSymbol.
-    self setSignature:signatureString
-!
-
-setSignature:aString
-    |numArgs tooManyArgs returnType|
-
-    signature := aString asSymbol.
-
-    numArgs := self class numArgsFromSignature:aString.
-    (tooManyArgs := (numArgs > self class maxNumberOfArguments)) ifTrue:[
-	numArgs := 0.
-    ].
-    self numberOfArgs:numArgs.
-    returnType := self class typeFromSignature:aString in:nil.
-
-    "/ for the convenience of the VM, also mirror the return type in
-    "/ the flags ...
-
-    returnType == #void ifTrue:[
-	accessFlags := accessFlags bitOr:R_VOID
-    ] ifFalse:[
-	returnType == #long ifTrue:[
-	    accessFlags := accessFlags bitOr:R_LONG
-	] ifFalse:[
-	    returnType == #double ifTrue:[
-		accessFlags := accessFlags bitOr:R_DOUBLE
-	    ]
-	]
-    ].
-    tooManyArgs ifTrue:[
-	^ ArgumentSignal
-	    raiseRequestWith:self
-	    errorString:'too many args in method'
-    ].
-
-    "Created: / 16.4.1996 / 11:34:29 / cg"
-    "Modified: / 16.10.1998 / 00:17:12 / cg"
-!
-
 signature
-    ^ signature 
-
-    "Created: 16.4.1996 / 11:34:29 / cg"
+
+    ^ signature ? descriptor
+
+    "Modified (format): / 14-08-2011 / 19:37:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 source
-    |classSource|
-
-"/    self isNative ifTrue:[
-"/        ^ 'native method'
-"/    ].
-
+    | classSource |
+    "/    self isNative ifTrue:[
+    "/        ^ 'native method'
+    "/    ].
     ForceByteCodeDisplay == true ifTrue:[
-	^ self decompiledBytecode
+        ^ self decompiledBytecode
     ].
-
     lineNumberTable notNil ifTrue:[
-	classSource := javaClass source.
-	classSource notNil ifTrue:[^ classSource].
+        classSource := javaClass source.
+        classSource notNil ifTrue:[ ^ classSource].
     ].
-
     ^ self decompiledSource
 
-    "Modified: / 4.1.1998 / 13:48:35 / cg"
+    "Modified: / 04-01-1998 / 13:48:35 / cg"
+    "Modified: / 13-12-2010 / 11:06:51 / Jan Kurs <kurs.jan@post.cz>"
 !
 
 sourceFilename
@@ -1146,18 +1276,45 @@
 !
 
 sourceLineNumber
-    ForceByteCodeDisplay == true ifTrue:[
-	^ 1
+    "
+    sourceLineNumber ifNil: [
+        sourceLineNumber := (JavaSourceCodeCache new) 
+            findLineForMethod: self
+            inClass:javaClass.
+    ].
+    "
+    sourceLineNumber := 0.
+
+    sourceLineNumber == 0 ifTrue:
+    [
+        "There is something wrong with parsing"
+"/        self halt.
+        self breakPoint: #libjava.
+        sourceLineNumber := self firstInstructionLineNumber -2.
     ].
 
-    lineNumberTable notNil ifTrue:[
-	^ lineNumberTable at:2
-    ].
-
-    ^ 1
-
-    "Created: 30.7.1997 / 15:40:45 / cg"
-    "Modified: 30.7.1997 / 15:46:12 / cg"
+    ^ sourceLineNumber.
+
+    "Created: / 30-07-1997 / 15:40:45 / cg"
+    "Modified: / 13-12-2010 / 23:46:30 / Marcel Hlopko <hlopik@gmail.com>"
+    "Modified: / 08-01-2011 / 16:20:40 / Jan Kurs <kurs.jan@post.cz>"
+    "Modified: / 05-02-2011 / 22:29:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+wrapper
+
+    ^nil
+
+    "Created: / 18-10-2010 / 19:11:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaMethod methodsFor:'compiler interface'!
+
+programmingLanguage
+
+    ^JavaLanguage instance
+
+    "Created: / 26-10-2010 / 23:42:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaMethod methodsFor:'debugging'!
@@ -1271,18 +1428,17 @@
         ^ self
     ].
 
+    "
     JavaDeparser isNil ifTrue:[
         aStream nextPutAll:'// Sorry - no decompiler'.
         ^ self
     ].
+    "
 
 
 "/    self isNative ifFalse:[
 "/        self isAbstract ifFalse:[
-            aStream nextPutAll:'// '; cr.
-            aStream nextPutAll:'// decompiled source'; cr.
-            aStream nextPutAll:'// '; cr.
-            aStream cr.
+            aStream nextPutAll:'// source not available...'; cr.
             SignalSet anySignal handle:[:ex |
                 ex signal == Object haltSignal ifTrue:[ex reject].
                 ex signal == MessageTracer breakpointSignal ifTrue:[ex reject].
@@ -1311,20 +1467,24 @@
                 aStream nextPutAll:ex suspendedContext sender sender sender sender sender sender sender sender printString.
                 aStream cr.
 
-                JavaDecompiler isNil ifTrue:[
+                "
+                JavaByteCodeDisassembler isNil ifTrue:[
                     aStream nextPutAll:'// Sorry - no decompiler'
                 ] ifFalse:[
-                    JavaDecompiler decompile:self to:aStream.
+                    JavaByteCodeDisassembler diassemble:self to:aStream.
                 ].
+                "
                 ex return
             ] do:[
-                aStream nextPutAll:(JavaDeparser decompile:self).
+                "aStream nextPutAll:(JavaDeparser decompile:self)."
+                JavaByteCodeDisassembler diassemble:self to:aStream.                
             ].
 "/        ].
 "/    ].
 
-    "Created: / 30.7.1997 / 16:28:09 / cg"
-    "Modified: / 21.12.1999 / 14:31:54 / cg"
+    "Created: / 30-07-1997 / 16:28:09 / cg"
+    "Modified: / 21-12-1999 / 14:31:54 / cg"
+    "Modified: / 22-03-2011 / 21:34:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 decompiler
@@ -1350,17 +1510,71 @@
 
 !JavaMethod methodsFor:'error handling'!
 
+errorInvalidClassRefAt: index
+
+    "Sent by the VM when an invalid entry in contant pool
+     is encountered - for instance when the VM expects
+     a classref but the entry is not a classref"
+
+    "
+    javaClass constantPool at: index.
+    "
+
+    JavaInvalidRefError new
+        javaClass: javaClass;
+        index: index;
+        raiseRequest
+
+    "Created: / 18-07-2011 / 23:33:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+errorInvalidFieldRefAt: index
+
+    "Sent by the VM when an invalid entry in contant pool
+     is encountered - for instance when the VM expects
+     a classref but the entry is not a classref"
+
+    "
+    javaClass constantPool at: index.
+    "
+
+    JavaInvalidRefError new
+        javaClass: javaClass;
+        index: index;
+        raiseRequest
+
+    "Created: / 18-07-2011 / 23:33:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+errorInvalidMethodRefAt: index
+
+    "Sent by the VM when an invalid entry in contant pool
+     is encountered - for instance when the VM expects
+     a classref but the entry is not a classref"
+
+    "
+    javaClass constantPool at: index.
+    "
+
+    JavaInvalidRefError new
+        javaClass: javaClass;
+        index: index;
+        raiseRequest
+
+    "Created: / 18-07-2011 / 19:59:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 invalidByteCode
     self isAbstract ifTrue:[
-	^ AbstractMethodInvokationSignal raise.
+        ^ AbstractMethodInvokationSignal raise.
     ].
-    ((self class numArgsFromSignature:signature) > self class maxNumberOfArguments) ifTrue:[
-	^ self error:'method cannot be executed - too many args'
+    ((self class numArgsFromSignature:descriptor) > self class maxNumberOfArguments) ifTrue:[
+        ^ self error:'method cannot be executed - too many args'
     ].
     ^ super invalidByteCode
 
-    "Created: / 27.1.1998 / 21:48:01 / cg"
-    "Modified: / 27.1.1998 / 21:50:19 / cg"
+    "Created: / 27-01-1998 / 21:48:01 / cg"
+    "Modified: / 14-08-2011 / 19:29:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 invalidMethodRef
@@ -1375,16 +1589,211 @@
     JavaVM throwClassNotFoundException
 ! !
 
+!JavaMethod methodsFor:'initialization'!
+
+setAccessFlags:flags
+    accessFlags := flags.
+
+    "Created: 16.4.1996 / 11:34:14 / cg"
+!
+
+setCode:codeBytes maxStack:max_stack maxLocals:max_locals u1:unknown1 u2:unknown2
+"/    javaByteCode := codeBytes.
+    byteCode := codeBytes.
+    "/ numStack := max_stack.
+    "/ numLocals := max_locals.
+    super numberOfVars:max_locals.
+    super stackSize:max_stack.
+
+"/    self displayString printNL.
+"/    '   nStack: ' print. numStack print. 
+"/    ' nLocal: ' print. numLocals print. 
+"/    ' u1: ' print. unknown1 print.
+"/    ' u2: ' print. unknown2 printNL.
+
+    "Modified: 1.8.1997 / 00:08:32 / cg"
+!
+
+setDescriptor:aString
+
+    descriptor := aString asSymbol.
+
+    "Created: / 16-04-1996 / 11:34:29 / cg"
+    "Modified: / 16-10-1998 / 00:17:12 / cg"
+    "Modified: / 13-08-2011 / 01:21:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 14-08-2011 / 19:41:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setJavaClass:aJavaClass
+    javaClass := aJavaClass
+
+    "Modified: 16.4.1996 / 12:36:27 / cg"
+    "Created: 16.4.1996 / 15:28:15 / cg"
+!
+
+setLineNumberTable:anArrayOfPCtoLineAssociations
+    "since this uses up lots of memory, compress it"
+
+    |allBytes allWords idx|
+
+    allBytes := allWords := true.
+
+    anArrayOfPCtoLineAssociations do:[:assoc |
+	assoc key > 255 ifTrue:[
+	    allBytes := false.
+	    assoc key > 16rFFFF ifTrue:[
+		allWords := false.
+	    ].
+	].
+	assoc value > 255 ifTrue:[
+	    allBytes := false.
+	    assoc value > 16rFFFF ifTrue:[
+		allWords := false
+	    ].
+	].
+    ].
+    allBytes ifTrue:[
+	lineNumberTable := ByteArray new:(anArrayOfPCtoLineAssociations size * 2).
+    ] ifFalse:[
+	allWords ifTrue:[
+	    lineNumberTable := WordArray new:(anArrayOfPCtoLineAssociations size * 2).
+	] ifFalse:[
+	    lineNumberTable := Array new:(anArrayOfPCtoLineAssociations size * 2).
+	]
+    ].
+
+    idx := 1.
+    anArrayOfPCtoLineAssociations do:[:assoc |
+	lineNumberTable at:idx   put:assoc key.
+	lineNumberTable at:idx+1 put:assoc value.
+	idx := idx + 2.
+    ].
+
+    "Created: 16.4.1996 / 12:34:04 / cg"
+    "Modified: 16.4.1996 / 12:49:06 / cg"
+!
+
+setLocalVariableTable:anArray
+     localVariableTable := anArray.
+!
+
+setName:nameString descriptor:aString
+
+
+    |numArgs tooManyArgs returnType|
+
+    selector := (nameString , aString) asSymbol.
+    self setDescriptor:aString.
+
+     numArgs := self class numArgsFromSignature:aString.
+     (tooManyArgs := (numArgs > self class maxNumberOfArguments)) ifTrue:[
+     numArgs := 0.
+     ].
+     self numberOfArgs:numArgs.
+     returnType := self class typeFromSignature:aString in:nil.
+
+     "/ for the convenience of the VM, also mirror the return type in
+     "/ the flags ...
+
+     returnType == #void ifTrue:[
+     accessFlags := accessFlags bitOr:R_VOID
+     ] ifFalse:[
+     returnType == #long ifTrue:[
+     accessFlags := accessFlags bitOr:R_LONG
+     ] ifFalse:[
+     returnType == #double ifTrue:[
+     accessFlags := accessFlags bitOr:R_DOUBLE
+     ]
+     ]
+     ].
+     tooManyArgs ifTrue:[
+     ^ ArgumentError
+     raiseRequestWith:self
+     errorString:'too many args in method'
+    ].
+
+    "Created: / 14-08-2011 / 19:41:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setSignature:aString
+
+    signature := aString asSymbol.
+
+    "Created: / 16-04-1996 / 11:34:29 / cg"
+    "Modified: / 16-10-1998 / 00:17:12 / cg"
+    "Modified (format): / 14-08-2011 / 19:41:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaMethod methodsFor:'inspecting'!
+
+inspectorExtraAttributes
+    "extra (pseudo instvar) entries to be shown in an inspector."
+
+    ^ Dictionary new
+        declareAllNewFrom:(super inspectorExtraAttributes ? #());
+        "/add:'-code' -> [ String streamContents:[:s | JavaDecompiler decompile: self to: s] ];
+        add:'-code' -> [ String streamContents:[:s | JavaByteCodeDisassembler diassemble: self to: s] ];
+        "/add:'-source' -> [ self source ];
+        yourself
+
+    "Modified: / 22-03-2011 / 21:13:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaMethod methodsFor:'interpretation'!
+
+interpretWithReceiver: receiver 
+
+    ^self 
+        interpretWithReceiver: receiver 
+        arguments: #()
+
+    "Created: / 24-02-2011 / 22:05:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+interpretWithReceiver: receiver arg: a1
+
+    ^self 
+        interpretWithReceiver: receiver 
+        arguments: (Array with: a1)
+
+    "Created: / 24-02-2011 / 22:05:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+interpretWithReceiver: receiver arg: a1 arg: a2
+
+    ^self 
+        interpretWithReceiver: receiver 
+        arguments: (Array with: a1 with: a2)
+
+    "Created: / 24-02-2011 / 22:05:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+interpretWithReceiver: receiver arg: a1 arg: a2 arg: a3
+
+    ^self 
+        interpretWithReceiver: receiver 
+        arguments: (Array with: a1 with: a2 with: a3)
+
+    "Created: / 24-02-2011 / 22:06:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+interpretWithReceiver: receiver arguments:args
+
+    ^ JavaByteCodeInterpreter 
+        interpret:self
+        receiver:receiver
+        arguments:args
+
+    "Modified: / 24-02-2011 / 23:00:42 / Marcel Hlopko <hlopik@gmail.com>"
+    "Created: / 24-02-2011 / 22:04:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaMethod methodsFor:'methodref interchangability'!
 
 homeMethod
     ^ self
 !
 
-mclass
-    ^ self javaClass
-!
-
 method
     ^ self
 !
@@ -1405,11 +1814,14 @@
     accessFlags := aJavaMethod accessFlags.
     selector := aJavaMethod selector.
     javaClass := aJavaMethod javaClass.
-    signature := aJavaMethod signature.
+    descriptor := aJavaMethod instVarNamed:#descriptor.
+    signature := aJavaMethod instVarNamed:#signature.
     lineNumberTable := aJavaMethod lineNumberTable.
     localVariableTable := aJavaMethod localVariableTable.
-
-    "Modified: / 16.10.1998 / 01:27:19 / cg"
+    annotations := aJavaMethod annotations.
+
+    "Modified: / 16-10-1998 / 01:27:19 / cg"
+    "Modified: / 14-08-2011 / 19:30:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 updateClassRefsFrom:oldClass to:newClass
@@ -1441,9 +1853,9 @@
 "/    ].
 
     self name = #'<init>' ifTrue:[
-        ^ self class specTextFromSignature:signature in:javaClass package withName:(javaClass lastName).
+        ^ self class specTextFromSignature:descriptor in:javaClass package withName:(javaClass lastName).
     ].
-    ^ self class specTextFromSignature:signature in:javaClass package withName:(self name)
+    ^ self class specTextFromSignature:descriptor in:javaClass package withName:(self name)
 !
 
 shortDisplayString
@@ -1453,7 +1865,7 @@
 signatureName
     "return a string to be used when browsing"
 
-    ^ self class specFromSignature:signature withName:(self name) in:nil
+    ^ self class specFromSignature:descriptor withName:(self name) in:nil
 
     "Modified: / 8.1.1998 / 19:15:33 / cg"
 !
@@ -1461,7 +1873,7 @@
 signatureNameFor:name withArgsIn:aPackage
     "return a string to be used when decompiling"
 
-    ^ self class specWithArgsFromSignature:signature withName:name in:aPackage
+    ^ self class specWithArgsFromSignature:descriptor withName:name in:aPackage
 
     "Created: 25.3.1997 / 18:49:45 / cg"
 !
@@ -1469,7 +1881,7 @@
 signatureNameIn:aPackage
     "return a string to be used when browsing"
 
-    ^ self class specFromSignature:signature withName:(self name) in:aPackage
+    ^ self class specFromSignature:descriptor withName:(self name) in:aPackage
 
     "Created: 18.3.1997 / 11:11:01 / cg"
 !
@@ -1477,7 +1889,7 @@
 signatureNameText
     "return a text to be used when browsing"
 
-    ^ self class specTextFromSignature:signature withName:(self name)
+    ^ self class specTextFromSignature:descriptor withName:(self name)
 
     "Created: 30.7.1997 / 14:40:29 / cg"
 !
@@ -1485,7 +1897,7 @@
 signatureNameTextFor:name withArgsIn:aPackage
     "return a text to be used when decompiling"
 
-    ^ self class specTextWithArgsFromSignature:signature withName:name in:aPackage
+    ^ self class specTextWithArgsFromSignature:descriptor withName:name in:aPackage
 
     "Created: 25.3.1997 / 18:49:45 / cg"
     "Modified: 1.8.1997 / 10:44:28 / cg"
@@ -1500,7 +1912,7 @@
     myName = '<init>' ifTrue:[
 	myName := javaClass name
     ].
-    ^ self class specFromSignature:signature withName:myName argNames:argNames in:nil
+    ^ self class specFromSignature:descriptor withName:myName argNames:argNames in:nil
 
     "Created: / 8.1.1998 / 21:04:03 / cg"
     "Modified: / 8.1.1998 / 21:22:38 / cg"
@@ -1515,7 +1927,7 @@
     myName = '<init>' ifTrue:[
 	myName := javaClass name
     ].
-    ^ self class specFromSignature:signature withName:myName argNames:argNames in:package
+    ^ self class specFromSignature:descriptor withName:myName argNames:argNames in:package
 
     "Modified: / 8.1.1998 / 21:05:52 / cg"
     "Created: / 8.1.1998 / 21:23:03 / cg"
@@ -1524,15 +1936,38 @@
 signatureNameWithArgsIn:aPackage
     "return a string to be used when browsing"
 
-    ^ self class specWithArgsFromSignature:signature withName:(self name) in:aPackage
-
-    "Created: 20.3.1997 / 12:44:17 / cg"
+    ^ self class specWithArgsFromSignature:descriptor withName:(self name) in:aPackage
+
+    "Created: / 20-03-1997 / 12:44:17 / cg"
+    "Modified: / 14-08-2011 / 19:29:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+signatureNameWithModifiers
+    "return a string to be used when deassembling"
+    
+    | result |
+
+    result := self signatureName.
+    self isFinal ifTrue: [ result := 'final ' , result ].
+    self isStatic ifTrue: [ result := 'static ' , result ].
+    self isSynchronized ifTrue: [ result := 'synchronized ' , result ].
+    self isPrivate 
+        ifTrue: [ result := 'private ' , result ]
+        ifFalse: 
+            [ self isProtected 
+                ifTrue: [ result := 'protected ' , result ]
+                ifFalse: [ self isPublic ifTrue: [ result := 'public ' , result ] ] ].
+    self isAbstract ifTrue: [ result := 'abstract ' , result ].
+    ^ result.
+
+    "Modified: / 08-01-1998 / 19:15:33 / cg"
+    "Created: / 22-03-2011 / 16:25:27 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
 !
 
 signatureNameWithoutReturnType
     "return a string to be used when browsing"
 
-    ^ self class argSpecFromSignature:signature withName:(self name)
+    ^ self class argSpecFromSignature:descriptor withName:(self name)
 
 ! !
 
@@ -1559,6 +1994,13 @@
     "Modified: / 25.9.1999 / 23:07:01 / cg"
 !
 
+hasPrimitiveCode
+
+    ^false
+
+    "Created: / 18-07-2011 / 20:45:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 hasResource
     ^ false
 !
@@ -1633,6 +2075,15 @@
     ^ false
 !
 
+isUnresolved
+    "return true, if the receiver is unresolved;"
+
+
+    ^ false
+
+    "Created: / 06-03-2011 / 22:57:35 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
+!
+
 isWrapped
     ^ self isBreakpointed
 
@@ -1869,6 +2320,13 @@
     "Modified: / 9.11.1999 / 17:06:03 / cg"
 !
 
+shouldBeSkippedInDebuggersWalkBack
+
+    ^false
+
+    "Created: / 30-11-2010 / 15:35:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 who
     "return the class and selector of where I am defined in."
 
@@ -1909,14 +2367,26 @@
     "Created: / 8.1.1998 / 19:17:58 / cg"
 ! !
 
+!JavaMethod methodsFor:'testing'!
+
+isSynthetic
+    ^false
+
+    "Created: / 18-10-2010 / 19:09:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaMethod class methodsFor:'documentation'!
 
 version
-    ^ '$Id$'
+    ^ '$Id: /cvs/stx/stx/libjava/JavaMethod.st,v 1.107 2011/08/18 18:42:48 vrany Exp $'
 !
 
 version_CVS
     ^ '§Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.106 2009/10/09 14:04:17 cg Exp §'
+!
+
+version_SVN
+    ^ '$Id: JavaMethod.st,v 1.107 2011/08/18 18:42:48 vrany Exp $'
 ! !
 
-JavaMethod initialize!
+JavaMethod initialize!
\ No newline at end of file