JavaMethod.st
author cg
Mon, 07 Apr 1997 19:47:22 +0000
changeset 169 269f334e9f34
parent 168 90e39cb3fa04
child 173 10513c48882f
permissions -rw-r--r--
*** empty log message ***

CompiledCode subclass:#JavaMethod
	instanceVariableNames:'javaByteCode numArgs numLocals returnType accessFlags name
		signature exceptionHandlerTable exceptionTable lineNumberTable
		localVariableTable javaClass numStack isNOOPMethod'
	classVariableNames:'SignatureTypeCodes ForceByteCodeDisplay'
	poolDictionaries:''
	category:'Java-Classes'
!


!JavaMethod class methodsFor:'initialization'!

initialize
    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.

    "
     JavaMethod initialize
    "
! !

!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 argSpec retvalSpec|

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

    ^ 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.
            spec := spec copyWith:argSpec.
"/        ]
    ].
    ^ spec


!

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

    |s argSpec retvalSpec|

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

    argSpec := self argSpecFromStream:s.

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

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

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

argSpecFromStream:s
    "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.
            spec size ~~ 0 ifTrue:[
                spec := spec , ' '
            ].
            spec := spec , argSpec.
"/        ]
    ].
    ^ spec


!

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"

    |argSpec spec argNr|

    argNr := 1.
    spec := ''.
    [s atEnd or:[s peek == $)]] whileFalse:[
        argSpec := self fieldTypeFromStream:s in:aPackage.
        spec size ~~ 0 ifTrue:[
            spec := spec , ', '
        ].
        spec := spec , argSpec.
        spec := spec , ' arg' , argNr printString.
        argNr := argNr + 1.
    ].
    ^ spec

    "Created: 20.3.1997 / 12:45:40 / cg"
    "Modified: 20.3.1997 / 12:49:52 / cg"
!

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

    |typeChar typeSym spec elType size className|

    typeChar := s next.

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

    typeSym == #unknown ifTrue:[
        ^ typeSym
    ].
    typeSym == #object ifTrue:[
        className := s upTo:$;.
        "/ strip off default
"/        (className startsWith:'java/lang/') ifTrue:[
"/            ^ className copyFrom:11
"/        ].
        ^ className copy replaceAll:$/ by:$.
    ].
    typeSym == #array ifTrue:[
        s peek isDigit ifTrue:[
            size := Integer readFrom:s.
            elType := self fieldTypeFromStream:s.
            ^ elType , '[' , size printString , ']'
        ].
        elType := self fieldTypeFromStream:s.
        ^ elType , '[]'
    ].
    ^ typeSym
!

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

    |typeChar typeSym spec 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

"/        (className startsWith:'java/lang/') ifTrue:[
"/            ^ className copyFrom:11
"/        ].

        nm := className.
        aPackage notNil ifTrue:[
            (nm startsWith:aPackage) ifTrue:[
                nm := nm copyFrom:(aPackage size + 2).
            ].
        ].
        
        nm := nm copy replaceAll:$/ by:$..
        ^ nm
    ].
    typeSym == #array ifTrue:[
        s peek isDigit ifTrue:[
            size := Integer readFrom:s.
            elType := self fieldTypeFromStream:s.
            ^ elType , '[' , size printString , ']'
        ].
        elType := self fieldTypeFromStream:s.
        ^ elType , '[]'
    ].
    ^ typeSym

    "Created: 18.3.1997 / 11:07:56 / cg"
    "Modified: 18.3.1997 / 11:18:09 / cg"
!

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

    |s argSpec|

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

    ^ self numArgsFromStream:s.

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

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

    |argSpec n t|

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

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

    |s argSpec retvalSpec|

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

    argSpec := self argSpecFromStream:s.

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

    retvalSpec := self retvalSpecFromStream:s.

    ^ retvalSpec 

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

retValSpecFromSignature:aSignature 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 

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

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

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

    |s c argSpec retvalSpec|

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

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

    ^ (self retvalSpecFromStream:s)

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

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

    ^ (self typeFromSignature:aSignature) = 'void'

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

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

    |argSpec spec|

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

!

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

    |argSpec spec|

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

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

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

    |s argSpec retvalSpec|

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

    argSpec := self argSpecFromStream:s.

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

    retvalSpec := self retvalSpecFromStream:s.

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

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

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' 
     JavaMethod specFromSignature:'(BB)S'       withName:'foo' 
    "

    "Created: 18.3.1997 / 11:06:22 / 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
    "given a signature, return its type as a string"

    |s c argSpec retvalSpec|

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

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

    ^ (self retvalSpecFromStream:s)

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

!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 decompileTo:s.
    ^ s contents
!

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

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

javaClass
    ^ javaClass

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

lineNumber
    ^ 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
    localVariableTable notNil ifTrue:[
        ^ (1 to:self numArgs) 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:self numArgs) collect:[:i | 'arg' , i printString]
!

name
    ^ name

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

