JavaMethod.st
author cg
Tue, 29 Dec 1998 16:50:12 +0000
changeset 506 81d3ef12bdc9
parent 504 e22c50026869
child 522 e7323b33dbe2
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1997 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


CompiledCode variableSubclass:#JavaMethod
	instanceVariableNames:'accessFlags selector javaClass signature lineNumberTable
		localVariableTable'
	classVariableNames:'AbstractMethodInvokationSignal 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 A_HASHANDLER'
	poolDictionaries:''
	category:'Java-Classes'
!

!JavaMethod class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

! !

!JavaMethod class methodsFor:'initialization'!

initialize
    AbstractMethodInvokationSignal isNil ifTrue:[
	AbstractMethodInvokationSignal := ExecutionErrorSignal newSignalMayProceed:true.
	AbstractMethodInvokationSignal nameClass:self message:#abstractMethodInvokationSignal.
	AbstractMethodInvokationSignal notifierString:'attempt to execute abstract method'.
    ].

    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.
    A_HASHANDLER   := 16r1000000.

    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.
     JavaMethodWithHandler initialize.
     ForceByteCodeDisplay := true.
     ForceByteCodeDisplay := false.
    "

    "Modified: / 16.10.1998 / 01:29:48 / cg"
! !

!JavaMethod class methodsFor:'instance creation'!

fromMethod:aJavaMethod
    "create a new javaMethod, copying values from another javaMethod"

    ^ self new fromMethod:aJavaMethod

    "Created: / 16.10.1998 / 01:25:12 / cg"
!

new
    "create a new javaMethod.
     Redefined, since constants are NOT stored in a literalArray,
     but my classes constantTable instead."

    ^ self basicNew:0.

    "Created: / 16.10.1998 / 01:13:02 / cg"
! !

!JavaMethod class methodsFor:'Signal constants'!

abstractMethodInvokationSignal
    "return the signal raised when an abstract method is invoked"

    ^ AbstractMethodInvokationSignal

    "Created: / 27.1.1998 / 21:50:05 / cg"
! !

!JavaMethod class methodsFor:'constants'!

A_HASHANDLER
    ^ A_HASHANDLER

    "Created: / 26.11.1998 / 22:23:12 / cg"
!

A_NATIVE
    ^ JavaClass A_NATIVE

    "Created: / 16.5.1998 / 01:18:24 / cg"
!

A_PUBLIC
    ^ JavaClass A_PUBLIC

    "Created: / 16.5.1998 / 00:01:10 / cg"
!

A_STATIC
    ^ JavaClass A_STATIC

    "Created: / 16.5.1998 / 00:01:17 / cg"
! !

!JavaMethod class methodsFor:'misc'!

forceByteCodeDisplay
    ^ ForceByteCodeDisplay

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

forceByteCodeDisplay:aBoolean
    ForceByteCodeDisplay := aBoolean

    "
     self forceByteCodeDisplay:true
     self forceByteCodeDisplay:false
    "

    "Created: / 4.2.1998 / 00:22:54 / 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"
!

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.
	]
    ].
    ^ sig

    "
     self argSignatureFromArgTypeArray:
	(Array 
	    with:(JavaVM javaClassObjectForClass:(Java at:'com.sun.java.swing.JComponent')))
    "

    "Modified: / 13.2.1998 / 14:57:58 / 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 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 , '[]'
    ].

    ^ typeSym

    "Created: / 18.3.1997 / 11:07:56 / cg"
    "Modified: / 18.7.1998 / 22:57:06 / 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"

    |spec|

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

    "Created: / 18.3.1997 / 11:12:19 / cg"
    "Modified: / 7.4.1998 / 22:28:27 / 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'!

accessFlags
    "java calls this the modifiers"

    ^ accessFlags

    "Created: / 9.4.1998 / 17:49:44 / cg"
!

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
    ^ nil

    "Created: / 16.10.1998 / 01:50:51 / cg"
!

exceptionTable
    ^ nil

    "Created: / 16.10.1998 / 01:51:04 / cg"
