JavaMethod.st
author cg
Mon, 12 Jan 1998 14:24:47 +0000
changeset 255 2d8b3948a08a
parent 252 04b330744577
child 256 2cbf20ad74b2
permissions -rw-r--r--
*** empty log message ***

'From Smalltalk/X, Version:3.3.1 on 9-jan-1998 at 11:23:07 pm'                  !

CompiledCode subclass:#JavaMethod
	instanceVariableNames:'accessFlags selector javaClass exceptionHandlerTable
		exceptionTable returnType signature lineNumberTable
		localVariableTable isNOOPMethod'
	classVariableNames:'SignatureTypeCodes ForceByteCodeDisplay A_PUBLIC A_PRIVATE
		A_PROTECTED A_STATIC A_FINAL A_SYNCHRONIZED A_ABSTRACT A_NATIVE
		A_BREAKPOINT R_VOID R_LONG R_DOUBLE'
	poolDictionaries:''
	category:'Java-Classes'
!


!JavaMethod class methodsFor:'initialization'!

initialize
    A_PUBLIC       := 16r0001.
    A_PRIVATE      := 16r0002.
    A_PROTECTED    := 16r0004.
    A_STATIC       := 16r0008.
    A_FINAL        := 16r0010.
    A_SYNCHRONIZED := 16r0020.
    A_NATIVE       := 16r0100.
    A_ABSTRACT     := 16r0400.

    R_VOID         := 16r100000.
    R_LONG         := 16r200000.
    R_DOUBLE       := 16r300000.

    A_BREAKPOINT   := 16r0800000.

    self flags:(self flags bitOr:Behavior flagJavaMethod).

    SignatureTypeCodes := IdentityDictionary new.
    SignatureTypeCodes at:$B put:#byte.
    SignatureTypeCodes at:$C put:#char.
    SignatureTypeCodes at:$D put:#double.
    SignatureTypeCodes at:$F put:#float.
    SignatureTypeCodes at:$I put:#int.
    SignatureTypeCodes at:$J put:#long.
    SignatureTypeCodes at:$S put:#'unsigned short'.
    SignatureTypeCodes at:$Z put:#boolean.
    SignatureTypeCodes at:$L put:#object.
    SignatureTypeCodes at:$[ put:#array.

    ForceByteCodeDisplay := false.

    "
     JavaMethod initialize
     ForceByteCodeDisplay := true.
     ForceByteCodeDisplay := false.
    "

    "Modified: / 7.1.1998 / 14:43:46 / cg"
! !

!JavaMethod class methodsFor:'misc'!

forceByteCodeDisplay
    ^ ForceByteCodeDisplay

    "Created: 7.4.1997 / 20:11:39 / cg"
! !

!JavaMethod class methodsFor:'signature parsing'!

argSigArrayFromSignature:aSignature
    "given a signature, return a specArray for the arguments"

    |s|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt].

    ^ self argSigArrayFromStream:s.

    "
     JavaMethod argSigArrayFromSignature:'(LObject;)V'
     JavaMethod argSigArrayFromSignature:'(BB)S'      
     JavaMethod argSigArrayFromSignature:'(LObject;LObject;II)V'      
    "
!

argSigArrayFromStream:s
    "parse an argSpec, return an array of specs - see java doc"

    |argSpec spec|

    spec := #().
    [s atEnd or:[s peek == $)]] whileFalse:[
"/        s peek == Character space ifTrue:[
"/            s next
"/        ] ifFalse:[
            argSpec := self fieldTypeFromStream:s in:nil.
            spec := spec copyWith:argSpec.
"/        ]
    ].
    ^ spec

    "Modified: / 8.1.1998 / 19:10:20 / cg"
!

argSpecFromSignature:aSignature withName:name
    "given a signature, return a spec"

    |s argSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecFromStream:s in:nil.

    s next ~~ $) ifTrue:[self halt. ^ name].

    ^ name , ' (' , argSpec , ')'

    "
     JavaMethod argSpecFromSignature:'(LObject;)V' withName:'foo' 
     JavaMethod argSpecFromSignature:'(BB)S'       withName:'foo' 
    "

    "Modified: / 8.1.1998 / 19:05:36 / cg"
!

argSpecFromStream:s in:aPackage
    "parse an argSpec - see java doc"

    |argSpec spec|

    spec := ''.
    [s atEnd or:[s peek == $)]] whileFalse:[
"/        s peek == Character space ifTrue:[
"/            s next
"/        ] ifFalse:[
	    argSpec := self fieldTypeFromStream:s in:aPackage.
	    spec size ~~ 0 ifTrue:[
		spec := spec , ' '
	    ].
	    spec := spec , argSpec.
"/        ]
    ].
    ^ spec

    "Created: 18.3.1997 / 11:06:44 / cg"