numArgs
    numArgs isNil ifTrue:[^ 0].
    ^ numArgs
!

numLocals
    numLocals isNil ifTrue:[^ 0].
    ^ numLocals
!

numStack
    numStack isNil ifTrue:[^ 0].
    ^ numStack
!

numVars
    numLocals isNil ifTrue:[^ 0].
    numArgs isNil ifTrue:[^ numLocals].
    ^ numLocals - numArgs
!

numberOfMethodArgs:n
    numArgs := n
!

retValSignature
    ^ self class retValSpecFromSignature:signature

!

returnType
    ^ returnType
!

returnsDouble
    ^ returnType == #double
!

returnsLong
    ^ returnType == #long
!

returnsVoid
    ^ returnType == #void
!

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.
    numStack := max_stack.
    numLocals := max_locals.

"/    self displayString printNL.
"/    '   nStack: ' print. numStack print. 
"/    ' nLocal: ' print. numLocals print. 
"/    ' u1: ' print. unknown1 print.
"/    ' u2: ' print. unknown2 printNL.

!

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:aString
    name := aString asSymbol.

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

setSignature:aString
    signature := aString asSymbol.

    self numberOfMethodArgs:(self class numArgsFromSignature:aString).
    returnType := self class typeFromSignature:aString.

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

signature
    ^ signature 

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

source
    |classSource|

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

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

    ^ self decompiledSource

    "Modified: 7.4.1997 / 20:10:57 / cg"
!

sourceFilename
    ^ javaClass sourceFile
! !

!JavaMethod methodsFor:'decompiling'!

decompileTo:aStream
    JavaDecompiler decompile:self to:aStream.
    self isNative ifFalse:[
        self isAbstract ifFalse:[
            aStream cr; cr.
            aStream nextPutAll:'decompiled source:'; cr; cr.
            SignalSet anySignal handle:[:ex |
                aStream nextPutAll:'error while decompiling:'.
                aStream cr; cr; spaces:4.
                aStream nextPutAll:ex errorString.
                ex return
            ] do:[
                aStream nextPutAll:(JavaDeparser decompile:self).
            ].
        ].
    ].
    ^ true

    "Modified: 20.3.1997 / 14:04:48 / cg"
! !

!JavaMethod methodsFor:'methodref interchangability'!

method
    ^ self
! !

!JavaMethod methodsFor:'misc'!

checkForNOOPMethod
    |insn1 insn2 insn3 idx ref mthd|

    isNOOPMethod notNil ifTrue:[^ self].

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

        insn1 == 42 "ALOAD_0" ifTrue:[
            insn2 := javaByteCode at:2.
            insn2 == 183 "INVOKENONVIRTUAL" ifTrue:[
                insn3 := javaByteCode at:5.
                insn3 == 177 "RETURN" ifTrue:[
                    idx := javaByteCode 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: 18.3.1997 / 18:06:00 / cg"
! !

!JavaMethod methodsFor:'printing & storing'!

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

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

printStringForBrowserWithSelector:selector
"/    self isStatic ifTrue:[
"/        ^ 'static ' , self signatureName
"/    ].
"/    self isBreakpointed ifTrue:[
"/        ^ (LabelAndIcon '!! ' , self signatureName
"/    ].
    name = #'<init>' ifTrue:[
        ^ self class specFromSignature:signature withName:(javaClass name).
    ].
    ^ self signatureName

    "Modified: 7.4.1997 / 17:28:00 / cg"
!

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

signatureName
    "return a string to be used when browsing"

    ^ self class specFromSignature:signature withName:name
!

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:name in:aPackage

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

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

    ^ self class specWithArgsFromSignature:signature withName: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: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:16r0400) ~~ 0
!

isBreakpointed
    ^ false
!

isFinal
    ^ (accessFlags bitAnd:16r0010) ~~ 0
!

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

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

isNative
    ^ (accessFlags bitAnd:16r0100) ~~ 0
!

isPrivate
    ^ (accessFlags bitAnd:16r0002) ~~ 0

!

isProtected
    ^ (accessFlags bitAnd:16r0004) ~~ 0
!

isPublic
    ^ (accessFlags bitAnd:16r0001) ~~ 0

!

isStatic
    ^ (accessFlags bitAnd:16r0008) ~~ 0
!

isSynchronized
    ^ (accessFlags bitAnd:16r0020) ~~ 0
!

isUnloaded
    ^ false
!

lineNumberForPC:pc
    |last num text classSource|

    num := nil.

    ForceByteCodeDisplay 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
    text := self decompiledSource asCollectionOfLines.

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

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

    "Modified: 7.4.1997 / 20:13:21 / cg"
!

package
    ^ 'none'

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

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

    |sel|

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

!JavaMethod methodsFor:'signature parsing'!

specWithArgsFromSignature: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: 20.3.1997 / 12:44:36 / cg"
! !

!JavaMethod class methodsFor:'documentation'!

version
    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.42 1997/04/07 19:47:22 cg Exp $'
! !
JavaMethod initialize!