!

hasLineNumberInformation
    ^ lineNumberTable notNil

    "Created: 16.4.1996 / 12:34:04 / cg"
    "Modified: 16.4.1996 / 12:49:06 / 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"
!

numVars
    |n|

    "/ a Java-stackframe includes the args in the locals
    n := self numLocals - self numArgs.
    ^ n

    "Modified: / 13.1.1998 / 17:34:37 / cg"
!

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
    ^ self class typeFromSignature:signature in:nil.

    "Modified: / 16.10.1998 / 00:17:43 / cg"
!

returnTypeClass
    |cls returnType|

    (returnType := self returnType) isNil ifTrue:[
	self halt.
    ].
    cls := Java at:returnType.
    cls notNil ifTrue:[^ cls].

    returnType == #void ifTrue:[
	^ nil
    ].
    returnType == #double ifTrue:[
	'warning: no returnTypeClass for double' printCR.
"/        self halt:'no returnTypeClass for double'.
	^ nil
    ].
    returnType == #float ifTrue:[
	'warning: no returnTypeClass for float' printCR.
"/        self halt:'no returnTypeClass for float'.
	^ nil
    ].
    returnType == #long ifTrue:[
	'warning: no returnTypeClass for long' printCR.
"/        self halt:'no returnTypeClass for long'.
	^ nil
    ].
    returnType == #int ifTrue:[
	'warning: no returnTypeClass for int' printCR.
"/        self halt:'no returnTypeClass for int'.
	^ nil
    ].
    returnType == #boolean ifTrue:[
	'warning: no returnTypeClass for boolean' printCR.
"/        self halt:'no returnTypeClass for boolean'.
	^ nil
    ].
    self halt.
    ^ nil

    "Created: / 13.2.1998 / 15:08:26 / cg"
    "Modified: / 16.10.1998 / 00:16:07 / cg"
!

returnsDouble
    ^ self returnType == #double

    "Modified: / 16.10.1998 / 00:18:24 / cg"
!

returnsLong
    ^ self returnType == #long

    "Modified: / 16.10.1998 / 00:18:41 / cg"
!

returnsVoid
    ^ self returnType == #void

    "Modified: / 16.10.1998 / 00:18:53 / cg"
!

selector
    "/ could theoretically be extracted from my classes
    "/ methodDictionary via:
    "/  ^ javaClass methodDictionary keyAtValue:self ifAbsent:nil.

    ^ selector

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

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
    self hasCode ifTrue:[
	MessageTracer unwrapMethod:self
    ].
    accessFlags := (accessFlags bitClear:A_BREAKPOINT).

    "Modified: / 13.11.1998 / 23:31:00 / cg"
!

isCounting
    ^ false.

    "Created: / 12.1.1998 / 20:02:23 / cg"
!

isCountingMemoryUsage
    ^ false.

    "Created: / 12.1.1998 / 20:03:22 / cg"
!

setBreakPoint
    self hasCode ifTrue:[
	MessageTracer trapMethod:self
    ].
    accessFlags := (accessFlags bitOr:A_BREAKPOINT).

    "Modified: / 13.11.1998 / 23:30:45 / cg"
!

setTraceFullPoint
    "not yet implemented"

    "Modified: / 9.1.1998 / 23:01:17 / cg"
    "Created: / 12.1.1998 / 20:04:45 / cg"
!

setTracePoint
    "not yet implemented"

    "Modified: / 9.1.1998 / 23:01:17 / cg"
    "Created: / 12.1.1998 / 20:04:02 / cg"
!

setTraceSenderPoint
    "not yet implemented"

    "Modified: / 9.1.1998 / 23:01:17 / cg"
    "Created: / 12.1.1998 / 20:04:35 / cg"
!

startCounting
    "not yet implemented"

    "Modified: / 9.1.1998 / 23:01:17 / cg"
    "Created: / 12.1.1998 / 20:05:01 / cg"
!