!

argSpecWithArgsFromStream:s in:aPackage
    "parse an argSpec - see java doc"

    ^ self argSpecWithArgsFromStream:s in:aPackage argNames:nil

    "Modified: / 8.1.1998 / 19:21:00 / cg"
!

argSpecWithArgsFromStream:s in:aPackage argNames:argNames
    "parse an argSpec - see java doc"

    |argSpec spec argNr nm|

    argNr := 1.
    spec := ''.
    [s atEnd or:[s peek == $)]] whileFalse:[
        argSpec := self fieldTypeFromStream:s in:aPackage.

        (argNames notNil
        and:[argNames size >= argNr
        and:[(nm := argNames at:argNr) notNil]]) ifFalse:[
            nm := 'arg' , argNr printString.
        ].
        argSpec := argSpec , ' ' , nm.

        spec size ~~ 0 ifTrue:[
            spec := spec , ', '
        ].
        spec := spec , argSpec.

        argNr := argNr + 1.
    ].
    ^ spec

    "Created: / 8.1.1998 / 19:20:36 / cg"
    "Modified: / 8.1.1998 / 21:14:33 / cg"
!

fieldTypeFromStream:s in:aPackage
    "parse a fieldTypeSpec - see java doc"

    |typeChar typeSym elType size className nm|

    typeChar := s next.

    typeSym := SignatureTypeCodes at:typeChar ifAbsent:#unknown.

    typeSym == #unknown ifTrue:[
	^ 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).
	    ].
	].
        
	nm := nm copy replaceAll:$/ 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 , '[]'
    ].

    ^ typeSym

    "Created: 18.3.1997 / 11:07:56 / cg"
    "Modified: 1.8.1997 / 10:57:54 / cg"
!

numArgsFromSignature:aSignature
    "given a signature, return the number of args"

    |s|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt].

    ^ self numArgsFromStream:s.

    "
     JavaMethod numArgsFromSignature:'(LObject;)V'
     JavaMethod numArgsFromSignature:'(BB)S'      
     JavaMethod numArgsFromSignature:'()V'      
    "
!

numArgsFromStream:s
    "parse an argSpec - see java doc"

    |n t|

    n := 0.
    [s atEnd or:[s peek == $)]] whileFalse:[
        t := self fieldTypeFromStream:s in:nil.
        "/
        "/ some args count as 2
        "/
        t == #long ifTrue:[
            n := n + 2.
        ] ifFalse:[
            t == #double ifTrue:[
                n := n + 2
            ] ifFalse:[
                n := n + 1.
            ]
        ]
    ].
    ^ n

    "Modified: / 8.1.1998 / 19:10:25 / cg"
!

retValSpecFromSignature:aSignature in:aPackage
    "given a signature, return a spec"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt].

    argSpec := self argSpecFromStream:s in:aPackage.

    s next ~~ $) ifTrue:[self halt].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ retvalSpec 

    "
     JavaMethod retValSpecFromSignature:'(LObject;)V'
     JavaMethod retValSpecFromSignature:'(BB)S'      
    "

    "Created: 18.3.1997 / 11:11:50 / cg"
!

