JavaClass.st
author cg
Thu, 07 Aug 1997 13:19:56 +0000
changeset 203 67af98594672
parent 200 518c67464105
child 204 c2f7436ceaaa
permissions -rw-r--r--
*** empty log message ***

Class subclass:#JavaClass
	instanceVariableNames:'fullName accessFlags constantPool sourceFile binaryFilePath
		fields initialized initValues staticFields hasUnresolvedConstants
		interfaces'
	classVariableNames:'InitialValuePerType'
	poolDictionaries:''
	category:'Java-Classes'
!

!JavaClass class methodsFor:'documentation'!

examples
"
    (Java at:'java.util.Stack') new inspect
    (Java at:'java.util.Vector') new inspect
"
! !

!JavaClass class methodsFor:'initialization'!

initialize
    InitialValuePerType := IdentityDictionary new.
    InitialValuePerType at:$B put:0.
    InitialValuePerType at:$C put:0.
    InitialValuePerType at:$D put:0.0.
    InitialValuePerType at:$F put:0.0 asShortFloat.
    InitialValuePerType at:$I put:0.
    InitialValuePerType at:$J put:0.
    InitialValuePerType at:$S put:0.
    InitialValuePerType at:$Z put:0.
    InitialValuePerType at:$L put:nil.
    InitialValuePerType at:$[ put:nil.

    "
     JavaClass initialize
    "
! !

!JavaClass class methodsFor:'instance creation'!

fullName:aString
    self shouldNotImplement.
    ^ self new flags:0; setFullName:aString

!

fullName:aString numStatic:nStatic
    |meta cls fullName parts s ns|

    "/ check for a JAVA nameSpace to exist
    JAVA isNil ifTrue:[
        Namespace name:'JAVA'
    ].

    "create the metaclass first"

    meta := Metaclass new.
    meta setSuperclass:(self).
    meta instSize:(JavaClass instSize + nStatic).
"/    meta setName:(aString , 'class') asSymbol.
"/    meta setClassVariableString:''.

    "then let the new meta create the class"
    cls := meta new.
    cls setSuperclass:JavaObject.
    cls instSize:0.
    cls setName:('JAVA::' , aString).
    cls flags:0.
"/    cls setClassVariableString:''.
    cls setInstanceVariableString:''.
    cls category:#java.

    cls setFullName:aString.

    "/ break up the package and create nameSpaces
    "/ for each package component.
    "/ This allows java.foo.bar to be visible in ST/X
    "/ under the name JAVA::java::foo::bar

    ns := JAVA.

    parts := aString asCollectionOfSubstringsSeparatedBy:$/.
    parts size > 1 ifTrue:[
        s := '' writeStream.
        s nextPutAll:'JAVA'.
        parts from:1 to:(parts size - 1) do:[:aPart |
            s nextPutAll:'::'.
            s nextPutAll:aPart
        ].
        Metaclass confirmationQuerySignal answer:false do:[
            Class updateChangeFileQuerySignal answer:false do:[
                ns := Namespace fullName:(s contents).
            ]
        ]
    ].
    ns isNamespace ifTrue:[
        ns at:parts last asSymbol put:cls.
    ].

    "/ for ST/X browsing
    Smalltalk at:('JAVA::' , aString) asSymbol put:cls.

    ^ cls

    "Created: 15.4.1996 / 15:52:55 / cg"
    "Modified: 3.8.1997 / 17:01:15 / cg"
!

name:aString
    self shouldNotImplement

    "Created: 15.4.1996 / 15:52:55 / cg"
! !

!JavaClass class methodsFor:'signature parsing'!

initialValueFromSignature:aSignature
    "given a signature, return an initializer value"

    |s|

    s := aSignature readStream.
    ^ self initialValueFromStream:s.

    "
     JavaClass initialValueFromSignature:'LObject;'    
     JavaClass initialValueFromSignature:'B'        
     JavaClass initialValueFromSignature:'I'        
    "


!

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

    |typeChar|

    typeChar := s next.
    ^ InitialValuePerType at:typeChar ifAbsent:nil.
! !

!JavaClass class methodsFor:'special'!

setInstanceVariableStringFromFields:f in:aClass
    |varNames|

    varNames := ''.
    f do:[:aField |
	varNames := varNames , aField name , ' '
    ].
    aClass setInstanceVariableString:varNames.

    "Created: 15.4.1996 / 16:42:52 / cg"
! !

!JavaClass methodsFor:'accessing'!

binaryFile
    ^ binaryFilePath


!

category
    "java classes do not really hav a category;
     simulate one by separating its name into individual components,
     prepending 'java'"

    |nameComponents|

    nameComponents := fullName asCollectionOfSubstringsSeparatedBy:$/.
    nameComponents size <= 1 ifTrue:[
        ^ 'java' "/ fullName  
    ].
    ^ ((nameComponents asStringWith:$/ from:1 to:(nameComponents size - 1))) replaceAll:$/ by:$.

    "Modified: 30.7.1997 / 15:35:22 / cg"
!

compiledMethodAt:name signature:sig
    "lookup the classes methodDictionary"

    methodDictionary keysAndValuesDo:[:mFullSelector :aMethod |
        aMethod name == name ifTrue:[
            aMethod signature == sig ifTrue:[
                ^ aMethod
            ]
        ]
    ].
    ^ nil

    "Created: 1.8.1997 / 00:01:58 / cg"
!

constantPool
    ^ constantPool
!

fields
    ^ fields
!

fullName
    ^ fullName
!

interfaces
    interfaces notNil ifTrue:[
	interfaces := interfaces collect:[:clsRef |
				    clsRef isUnresolved ifTrue:[
					clsRef preResolve
				    ] ifFalse:[
					clsRef
				    ]
				 ].
    ].
    ^ interfaces
!

javaClass
    ^ self
!

name
    ^ name "/ fullName
!

nameSpace
    ^ JAVA

    "Created: 20.1.1997 / 13:04:30 / cg"
!

nameWithoutNameSpacePrefix
    ^ fullName

    "Created: 20.1.1997 / 13:05:30 / cg"
!

nameWithoutPrefix
    ^ fullName

    "Created: 20.1.1997 / 13:06:06 / cg"
!

package
    "extract from the fullName"

    |components|

    components := fullName asCollectionOfSubstringsSeparatedBy:$/.
    components size > 1 ifTrue:[
	^ (components copyWithoutLast:1) asStringWith:$/
    ].
    ^ fullName

    "
     Java allClasses first fullName
     Java allClasses first package  
    "
!

source
    ^ Java classSourceOf:self

    "
     (Java at:'java.awt.Frame') source
     (Java at:'ArcTest') source
     (Java at:'ArcCanvas') source
    "

    "Modified: 30.7.1997 / 14:31:01 / cg"
!

sourceFile
    ^ sourceFile
!

staticFields
    ^ staticFields
!

typeOfField:aFieldName

    fields do:[:aField |
	aField name = aFieldName ifTrue:[
	    ^ aField type
	]
    ].
    self error:'no such field'

    "
     (JAVA at:#'java/awt/image/ColorModel') typeOfField:'pixel_bits' 
    "

    "Modified: 21.1.1997 / 22:48:28 / cg"
! !

!JavaClass methodsFor:'compiler interface'!

compilerClass
    "return the compiler to use for this class - 
     this can be redefined in special classes, to get classes with
     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."

    ^ Compiler.

    ^ JavaCompiler

    "Created: 31.7.1997 / 23:03:37 / cg"
    "Modified: 4.8.1997 / 16:50:08 / cg"
!

evaluatorClass
    "return the compiler to use for expression evaluation for this class - 
     this can be redefined in special classes, to get classes with
     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."

    ^ Compiler.

    ^ JavaCompiler

    "Created: 31.7.1997 / 23:03:56 / cg"
    "Modified: 4.8.1997 / 16:49:14 / cg"
!

parserClass
    "return the parser to use for parsing this class - 
     this can be redefined in special classes, to get classes with
     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."

    ^ Compiler.

    ^ JavaCompiler

    "Created: 31.7.1997 / 23:04:11 / cg"
    "Modified: 4.8.1997 / 16:50:18 / cg"
! !

!JavaClass methodsFor:'documentation support'!

htmlDocumentation
    ^ nil "/ replace by access to javadoc-generated documentation later

    "Modified: 22.3.1997 / 14:18:50 / cg"
! !

!JavaClass methodsFor:'fileOut'!

basicFileOutDefinitionOn:aStream withNameSpace:nameSpaceBoolean
    JavaDecompiler definitionOf:self on:aStream

    "Modified: 22.3.1997 / 14:30:28 / cg"
!

fileOut
    self warn:'fileOut not yet supported'

    "Modified: 22.3.1997 / 14:30:28 / cg"
    "Created: 22.3.1997 / 14:35:43 / cg"
! !

!JavaClass methodsFor:'java initialization'!

classInit
    "call the classes JAVA clinit function"

    |m|

    initialized := true.

    m := self compiledMethodAt:#'<clinit>()V'.
    m notNil ifTrue:[
"/        'calling clinit() of ' print. self fullName printNL.
        [
            self 
                invokeJavaMethod:m 
                sender:thisContext
                selector:#'<clinit>()V'.
        ] valueOnUnwindDo:[
            initialized := false
        ]
    ] ifFalse:[
"/        self fullName print. ' has no clinit()' printNL.
    ].

    "
     JavaInterpreter instructionTrace:true.
     JavaInterpreter callTrace:true.

     (Java classNamed:'java.lang.String') classInit
     (Java classNamed:'java.lang.System') classInit

     (Java classNamed:'java/io/FileDescriptor') classInit
     (Java classNamed:'java.util.Properties') classInit 
    "

    "Modified: 30.7.1997 / 13:28:38 / cg"
!

initializeIfNotYetDone
    "if not yet done, call the classes JAVA clinit function"

    initialized ~~ true ifTrue:[
        self classInit
    ]

    "Created: 1.8.1997 / 22:37:40 / cg"
!

initializeStaticFields
    staticFields isNil ifTrue:[^ self].

    staticFields do:[:f |
	|val type|

	(val := f constantValue) isNil ifTrue:[
	    "/ careful: int/long etc. constants must be initialized
	    "/ with correct type.
	    type := f type.
	    type == #long ifTrue:[
		val := 0.
	    ] ifFalse:[type == #int ifTrue:[
		val := 0.
	    ] ifFalse:[type == #float ifTrue:[
		val := 0.0 asShortFloat
	    ] ifFalse:[type == #double ifTrue:[
		val := 0.0 
	    ] ifFalse:[type == #byte ifTrue:[
		val := 0.
	    ] ifFalse:[type == #char ifTrue:[
		val := 0.
	    ] ifFalse:[type == #'unsigned short' ifTrue:[
		val := 0.
	    ] ifFalse:[type == #boolean ifTrue:[
		val := 0.
	    ]]]]]]]].
	].
	self instVarNamed:(f name) put:val.
    ].