startCountingMemoryUsage
    "not yet implemented"

    "Modified: / 9.1.1998 / 23:01:17 / cg"
    "Created: / 12.1.1998 / 20:05:04 / cg"
!

startTiming
    "not yet implemented"

    "Modified: / 9.1.1998 / 23:01:17 / cg"
    "Created: / 12.1.1998 / 20:04:57 / cg"
! !

!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 |
		ex signal == Object haltSignal ifTrue:[ex reject].
		ex signal == MessageTracer breakpointSignal ifTrue:[ex reject].
		ex signal == Signal noHandlerSignal ifTrue:[ex reject].

		aStream nextPutAll:'error while decompiling:'.
		aStream cr; cr; spaces:4.
		aStream nextPutAll:ex errorString.
		aStream cr.
		aStream nextPutAll:ex suspendedContext printString.
		aStream cr.
		aStream nextPutAll:ex suspendedContext sender printString.
		aStream cr.
		aStream nextPutAll:ex suspendedContext sender sender printString.
		aStream cr.
		aStream nextPutAll:ex suspendedContext sender sender sender printString.
		aStream cr.
		aStream nextPutAll:ex suspendedContext sender sender sender sender printString.
		aStream cr.
		aStream nextPutAll:ex suspendedContext sender sender sender sender sender printString.
		aStream cr.

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

    "Created: / 30.7.1997 / 16:28:09 / cg"
    "Modified: / 20.10.1998 / 10:01:08 / cg"
!

decompiler
    ^ JavaDecompiler

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

isMethod
    "return true, if the receiver is some kind of method;
     true returned here - the method is redefined from Object."

    ^ true

    "Created: / 13.11.1998 / 23:57:40 / cg"
!

originalMethod
    ^ self

    "Created: / 13.1.1998 / 15:03:05 / cg"
! !

!JavaMethod methodsFor:'error handling'!

invalidByteCode
    self isAbstract ifTrue:[
	^ AbstractMethodInvokationSignal raise.
    ].
    ((self class numArgsFromSignature:signature) > 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"
!

invalidMethodRef
    self halt.
    ^ nil.

    "Modified: / 27.1.1998 / 21:50:19 / cg"
    "Created: / 16.10.1998 / 11:27:21 / cg"
! !

!JavaMethod methodsFor:'methodref interchangability'!

method
    ^ self
! !

!JavaMethod methodsFor:'misc'!

fromMethod:aJavaMethod
    "copy values from another javaMethod"

    flags := aJavaMethod flags.
    byteCode := aJavaMethod byteCode.
    accessFlags := aJavaMethod accessFlags.
    selector := aJavaMethod selector.
    javaClass := aJavaMethod javaClass.
    signature := aJavaMethod signature.
    lineNumberTable := aJavaMethod lineNumberTable.
    localVariableTable := aJavaMethod localVariableTable.

    "Modified: / 16.10.1998 / 01:27:19 / 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 displayString , '::' , self signatureName , ')'

    "Modified: / 5.11.1998 / 19:49:07 / 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 lastName).
    ].
    ^ self signatureNameText

    "Modified: / 5.11.1998 / 19:44:55 / 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
    ^ nil

    "Created: / 16.10.1998 / 02:06:11 / cg"
!

hasResource
    ^ false
!

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

isBreakpointed
    ^ (accessFlags bitAnd:A_BREAKPOINT) ~~ 0

    "Modified: / 11.1.1998 / 13:28:43 / cg"
!

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

isJavaMethod
    ^ true

    "Created: / 10.11.1998 / 18:24:51 / 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
!

isTraced
    ^ false

    "Modified: / 11.1.1998 / 13:28:43 / cg"
    "Created: / 11.1.1998 / 13:38:11 / cg"
!

isUnloaded
    ^ false
!

isWrapped
    ^ self isBreakpointed

    "Modified: / 11.1.1998 / 13:28:43 / cg"
    "Created: / 11.1.1998 / 13:38:04 / cg"
!

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: / 14.1.1998 / 13:30:54 / cg"
!

package
    ^ 'none'

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