returnTypeFromSignature:aSignature in:aPackage
    "given a signature, return its type as a string"

    |s c|

    s := aSignature readStream.
    (c := s peek) ~~ $( ifTrue:[
        c == $' ifTrue:[
           [s peek ~= $'] whileTrue:[s next].
           s next.
           ^ (self retvalSpecFromStream:s in:aPackage)
        ].
        ^ (self retvalSpecFromStream:s in:aPackage)
    ].

    s next.
    self argSpecFromStream:s in:aPackage.
    s next ~~ $) ifTrue:[self halt. ^ nil].

    ^ (self retvalSpecFromStream:s in:aPackage)

    "
     JavaMethod returnTypeFromSignature:'(LObject;)V' 
     JavaMethod returnTypeFromSignature:'(BB)S'       
     JavaMethod returnTypeFromSignature:'()J'       
     JavaMethod returnTypeFromSignature:'''first''J'       
    "

    "Created: / 1.8.1997 / 10:54:31 / cg"
    "Modified: / 8.1.1998 / 19:09:06 / cg"
!

returnsVoidFromSignature:aSignature
    "given a signature, return true if it returns void, false if not"

    ^ (self typeFromSignature:aSignature in:nil) = 'void'

    "
     JavaMethod returnsVoidFromSignature:'(LObject;)V' 
     JavaMethod returnsVoidFromSignature:'(BB)S'       
    "

    "Modified: / 8.1.1998 / 19:13:53 / cg"
!

retvalSpecFromStream:s in:aPackage
    "parse a retvalSpec - see java doc"

    s atEnd ifTrue:[self halt. ^ #void].
    s peek == $V ifTrue:[^ #void].
    ^ self fieldTypeFromStream:s in:aPackage

    "Created: 18.3.1997 / 11:12:19 / cg"
!

specComponentsWithArgsFromSignature:aSignature withName:name in:aPackage
    "given a signature, return a spec"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecWithArgsFromStream:s in:aPackage.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ Array with:retvalSpec with:name with:argSpec

    "
     JavaMethod specWithArgsFromSignature:'(LObject;)V' withName:'foo' in:nil    
     JavaMethod specComponentsWithArgsFromSignature:'(LObject;)V' withName:'foo' in:nil  
    "

    "Created: 18.3.1997 / 11:06:22 / cg"
    "Modified: 1.8.1997 / 11:03:50 / cg"
!

specFromSignature:aSignature withName:name argNames:argNames in:aPackage
    "given a signature, return a spec"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecWithArgsFromStream:s in:aPackage argNames:argNames.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ retvalSpec , ' ' , name , ' (' , argSpec , ')'

    "
     JavaMethod specFromSignature:'(LObject;)V' withName:'foo' argNames:#('a') in:nil 
     JavaMethod specFromSignature:'(BB)S'       withName:'foo' argNames:#('a' 'b') in:nil
    "

    "Created: / 18.3.1997 / 11:06:22 / cg"
    "Modified: / 8.1.1998 / 21:14:43 / cg"
!

specFromSignature:aSignature withName:name in:aPackage
    "given a signature, return a spec"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecFromStream:s in:aPackage.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ retvalSpec , ' ' , name , ' (' , argSpec , ')'

    "
     JavaMethod specFromSignature:'(LObject;)V' withName:'foo' in:nil
     JavaMethod specFromSignature:'(BB)S'       withName:'foo' in:nil
    "

    "Created: / 18.3.1997 / 11:06:22 / cg"
    "Modified: / 8.1.1998 / 21:06:32 / cg"
!

specTextFromSignature:aSignature withName:name
    "given a signature, return a spec as boldified text"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecFromStream:s in:nil.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:nil.

    ^ retvalSpec , ' ' , (name asText allBold) , ' (' , argSpec , ')'

    "
     JavaMethod specTextFromSignature:'(LObject;)V' withName:'foo' 
     JavaMethod specTextFromSignature:'(BB)S'       withName:'foo' 
    "

    "Modified: / 8.1.1998 / 19:11:20 / cg"
!

specTextWithArgsFromSignature:aSignature withName:name in:aPackage
    "given a signature, return a spec"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecWithArgsFromStream:s in:aPackage.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ retvalSpec , ' ' , (name asText allBold) , ' (' , argSpec , ')'

    "
     JavaMethod specWithArgsFromSignature:'(LObject;)V' withName:'foo' in:nil 
     JavaMethod specWithArgsFromSignature:'(BB)S'       withName:'foo' in:nil  
    "

    "Modified: 20.3.1997 / 12:50:10 / cg"
    "Created: 1.8.1997 / 10:43:57 / cg"
!

specWithArgsFromSignature:aSignature withName:name in:aPackage
    "given a signature, return a spec"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecWithArgsFromStream:s in:aPackage.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ retvalSpec , ' ' , name , ' (' , argSpec , ')'

    "
     JavaMethod specWithArgsFromSignature:'(LObject;)V' withName:'foo' in:nil 
     JavaMethod specWithArgsFromSignature:'(BB)S'       withName:'foo' in:nil  
    "

    "Created: 18.3.1997 / 11:06:22 / cg"
    "Modified: 20.3.1997 / 12:50:10 / cg"
!

typeFromSignature:aSignature in:package
    "given a signature, return its type as a string"

    |s c|

    s := aSignature readStream.
    (c := s peek) ~~ $( ifTrue:[
        c == $' ifTrue:[
           s next.
           [s peek ~= $'] whileTrue:[s next].
           s next.
           ^ (self retvalSpecFromStream:s in:package)
        ].
        ^ (self retvalSpecFromStream:s in:package)
    ].

    s next.
    self argSpecFromStream:s in:nil.
    s next ~~ $) ifTrue:[self halt. ^ nil].

    ^ (self retvalSpecFromStream:s in:package)

    "
     JavaMethod typeFromSignature:'(LObject;)Ljava/lang/Object'               
     JavaMethod typeFromSignature:'(LObject;)Ljava/lang/Object' in:'java.lang'  
    "

    "Created: / 1.8.1997 / 10:50:38 / cg"
    "Modified: / 8.1.1998 / 19:09:31 / cg"
! !

!JavaMethod methodsFor:'accessing'!

argSignature
    ^ self class argSigArrayFromSignature:signature
!

constantPool
    ^ javaClass constantPool

    "Modified: 16.4.1996 / 12:36:27 / cg"
    "Created: 16.4.1996 / 15:28:50 / cg"
!

containingClass
    ^ javaClass

!

decompiledBytecode
    |s|

    s := '' writeStream.
    JavaDecompiler decompile:self to:s.
    ^ s contents

    "Created: 7.4.1997 / 20:10:37 / cg"
!

decompiledSource
    |s|

    s := '' writeStream.
    self decompileSourceTo:s.
    ^ s contents

    "Modified: 30.7.1997 / 16:27:55 / cg"
!

exceptionHandlerTable
    ^ exceptionHandlerTable

    "Modified: 16.4.1996 / 12:49:06 / cg"
    "Created: 7.2.1997 / 20:04:20 / cg"
!

exceptionTable
    ^ exceptionTable

    "Created: 16.4.1996 / 12:34:04 / cg"
    "Modified: 16.4.1996 / 12:49:06 / cg"
!

hasLineNumberInformation
    ^ lineNumberTable notNil

    "Created: 16.4.1996 / 12:34:04 / cg"
    "Modified: 16.4.1996 / 12:49:06 / cg"
!

isNOOPMethod:aBoolean
    isNOOPMethod := aBoolean

    "Created: 18.3.1997 / 13:31:16 / cg"
!

javaByteCode
"/    ^ javaByteCode
    ^ byteCode

    "Created: 16.4.1996 / 14:55:44 / cg"
    "Modified: 1.8.1997 / 00:08:45 / cg"
!

javaClass
    ^ javaClass

    "Modified: 16.4.1996 / 12:36:27 / cg"
    "Created: 16.4.1996 / 14:55:44 / cg"
!

lineNumber
    lineNumberTable isNil ifTrue:[^ nil].
    ^ lineNumberTable at:2

    "Created: 16.4.1996 / 12:34:04 / cg"
    "Modified: 16.4.1996 / 12:49:06 / cg"
!

lineNumberTable
    ^ lineNumberTable

    "Created: 16.4.1996 / 12:34:04 / cg"
    "Modified: 16.4.1996 / 12:49:06 / cg"
!

localVariableTable
    ^ localVariableTable

    "
     JavaMethod allInstancesDo:[:m| m localVariableTable notNil ifTrue:[self halt]]
    "
!

methodArgAndVarNames
    ^ ((1 to:self numArgs) collect:[:i | 'arg' , i printString])
      ,
      ((1 to:self numVars) collect:[:i | 'local' , i printString])

!

methodArgNames
    |nA|

    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:[:i | 'arg' , i printString]
!

name
    ^ (selector copyWithoutLast:signature size) asSymbol

    "Created: 16.4.1996 / 11:34:22 / cg"
!

numLocals
    ^super numVars.
"/    numLocals isNil ifTrue:[^ 0].
"/    ^ numLocals

    "Modified: / 3.1.1998 / 21:15:38 / cg"
!

numStack
    ^super stackSize.
"/    numStack isNil ifTrue:[^ 0].
"/    ^ numStack
!

numVars
    ^ self numLocals - self numArgs
!

previousVersion
    ^ nil

    "Created: 30.7.1997 / 15:56:18 / cg"
!

retValSignature
    ^ self class retValSpecFromSignature:signature in:nil

    "Modified: / 8.1.1998 / 19:06:40 / cg"
!

returnType
    ^ returnType
!

returnsDouble
    ^ returnType == #double
!

returnsLong
    ^ returnType == #long
!

returnsVoid
    ^ returnType == #void
!

selector
    ^ selector

    "Created: / 7.1.1998 / 14:05:11 / 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"
!

setExceptionHandlerTable:anArray
    exceptionHandlerTable := anArray.

    "Created: 16.4.1996 / 12:34:04 / cg"
!

setExceptionTable:anArray
    exceptionTable := anArray.

    "Created: 16.4.1996 / 12:34:04 / 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
    signature := aString asSymbol.

    self numberOfArgs:(self class numArgsFromSignature:aString).
    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
            ]
        ]
    ].

    "Created: / 16.4.1996 / 11:34:29 / cg"
    "Modified: / 8.1.1998 / 19:13:59 / cg"
!

signature
    ^ signature 

    "Created: 16.4.1996 / 11:34:29 / cg"
!

source
    |classSource|

"/    self isNative ifTrue:[
"/        ^ 'native method'
"/    ].

    ForceByteCodeDisplay == true ifTrue:[
	^ self decompiledBytecode
    ].

    lineNumberTable notNil ifTrue:[
	classSource := javaClass source.
	classSource notNil ifTrue:[^ classSource].
    ].

    ^ self decompiledSource

    "Modified: / 4.1.1998 / 13:48:35 / cg"
!

sourceFilename
    ^ javaClass sourceFile
!

sourceLineNumber
    ForceByteCodeDisplay == true ifTrue:[
	^ 1
    ].

    lineNumberTable notNil ifTrue:[
	^ lineNumberTable at:2
    ].

    ^ 1

    "Created: 30.7.1997 / 15:40:45 / cg"
    "Modified: 30.7.1997 / 15:46:12 / cg"
! !

!JavaMethod methodsFor:'debugging'!

breakPoint
    Debugger enter:thisContext sender withMessage:'breakpoint'

    "Modified: / 9.1.1998 / 23:01:17 / cg"
!

clearBreakPoint
    accessFlags := (accessFlags bitClear:A_BREAKPOINT)
!

setBreakPoint
    accessFlags := (accessFlags bitOr:A_BREAKPOINT)
! !

!JavaMethod methodsFor:'decompiling'!

decompileSourceTo:aStream
"/    self isNative ifFalse:[
"/        self isAbstract ifFalse:[
            aStream nextPutAll:'// '; cr.
            aStream nextPutAll:'// decompiled source'; cr.
            aStream nextPutAll:'// '; cr.
            aStream cr.
            SignalSet anySignal handle:[:ex |
                aStream nextPutAll:'error while decompiling:'.
                aStream cr; cr; spaces:4.
                aStream nextPutAll:ex errorString.

                JavaDecompiler decompile:self to:aStream.
                ex return
            ] do:[
                aStream nextPutAll:(JavaDeparser decompile:self).
            ].
"/        ].
"/    ].

    "Created: / 30.7.1997 / 16:28:09 / cg"
    "Modified: / 8.1.1998 / 23:06:10 / cg"
!

decompiler
    ^ JavaDecompiler

    "Created: 30.7.1997 / 16:36:48 / cg"
! !

!JavaMethod methodsFor:'methodref interchangability'!

method
    ^ self
! !

!JavaMethod methodsFor:'misc'!

checkForNOOPMethod
    |code insn1 insn2 insn3 idx ref mthd|

    isNOOPMethod notNil ifTrue:[^ self].

    code := self javaByteCode.
    code notNil ifTrue:[
	insn1 := code at:1.
	insn1 == 177 "RETURN" ifTrue:[
	    'JAVA [info]: dummy static method: ' print. self displayString printCR.
	    isNOOPMethod := true.
	    ^ self
	].

	insn1 == 42 "ALOAD_0" ifTrue:[
	    insn2 := code at:2.
	    insn2 == 183 "INVOKENONVIRTUAL" ifTrue:[
		insn3 := code at:5.
		insn3 == 177 "RETURN" ifTrue:[
		    idx := code wordAt:3 MSB:true.
		    ref := javaClass constantPool at:idx.
		    mthd := ref method.
		    mthd isNOOPMethod ifTrue:[
			'JAVA [info]: dummy method (calls dummy): ' print. self displayString printCR.
			isNOOPMethod := true.
		    ] ifFalse:[
			isNOOPMethod := false.
		    ].
		    ^ self
		]
	    ].
	].
    ].
    isNOOPMethod := false.
    ^ self

    "Created: 18.3.1997 / 13:31:50 / cg"
    "Modified: 1.8.1997 / 00:09:42 / cg"
!

updateClassRefsFrom:oldClass to:newClass
    javaClass == oldClass ifTrue:[
        "/ invalidate
        byteCode := nil.
    ]

    "Created: / 6.1.1998 / 18:19:48 / cg"
! !

!JavaMethod methodsFor:'printing & storing'!

displayString
    javaClass isNil ifTrue:[
	^ 'JavaMethod(???)'
    ].
    ^ 'JavaMethod(' , javaClass name , '::' , self signatureName , ')'

    "Modified: 7.4.1997 / 15:54:10 / cg"
!

printStringForBrowserWithSelector:dummySelector
"/    self isStatic ifTrue:[
"/        ^ 'static ' , self signatureName
"/    ].
"/    self isBreakpointed ifTrue:[
"/        ^ (LabelAndIcon '!! ' , self signatureName
"/    ].

    self name = #'<init>' ifTrue:[
	^ self class specTextFromSignature:signature withName:(javaClass name).
    ].
    ^ self signatureNameText

    "Modified: 30.7.1997 / 14:40:42 / cg"
!

shortDisplayString
    ^ javaClass name , '::' , self signatureNameWithoutReturnType
!

signatureName
    "return a string to be used when browsing"

    ^ self class specFromSignature:signature withName:(self name) in:nil

    "Modified: / 8.1.1998 / 19:15:33 / cg"
!

signatureNameFor:name withArgsIn:aPackage
    "return a string to be used when decompiling"

    ^ self class specWithArgsFromSignature:signature withName:name in:aPackage

    "Created: 25.3.1997 / 18:49:45 / cg"
!

signatureNameIn:aPackage
    "return a string to be used when browsing"

    ^ self class specFromSignature:signature withName:(self name) in:aPackage

    "Created: 18.3.1997 / 11:11:01 / cg"
!

signatureNameText
    "return a text to be used when browsing"

    ^ self class specTextFromSignature:signature withName:(self name)

    "Created: 30.7.1997 / 14:40:29 / cg"
!

signatureNameTextFor:name withArgsIn:aPackage
    "return a text to be used when decompiling"

    ^ self class specTextWithArgsFromSignature:signature withName:name in:aPackage

    "Created: 25.3.1997 / 18:49:45 / cg"
    "Modified: 1.8.1997 / 10:44:28 / cg"
!

signatureNameWithArgNames:argNames
    "return a string to be used when browsing"

    |myName|

    myName := self name.
    myName = '<init>' ifTrue:[
        myName := javaClass name
    ].
    ^ self class specFromSignature:signature withName:myName argNames:argNames in:nil

    "Created: / 8.1.1998 / 21:04:03 / cg"
    "Modified: / 8.1.1998 / 21:22:38 / cg"
!

signatureNameWithArgNames:argNames in:package
    "return a string to be used when browsing"

    |myName|

    myName := self name.
    myName = '<init>' ifTrue:[
        myName := javaClass name
    ].
    ^ self class specFromSignature:signature withName:myName argNames:argNames in:package

    "Modified: / 8.1.1998 / 21:05:52 / cg"
    "Created: / 8.1.1998 / 21:23:03 / cg"
!

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"
!

signatureNameWithoutReturnType
    "return a string to be used when browsing"

    ^ self class argSpecFromSignature:signature withName:(self name)

! !

!JavaMethod methodsFor:'queries'!

handlerFor:anException at:pc
    exceptionHandlerTable isNil ifTrue:[^ nil].
    exceptionHandlerTable do:[:entry |
	|hpc|

	hpc := entry handlerPCFor:anException at:pc in:self.
	hpc notNil ifTrue:[^ hpc].
    ].

    ^ nil
!

hasResource
    ^ false
!

isAbstract
    ^ (accessFlags bitAnd:A_ABSTRACT) ~~ 0
!

isBreakpointed
    ^ false
!

isFinal
    ^ (accessFlags bitAnd:A_FINAL) ~~ 0
!

isIgnored
    "not really a java attribute;
     added to allow browsing"

    ^ false.

    "Created: 30.7.1997 / 15:34:33 / cg"
!

isNOOPMethod
    isNOOPMethod isNil ifTrue:[
	self checkForNOOPMethod
    ].
    ^ isNOOPMethod

    "Modified: 18.3.1997 / 18:04:02 / cg"
!

isNative
    ^ (accessFlags bitAnd:A_NATIVE) ~~ 0
!

isPrivate
    ^ (accessFlags bitAnd:A_PRIVATE) ~~ 0
!

isProtected
    ^ (accessFlags bitAnd:A_PROTECTED) ~~ 0
!

isPublic
    ^ (accessFlags bitAnd:A_PUBLIC) ~~ 0
!

isStatic
    ^ (accessFlags bitAnd:A_STATIC) ~~ 0
!

isSynchronized
    ^ (accessFlags bitAnd:A_SYNCHRONIZED) ~~ 0
!

isUnloaded
    ^ false
!

lineNumberForPC:pc
    |last num text classSource|

    num := nil.

    ForceByteCodeDisplay == true ifFalse:[

	lineNumberTable notNil ifTrue:[
	    classSource := javaClass source.
	    classSource notNil ifTrue:[
		lineNumberTable pairWiseDo:[:lPc :lNr |
		    lPc >= pc ifTrue:[
			"/ lPc == pc ifTrue:[^ lNr].
			last isNil ifTrue:[^ lNr].
			^ last.
		    ].
		    last := lNr.
		].
		last notNil ifTrue:[        
		    ^ last
		].
		^ lineNumberTable at:2
	    ].
	].
    ].

    "/ decompile and look which line the pc falls into

    ForceByteCodeDisplay == true ifTrue:[
	text := self decompiledBytecode asCollectionOfLines.
    ] ifFalse:[
	text := self decompiledSource asCollectionOfLines.
    ].

    text keysAndValuesDo:[:lineNr :line |
	|nr|

	(line startsWith:'    ') ifFalse:[
	    nr := Integer readFrom:line onError:0.
	    nr >= pc ifTrue:[
		^ lineNr
	    ]
	]
    ].
    ^ num

    "Modified: 12.8.1997 / 01:55:24 / cg"
!

package
    ^ 'none'

    "Created: 5.2.1997 / 11:31:26 / cg"
!

who
    "return the class and selector of where I am defined in."

    |sel|

    javaClass isNil ifTrue:[^ nil].
    sel := javaClass methodDictionary keyAtValue:self ifAbsent:nil.
    sel isNil ifTrue:[^ nil].
    ^ Method::MethodWhoInfo class:javaClass selector:sel.
! !

!JavaMethod methodsFor:'signature parsing'!

XXXspecWithArgsFromSignature:aSignature withName:name in:aPackage
    "given a signature, return a spec with args"

    |s argSpec retvalSpec|

    s := aSignature readStream.
    s next ~~ $( ifTrue:[self halt. ^ name].

    argSpec := self argSpecWithArgsFromStream:s in:aPackage.

    s next ~~ $) ifTrue:[self halt. ^ name].

    retvalSpec := self retvalSpecFromStream:s in:aPackage.

    ^ retvalSpec , ' ' , name , ' (' , argSpec , ')'

    "
     JavaMethod specFromSignature:'(LObject;)V' withName:'foo' 
     JavaMethod specFromSignature:'(BB)S'       withName:'foo' 
    "

    "Created: / 8.1.1998 / 19:17:58 / cg"
! !

!JavaMethod methodsFor:'vm support'!

_arrayLength:arr
    ^ arr size

    "Created: / 5.1.1998 / 02:40:01 / cg"
!

_athrow:aJavaException
    JavaVM throwException:aJavaException.

    "Created: / 4.1.1998 / 14:37:04 / cg"
    "Modified: / 9.1.1998 / 02:26:50 / cg"
!

_checkCast:anObject class:aClassOrInterface
    "trampouline for unhandled cases ..."

    aClassOrInterface isBehavior ifTrue:[
        aClassOrInterface isInterface ifTrue:[
            (anObject class hasInterface:aClassOrInterface) ifTrue:[
                ^ true
            ]
        ].
        ^ false.
    ].
    (aClassOrInterface isMemberOf:JavaClassPointerRef) ifTrue:[
        "/ must be a pointer to an array of that class

        ^ anObject isArray 
    ].
    self halt.
    ^ false.

    "Created: / 4.1.1998 / 16:44:59 / cg"
    "Modified: / 7.1.1998 / 00:01:26 / cg"
!

_ddiv:op1 _:op2
    |quo|

    quo := op1 / op2.
    ^ quo asFloat

    "Modified: / 7.1.1998 / 00:55:35 / cg"
    "Created: / 8.1.1998 / 00:39:23 / cg"
!

_l2d:op1
    ^ op1 asFloat

    "Created: / 7.1.1998 / 00:23:28 / cg"
!

_ladd:op1 _:op2
    |sum|

    sum := (op1 + op2) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ sum

    "Created: / 6.1.1998 / 21:06:34 / cg"
    "Modified: / 9.1.1998 / 03:05:28 / cg"
!

_land:op1 _:op2
    |rslt|

    (op1 < 0 or:[op2 < 0]) ifTrue:[
        self halt.
    ].
    rslt := op1 bitAnd: op2.
    ^ rslt

    "Created: / 7.1.1998 / 16:46:50 / cg"
    "Modified: / 7.1.1998 / 21:21:53 / cg"
!

_ldiv:op1 _:op2
    |quo|

    quo := op1 // op2.
    ^ quo

    "Created: / 7.1.1998 / 00:17:23 / cg"
    "Modified: / 7.1.1998 / 00:55:35 / cg"
!

_lmul:op1 _:op2
    |prod|

    prod := (op1 * op2) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ prod

    "Created: / 7.1.1998 / 00:17:34 / cg"
    "Modified: / 9.1.1998 / 03:05:37 / cg"
!

_lor:op1 _:op2
    |rslt|

    (op1 < 0 or:[op2 < 0]) ifTrue:[
        self halt.
    ].
    rslt := op1 bitOr: op2.
    ^ rslt

    "Created: / 7.1.1998 / 21:21:42 / cg"
!

_lrem:op1 _:op2
    |rem|

    rem := op1 rem: op2.
    ^ rem

    "Modified: / 7.1.1998 / 00:23:11 / cg"
    "Created: / 7.1.1998 / 00:55:26 / cg"
!

_lshl:op1 _:op2
    |rslt|

    op1 < 0 ifTrue:[
        self halt
    ].

    (op1 < 0) ifTrue:[
        self halt.
    ].
    rslt := (op1 bitShift:op2) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ rslt

    "Created: / 7.1.1998 / 16:49:47 / cg"
    "Modified: / 7.1.1998 / 21:22:32 / cg"
!

_lshr:op1 _:op2
    |rslt|

    op1 < 0 ifTrue:[
        self halt
    ].

    (op1 < 0) ifTrue:[
        self halt.
    ].
    rslt := (op1 bitShift:op2 negated) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ rslt

    "Created: / 7.1.1998 / 16:49:29 / cg"
    "Modified: / 7.1.1998 / 21:22:25 / cg"
!

_lsub:op1 _:op2
    |diff|

    diff := (op1 - op2) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ diff

    "Created: / 6.1.1998 / 21:12:35 / cg"
    "Modified: / 9.1.1998 / 03:05:12 / cg"
!

_lushr:op1 _:op2
    |rslt|

    op1 < 0 ifTrue:[
        self halt
    ].

    (op1 < 0) ifTrue:[
        self halt.
    ].
    rslt := (op1 bitShift:op2 negated) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ rslt

    "Created: / 7.1.1998 / 16:49:07 / cg"
    "Modified: / 7.1.1998 / 21:22:17 / cg"
!

_lxor:op1 _:op2
    |rslt|

    (op1 < 0 or:[op2 < 0]) ifTrue:[
        self halt.
    ].
    rslt := op1 bitXor: op2.
    ^ rslt

    "Created: / 7.1.1998 / 16:40:04 / cg"
    "Modified: / 7.1.1998 / 21:22:00 / cg"
!

_monitorEnter:someObject
    ^ JavaVM monitorEnter:someObject

    "Modified: / 2.1.1998 / 23:45:36 / cg"
!

_monitorExit:someObject
    ^ JavaVM monitorExit:someObject

    "Created: / 2.1.1998 / 23:45:44 / cg"
!

_multiNew:typeRef _:dim1 
    |clsRef cls arr elType elSizes|

    clsRef := typeRef asClassPointerRef.
    cls := clsRef arrayClass.
    arr := cls new:dim1.

    ^ arr

    "Modified: / 7.4.1997 / 13:45:19 / cg"
    "Created: / 6.1.1998 / 23:15:38 / cg"
!

_multiNew:typeRef _:dim1 _:dim2
    |clsRef cls arr elType elSizes|

    clsRef := typeRef asClassPointerRef.
    cls := clsRef arrayClass.
    arr := cls new:dim2.

    elType := typeRef deref.

    1 to:dim2 do:[:idx |
        arr at:idx put:(self _multiNew:elType _:dim1)
    ].

    ^ arr

    "Created: / 6.1.1998 / 23:15:47 / cg"
    "Modified: / 6.1.1998 / 23:34:28 / cg"
!

_multiNew:typeRef _:dim1 _:dim2 _:dim3
    |clsRef cls arr elType elSizes|

    clsRef := typeRef asClassPointerRef.
    cls := clsRef arrayClass.
    arr := cls new:dim3.

    elType := typeRef deref.

    1 to:dim3 do:[:idx |
        arr at:idx put:(self _multiNew:elType _:dim1 _:dim2)
    ].

"/ self halt.
    ^ arr

    "Created: / 6.1.1998 / 23:15:53 / cg"
    "Modified: / 6.1.1998 / 23:34:35 / cg"
!

_saload:arr at:index 
    ^ arr at:index+1

    "Created: / 5.1.1998 / 02:44:40 / cg"
!

_sastore:arr at:index put:val
    arr at:index+1 put:val

    "Created: / 5.1.1998 / 02:35:52 / cg"
!

enterSynchronized

    "Created: / 9.1.1998 / 10:53:10 / cg"
!

nativeMethodInvokation
    ^ JavaVM 
	perform:('_' , javaClass name , '_' , self name , ':') asSymbol
	with:thisContext sender.

    "Created: / 1.1.1998 / 15:16:14 / cg"
    "Modified: / 4.1.1998 / 14:23:10 / cg"
!

nullPointerException
    JavaVM throwNullPointerException.

    "Created: / 9.1.1998 / 02:25:02 / cg"
    "Modified: / 9.1.1998 / 02:26:56 / cg"
! !

!JavaMethod class methodsFor:'documentation'!

version
    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.54 1998/01/12 14:24:34 cg Exp $'
! !
JavaMethod initialize!