! !

!JavaClass methodsFor:'java instance creation'!

initValueFor:instVarName
    |idx field|

    idx := fields findFirst:[:field | field name = instVarName].
    idx == 0 ifTrue:[
	superclass ~~ JavaObject ifTrue:[
	    ^ superclass initValueFor:instVarName
	].
	self halt
    ] ifFalse:[
	field := fields at:idx.
	^ field initialValue
    ].
!

new
    "create a new instance, and call its JAVA init function"

    |newJavaObject|

    newJavaObject := self newCleared.
    newJavaObject invoke:#'<init>()V'.
    ^ newJavaObject

    "
     (Java classNamed:'java.lang.String') basicNew inspect
     (Java classNamed:'java.lang.String') new inspect
    "

    "Modified: 30.7.1997 / 17:40:25 / cg"
!

newCleared
    "create a new cleared JAVA instance.
     Its instVars are cleared to the corresponding typed values;
     however, <init> is not invoked for it."

    |newJavaObject|

    newJavaObject := super basicNew.

    fields isNil ifTrue:[
	'OOPS - no fieldSpec for new object' errorPrintNL.
	newJavaObject initializeToZero.     "/ mhmh
    ] ifFalse:[
	initValues notNil ifTrue:[
	    newJavaObject initializeFields:initValues
	]
    ].
    ^ newJavaObject

    "
     (Java classNamed:'java.lang.String') basicNew inspect
     (Java classNamed:'java.lang.String') newCleared inspect
     (Java classNamed:'java.lang.String') new inspect
    "

    "Modified: 18.3.1997 / 17:31:18 / cg"