quickLineNumberForPC:pc
    |last|

    lineNumberTable 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
    ].
    ^ nil

    "Modified: / 14.1.1998 / 13:30:54 / cg"
    "Created: / 10.11.1998 / 14:18:22 / cg"
!

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

    |sel|

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

    "Modified: / 16.10.1998 / 13:42:10 / cg"
! !

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

_aaload:arr _:index
    "this is only invoked, if aaload encounters either a bad index
     or an unknown array-class."

    |i|

    i := index + 1.
    (i between:1 and:arr size) ifFalse:[
	JavaVM throwArrayIndexOutOfBoundsException:index
    ].

    'Java: warning bad array in aaload' errorPrintCR.
    ^ arr at:i

    "Modified: / 14.1.1998 / 23:19:59 / cg"
!

_aastore:arr _:index _:num
    "this is only invoked, if aastore encounters either a bad index,
     or an unknown array-class."

    |i|

    i := index + 1.
    (i between:1 and:arr size) ifFalse:[
	JavaVM throwArrayIndexOutOfBoundsException:index
    ].

    'Java: warning bad array in aastore' errorPrintCR.
    arr at:i put:num

    "Modified: / 14.1.1998 / 23:19:42 / cg"
    "Created: / 14.1.1998 / 23:22:01 / cg"
!

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

_caload:arr _:index
    "this is only invoked, if caload encounters either a bad index
     or a non-string-receiver."

    |i|

    i := index + 1.
    (i between:1 and:arr size) ifFalse:[
	JavaVM throwArrayIndexOutOfBoundsException:index
    ].

    ^ arr at:i

    "Modified: / 14.1.1998 / 23:19:59 / cg"
    "Created: / 9.4.1998 / 17:51:42 / cg"
!

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

    aClassOrInterface isBehavior ifTrue:[
	aClassOrInterface == ByteArray ifTrue:[
	    ^ anObject class == aClassOrInterface
	].

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

	anObject isArray ifTrue:[
	    ^ true
	].
	self halt.
	^ false.
    ].
    (aClassOrInterface isMemberOf:JavaBuiltInClassPointerRef) ifTrue:[
	aClassOrInterface arrayClass == anObject class ifTrue:[
	    ^ true
	].
    ].

    (anObject isMemberOf:Array) ifTrue:[
	anObject size == 0 ifTrue:[
	    ^ true
	].
	(self _checkCast:(anObject at:1) class:(aClassOrInterface deref)) ifTrue:[
	    ^ true
	].
	self halt.
	^ false
    ].
    self halt.
    ^ false.

    "Created: / 4.1.1998 / 16:44:59 / cg"
    "Modified: / 10.11.1998 / 01:51:01 / cg"
!

_d2l:op1
    |v|

    v := op1 asInteger.
    v > 16r7FFFFFFFFFFFFFFF ifTrue:[
	self halt.
	v := 16r7FFFFFFFFFFFFFFF
    ] ifFalse:[
	v < 16r8000000000000000 negated ifTrue:[
	    self halt.
	    v := 16r8000000000000000 negated
	]
    ].
    ^ v

    "Created: / 7.1.1998 / 00:23:28 / cg"
    "Modified: / 17.10.1998 / 21:55:49 / 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"
!

_iaload:arr _:index
    "this is only invoked, if iaload encounters either a bad index
     or an unknown array-class."

    |i|

    i := index + 1.
    (i between:1 and:arr size) ifFalse:[
	JavaVM throwArrayIndexOutOfBoundsException:index
    ].

    'Java: warning bad array in iaload' errorPrintCR.
    ^ (arr at:i) asInteger

    "Modified: / 14.1.1998 / 23:19:42 / cg"
!

_iastore:arr _:index _:num
    "this is only invoked, if iastore encounters either a bad index,
     bad number to store, or an unknown array-class."

    |i|

    i := index + 1.
    (i between:1 and:arr size) ifFalse:[
	JavaVM throwArrayIndexOutOfBoundsException:index
    ].

    'Java: warning bad array in iastore' errorPrintCR.
    arr at:i put:num

    "Modified: / 14.1.1998 / 23:19:42 / cg"
    "Created: / 14.1.1998 / 23:21:38 / cg"