!

newFromInterpreter:anInterpreter sender:aJavaContext
    "create a new instance, and call its JAVA init function.
     This is done in the context of an already running interpreter."

    |newJavaObject|

    newJavaObject := self newCleared.
    newJavaObject invoke:#'<init>' interpreter:anInterpreter sender:aJavaContext.
    ^ newJavaObject

    "Created: 18.3.1997 / 17:33:07 / cg"
! !

!JavaClass methodsFor:'message sending'!

invokeJava:selector
    "send javaSelector (name+sig) message, without arguments
     as a static call to the class"

    ^ self
	invokeJava:selector sender:thisContext sender

    "Modified: 7.4.1997 / 22:52:30 / cg"
!

invokeJava:selector sender:aContext
    "send javaSelector (name+sig) message, without arguments
     as a static call to the class"

    |method|

    method := self lookupMethodFor:selector.
    method notNil ifTrue:[
        ^ self 
            invokeJavaMethod:method 
            sender:aContext
            selector:selector
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "Created: 7.4.1997 / 22:52:10 / cg"
    "Modified: 30.7.1997 / 13:29:09 / cg"
!

invokeJava:selector with:arg
    "send javaSelector (name+sig) message, with 1 argument
     as a static call to the class"

    |method|

    method := self lookupMethodFor:selector.
    method notNil ifTrue:[
        ^ self 
                invokeJavaMethod:method 
                sender:thisContext
                selector:selector
                with:arg 
    ].
    ^ self doesNotUnderstand:(Message selector:selector)

    "Modified: 30.7.1997 / 13:37:58 / cg"
!

invokeJava:selector with:arg sender:aContext
    "send javaSelector (name+sig) message, with 1 argument
     as a static call to the class"

    |method|

    method := self lookupMethodFor:selector.
    method notNil ifTrue:[
        ^ self 
            invokeJavaMethod:method 
            sender:aContext
            selector:selector
            with:arg 
    ].
    ^ self doesNotUnderstand:(Message selector:selector)

    "Created: 7.4.1997 / 22:52:51 / cg"
    "Modified: 30.7.1997 / 13:39:45 / cg"
!

invokeJavaMethod:aJavaMethod sender:aContext selector:sel
    "invoke a static java method, without arguments"

    |i val|

    aJavaMethod numArgs ~~ 0 ifTrue:[
        self halt:'need arguments'
    ].
    aJavaMethod isStatic ifFalse:[
        self halt:'non-static function'
    ].

    i := JavaInterpreter new.
    val := i interpret:aJavaMethod sender:aContext.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)

    "Modified: 30.7.1997 / 12:01:52 / cg"
    "Created: 30.7.1997 / 13:34:33 / cg"
!

invokeJavaMethod:aJavaMethod sender:aContext selector:sel with:arg1
    "invoke a static java method, without arguments"

    |i val|

    aJavaMethod numArgs ~~ 1 ifTrue:[
        self halt:'need arguments'
    ].
    aJavaMethod isStatic ifFalse:[
        self halt:'non-static function'
    ].

    i := JavaInterpreter new.
    i push:arg1.
    val := i interpret:aJavaMethod sender:aContext.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)

    "Created: 30.7.1997 / 13:34:33 / cg"
    "Modified: 30.7.1997 / 13:38:46 / cg"
!

invokeJavaMethod:aJavaMethod with:arg sender:aContext 
    "invoke a static java method, with one argument"

    |i val|

    aJavaMethod numArgs ~~ 1 ifTrue:[
	self halt:'argument count'
    ].
    aJavaMethod isStatic ifFalse:[
	self halt:'non-static function'
    ].

    i := JavaInterpreter new.
    i push:arg.

    val := i interpret:aJavaMethod sender:aContext.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)

    "Modified: 7.4.1997 / 22:50:02 / cg"
    "Created: 7.4.1997 / 22:53:18 / cg"
!

invokeStatic:selector
    "send a static message, without args."

    |method cls sel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |

"/     aMethod name printNL.
        
                aMethod isStatic ifTrue:[
                    sel == selector ifTrue:[
                        ^ self 
                            invokeJavaMethod:aMethod 
                            sender:thisContext
                            selector:selector
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "Created: 5.8.1997 / 14:35:34 / cg"
    "Modified: 5.8.1997 / 14:36:54 / cg"
!

lookupMethodFor:selector
    |method cls sel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
	cls := self.
	[cls notNil] whileTrue:[
	    method := cls compiledMethodAt:sel.
	    method notNil ifTrue:[ ^ method ].
	    cls := cls superclass.
	].
    ].

    ^ nil
! !

!JavaClass methodsFor:'printOut'!

printNameInHierarchy
    "return my name as printed in the hierarchy"

    ^ self displayString

    "Modified: 22.3.1997 / 14:16:55 / cg"
!

printOutOn:aStream
    self warn:'printOut not yet supported'

    "Created: 22.3.1997 / 14:36:12 / cg"
!

printOutProtocolOn:aStream
    self warn:'printOut not yet supported'

    "Created: 22.3.1997 / 14:36:28 / cg"
! !

!JavaClass methodsFor:'printing & storing'!

displayString
    ^ (fullName copyFrom:1) replaceAll:$/ by:$.

"/    ^ 'JAVA-' , name .
"/    ^ name , '(Java)'  "/ 'JavaClass(' , name , ')'

    "Created: 15.4.1996 / 16:02:48 / cg"




! !

!JavaClass methodsFor:'private accessing'!

addMethod:m name:name signature:signature
    |sel|

    sel := (name , signature) asSymbol.
    self addSelector:sel withMethod:m.
    ^ self.

"/    selectorArray isNil ifTrue:[
"/        selectorArray := #().
"/        methodArray := #()
"/    ].
"/    selectorArray := selectorArray copyWith:(name , signature) asSymbol. "/ name.
"/"/    selectorArray := selectorArray copyWith:name asSymbol. "/ name.
"/    methodArray := methodArray copyWith:m

    "Created: 15.4.1996 / 16:42:52 / cg"


!

addSelector:newSelector withMethod:newMethod
    "redefined to not flush smalltalk caches and send NO smalltalk-class
     change notification. Will eventually flush Java caches."

    |nargs oldMethod|

    oldMethod := self compiledMethodAt:newSelector.
    (self primAddSelector:newSelector withMethod:newMethod) ifFalse:[^ false].

    ^ true

    "Created: 20.1.1997 / 13:00:48 / cg"
!

markUninitialized
    initialized := false.
!

setAccessFlags:flags
    accessFlags := flags.

    "Created: 15.4.1996 / 16:42:52 / cg"
!

setBinaryFilePath:aPathName
    binaryFilePath := aPathName
!

setConstantPool:anArray
    constantPool := anArray.
    hasUnresolvedConstants := true

    "Created: 15.4.1996 / 16:42:52 / cg"
!

setFields:f
    JavaClass setInstanceVariableStringFromFields:f in:self.

    instSize := superclass instSize + f size.

    fields := f.
    initValues := self allInstVarNames collect:[:nm |
	self initValueFor:nm
    ].
    initValues isEmpty ifTrue:[
	initValues := nil
    ].

    "Created: 15.4.1996 / 16:42:52 / cg"


!

setFullName:aString
    |nameComponents|

    fullName := aString asSymbol.
    nameComponents := aString asCollectionOfSubstringsSeparatedBy:$/.
    name := nameComponents last asSymbol

    "Created: 15.4.1996 / 16:42:52 / cg"
!

setInterfaces:i
    i size > 0 ifTrue:[
	interfaces := i
    ] ifFalse:[
	interfaces := nil
    ]

    "Modified: 7.4.1997 / 15:44:53 / cg"
!

setSourceFile:aFilename
    sourceFile := aFilename.

    "Created: 15.4.1996 / 16:42:52 / cg"
!

setStaticFields:f
    JavaClass setInstanceVariableStringFromFields:f in:self class.

    staticFields := f.


!

setSuperclass:aClass
    aClass isNil ifTrue:[
	super setSuperclass:JavaObject
    ] ifFalse:[
	(aClass isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
	    self halt.
	].
	super setSuperclass:aClass.
    ].

    instvars notNil ifTrue:[
	(superclass notNil and:[(superclass isMemberOf:JavaUnresolvedClassConstant) not]) ifTrue:[
	    instSize := superclass instSize + (instvars asCollectionOfWords size)
	] ifFalse:[
	    instSize := instvars asCollectionOfWords size
	]
    ].

    "Created: 15.4.1996 / 16:42:52 / cg"
! !

!JavaClass methodsFor:'queries'!

browserClass
    "return the browser to use for this class - 
     this can be redefined in special classes, to get different browsers"

    ^ JavaBrowser




!

hasInterface:aJavaInterface
    interfaces size > 0 ifTrue:[
	self interfaces do:[:if |
	    aJavaInterface == if ifTrue:[
		^ true
	    ].
	]
    ].
"/  ^ false.

    aJavaInterface methodDictionary keysAndValuesDo:[:sel :mthd |
	(self canUnderstand:sel) ifFalse:[
	    self halt.
	    ^ false.
	]
    ].
    ^ true
!

isAbstract
    ^ (accessFlags bitAnd:16r0400) ~~ 0
!

isClass
    ^ true
!

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

isInitialized
    ^ initialized == true
!

isInterface
    ^ (accessFlags bitAnd:16r0200) ~~ 0
!

isJavaClass
    ^ self ~~ JavaClass

    "Created: 18.3.1997 / 17:48:01 / cg"
!

isObsolete 
    "return true, if the receiver is obsolete 
     Java classes are never."

    ^ false


!

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

isUnresolved
    ^ false
!

supportsMethodCategories
    ^ self == JavaClass

    "Created: 30.7.1997 / 14:58:58 / cg"
! !

!JavaClass methodsFor:'smalltalk interface'!

invoke:selector
    "send a message, without args."

    |method cls sel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |

"/     aMethod name printNL.
        
                (aMethod name == selector 
                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
                    aMethod numArgs == 0 ifTrue:[
                        ^ self 
                            invokeJavaMethod:aMethod 
                            sender:thisContext
                            selector:selector
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#'<init>'. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#isEmpty. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#size. 
    "

    "Created: 30.7.1997 / 14:06:50 / cg"
    "Modified: 1.8.1997 / 00:06:56 / cg"
!

invoke:selector signature:signature
    "send a message, without args."

    |method cls sel sig|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        sig := signature asSymbolIfInterned.
        sig notNil ifTrue:[
            cls := self.
            [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
                method := cls compiledMethodAt:sel signature:signature.
                method notNil ifTrue:[
                    ^ self 
                        invokeJavaMethod:method 
                        sender:thisContext
                        selector:sel
                ].
                cls := cls superclass.
            ].
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#'<init>'. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#isEmpty. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#size. 
    "

    "Created: 30.7.1997 / 14:12:29 / cg"
    "Modified: 1.8.1997 / 00:04:45 / cg"
!

invoke:selector signature:signature with:arg
    "send a message, with 1 arg1."

    |method cls sel sig|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        sig := signature asSymbolIfInterned.
        sig notNil ifTrue:[
            cls := self.
            [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
                method := cls compiledMethodAt:sel signature:signature.
                method notNil ifTrue:[
                    ^ self 
                        invokeJavaMethod:method 
                        sender:thisContext
                        selector:sel
                        with:arg
                ].
                cls := cls superclass.
            ].
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#'<init>'. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#isEmpty. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#size. 
    "

    "Created: 30.7.1997 / 14:13:30 / cg"
    "Modified: 1.8.1997 / 00:04:40 / cg"
!

invoke:selector with:arg
    "send a message, with one arg"

    |method cls sel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |

"/     aMethod name printNL.
                (aMethod name == selector 
                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
                    aMethod numArgs == 1 ifTrue:[
                        ^ self 
                            invokeJavaMethod:aMethod 
                            sender:thisContext 
                            selector:selector    
                            with:arg
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "Modified: 30.7.1997 / 13:59:49 / cg"
!

invoke:selector with:arg1 with:arg2
    "send a message, with two args"

    |method cls sel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |

"/     aMethod name printNL.
                (aMethod name == selector 
                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
                    aMethod numArgs == 2 ifTrue:[
                        ^ self 
                            invokeJavaMethod:aMethod 
                            sender:thisContext 
                            selector:selector    
                            with:arg1
                            with:arg2
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "Modified: 30.7.1997 / 13:39:15 / cg"
    "Created: 30.7.1997 / 14:00:09 / cg"
!

invoke:selector withAll:args
    "send a message, with a number of args"

    |method cls sel numArgGiven|

    numArgGiven := args size.

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |

"/     aMethod name printNL.
                (aMethod name == selector 
                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
                    aMethod numArgs == numArgGiven ifTrue:[
                        ^ self 
                            invokeJavaMethod:aMethod 
                            sender:thisContext 
                            selector:selector    
                            withAll:args
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "Modified: 30.7.1997 / 13:39:15 / cg"
    "Created: 30.7.1997 / 14:00:53 / cg"
!

invokeSignature:signature
    "send a message, without args."

    |method cls sel|

    sel := signature asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |

"/     aMethod name printNL.
        
                aMethod signatureName = signature ifTrue:[
                    aMethod numArgs == 0 ifTrue:[
                        ^ self 
                            invokeJavaMethod:aMethod 
                            sender:thisContext
                            selector:signature
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ self doesNotUnderstand:(Message selector:signature)

    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#'<init>'. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#isEmpty. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') basicNew.
     stack invoke:#size. 
    "

    "Modified: 30.7.1997 / 14:07:55 / cg"
    "Created: 30.7.1997 / 14:09:31 / cg"
!

methodMatching:aSmalltalkSelector
    |numArgs cls|

    numArgs := aSmalltalkSelector numArgs.
    cls := self.
    [cls notNil] whileTrue:[
	methodDictionary keysAndValuesDo:[:jSelector :aMethod |
	    aMethod numArgs == numArgs ifTrue:[
		aMethod name = aSmalltalkSelector ifTrue:[
		    ^ aMethod
		]
	    ]
	].
	cls := cls superclass
    ].
    ^ nil

    "Modified: 1.2.1997 / 21:57:36 / cg"
    "Created: 1.2.1997 / 21:57:53 / cg"
! !

!JavaClass methodsFor:'special'!

updateClassRefsFrom:oldClass to:newClass
    constantPool updateClassRefsFrom:oldClass to:newClass.
    interfaces notNil ifTrue:[
        interfaces := interfaces collect:[:anInterface |
                                            anInterface == oldClass ifTrue:[
                                                newClass
                                            ] ifFalse:[
                                                oldClass
                                            ]
                                         ]
    ]

    "Modified: 7.8.1997 / 15:13:06 / cg"
! !

!JavaClass class methodsFor:'documentation'!

version
    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.58 1997/08/07 13:19:56 cg Exp $'
! !
JavaClass initialize!