!

_instanceof:anObject _:aClassOrInterface
    "trampouline for unhandled cases ..."

"/    aClassOrInterface isInterface ifTrue:[
"/        (anObject class hasInterface:aClassOrInterface) ifTrue:[
"/(aClassOrInterface name includesString:'LightweightPeer') ifTrue:[self halt].
"/            ^ 1
"/        ].
"/    ].
"/ (aClassOrInterface name includesString:'LightweightPeer') ifTrue:[self halt].
    ^ 0.

    "Created: / 13.2.1998 / 17:42:38 / cg"
    "Modified: / 13.2.1998 / 18:03:03 / cg"
!

_l2d:op1
    ^ op1 asFloat

    "Created: / 7.1.1998 / 00:23:28 / cg"
    "Modified: / 13.1.1998 / 14:31:59 / 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 quo: op2.
    ^ quo

    "Created: / 7.1.1998 / 00:17:23 / cg"
    "Modified: / 14.1.1998 / 13:38:38 / cg"
!

_lmul:op1 _:op2
    |prod o1 o2 sign|

"/ self halt.
    "/ ST's largeIntegers compute a correct result;
    "/ but here, we want the overflow to flow into the
    "/ sign bit ... (sigh)

    sign := 1.
    (o1 := op1) < 0 ifTrue:[
	sign := -1.
	o1 := o1 negated.
    ].
    (o2 := op2) < 0 ifTrue:[
	sign := sign negated.
	o2 := o2 negated.
    ].

    prod := (o1 * o2) bitAnd:16rFFFFFFFFFFFFFFFF.
    (prod bitAnd:16r8000000000000000) ~~ 0 ifTrue:[
    ].
    sign == -1 ifTrue:[
	prod := prod negated
    ].
    ^ prod

    "Created: / 7.1.1998 / 00:17:34 / cg"
    "Modified: / 17.10.1998 / 21:56:52 / 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.
    ].
    rslt := (op1 bitShift:op2) bitAnd:16rFFFFFFFFFFFFFFFF.
    ^ rslt

    "Created: / 7.1.1998 / 16:49:47 / cg"
    "Modified: / 11.11.1998 / 01:54:47 / 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"
!

_monenter:anObject
    ^ JavaVM monitorEnter:anObject.
!

_monexit:anObject
    ^ JavaVM monitorExit:anObject.
!

_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|

    typeRef == Array ifTrue:[
	self halt.
    ].

    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: / 10.11.1998 / 02:09:35 / 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"
!

divisionByZero
    JavaVM 
	throwExceptionClassName:'java.lang.ArithmeticException'
	withMessage:'/ by zero'

    "Created: / 15.1.1998 / 02:27:23 / cg"
!

enterSynchronized

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

monitorEnter:someObject
    ^ JavaVM monitorEnter:someObject

    "Modified: / 2.1.1998 / 23:45:36 / cg"
    "Created: / 14.1.1998 / 20:58:43 / cg"
!

monitorExit:someObject
    ^ JavaVM monitorExit:someObject

    "Created: / 14.1.1998 / 20:58:48 / cg"
!

nativeMethodInvokation
    |nm sel|

    nm := selector copyWithoutLast:signature size.
    sel := ('_' , javaClass lastName , '_' , nm , ':') asSymbol.
"/    (JavaVM respondsTo:sel) ifTrue:[
	^ JavaVM 
	    perform:sel
	    with:thisContext sender.
"/    ].
"/
"/    self error:('unimplemented nativeMethod: ' , javaClass name , ' ' , self name).
    ^ nil

    "Created: / 1.1.1998 / 15:16:14 / cg"
    "Modified: / 23.12.1998 / 18:57:08 / 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.83 1998/12/29 16:50:12 cg Exp $'
! !
JavaMethod initialize!