JavaObject.st
author cg
Thu, 27 Jun 1996 14:25:32 +0000
changeset 83 2d61ef3579e4
parent 78 ef7b6b87d4ce
child 91 9b325648aa77
permissions -rw-r--r--
*** empty log message ***

Object subclass:#JavaObject
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Java-Classes'
!


!JavaObject  class methodsFor:'misc'!

resolveClassRefs
!

resolveClassRefsIgnoring:setOfClasses
! !

!JavaObject  class methodsFor:'smalltalk interface'!

convertJavaObject:val signature:retValSignature
    retValSignature = 'void' ifTrue:[
        ^ #void
    ].
    retValSignature = 'boolean' ifTrue:[
        val == 0 ifTrue:[^ false].
        ^ true
    ].
    retValSignature = 'int' ifTrue:[
        val isInteger ifFalse:[
            self halt
        ].
        ^ val
    ].
    retValSignature = 'char[]' ifTrue:[
        "/ these are ST-strings
        ^ val
    ].

    retValSignature = 'char' ifTrue:[
        "/ these are ST-characters
        val isInteger ifTrue:[
            ^ Character value:val
        ].
        self halt.
        ^ val
    ].

    retValSignature = 'Object' ifTrue:[
        ^ val
    ].

    retValSignature = 'String' ifTrue:[
        ^ self stringFromJavaString:val
    ].

    'no conversion for: ' print. val class name print. ' to: ' print. retValSignature printNL.
    ^ val.


!

javaStringFrom:aString
    "hard-coding internas of java.lang.String here is bad ..."

    |s|

    s := (Java at:'java/lang/String') basicNew.
    s instVarNamed:'value'  put: aString.
    s instVarNamed:'offset' put: 0.
    s instVarNamed:'count'  put: aString size.
    ^ s
!

stringFromJavaString:aJavaString
    "hard-coding internas of java.lang.String here is bad ..."

    (aJavaString instVarNamed:'offset') ~~ 0 ifTrue:[self halt].

    ^ ((aJavaString instVarNamed:'value') 
        copyTo:(aJavaString instVarNamed:'count')) asString
! !

!JavaObject methodsFor:'initialization'!

initializeFields:initialValues
    |sz|

    sz := self class instSize.
    1 to:sz do:[:i |
        self instVarAt:i put:(initialValues at:i)
    ]
!

initializeToZero
    |sz|

    sz := self class instSize.
    1 to:sz do:[:i |
        self instVarAt:i put:0
    ]
! !

!JavaObject methodsFor:'message sending'!

invokeJava:selector
    "send javaSelector (name+sig) message, without arguments"

    |method|

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

    ^ self doesNotUnderstand:(Message selector:selector)

!

invokeJava:selector with:arg
    "send javaSelector (name+sig) message, with 1 argument"

    |method|

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

invokeJava:selector with:arg1 with:arg2
    "send javaSelector (name+sig) message, with 2 arguments"

    |method|

    method := self class lookupMethodFor:selector.
    method notNil ifTrue:[
        ^ self invokeJavaMethod:method with:arg1 with:arg2
    ].
    ^ self doesNotUnderstand:(Message selector:selector)
!

invokeJavaMethod:aJavaMethod
    "invoke java method, without arguments"

    ^ self invokeJavaMethod:aJavaMethod sender:thisContext sender.
!

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

    |i val|

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

    i := JavaInterpreter new.
    i push:self.

    val := i interpret:aJavaMethod sender:aContext.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)
!

invokeJavaMethod:aJavaMethod with:arg
    "invoke a java method, with one argument.
     CAVEAT: this cannot be a long or doubles currently."

    |i val|

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

    i := JavaInterpreter new.
    i push:self.
    i push:arg.

    val := i interpret:aJavaMethod sender:thisContext sender.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)

!

invokeJavaMethod:aJavaMethod with:arg1 with:arg2
    "invoke a java method, with two arguments.
     CAVEAT: these cannot be long or doubles currently."

    |i val|

    aJavaMethod numArgs ~~ 2 ifTrue:[
        self halt:'argument count'
    ].
    aJavaMethod isStatic ifTrue:[
        self halt:'static function'
    ].

    i := JavaInterpreter new.
    i push:self.
    i push:arg1.
    i push:arg2.

    val := i interpret:aJavaMethod sender:thisContext sender.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)

!

invokeJavaMethod:aJavaMethod with:arg1 with:arg2 with:arg3 with:arg4
    "invoke a java method, with 4 arguments.
     CAVEAT: these cannot be long or doubles currently."

    |i val|

    aJavaMethod numArgs ~~ 4 ifTrue:[
        self halt:'argument count'
    ].
    aJavaMethod isStatic ifTrue:[
        self halt:'static function'
    ].

    i := JavaInterpreter new.
    i push:self.
    i push:arg1.
    i push:arg2.
    i push:arg3.
    i push:arg4.

    val := i interpret:aJavaMethod sender:thisContext sender.

    ^ JavaObject convertJavaObject:val signature:(aJavaMethod retValSignature)

! !

!JavaObject methodsFor:'printing & storing'!

displayString
    self class fullName = 'java/lang/String' ifTrue:[
        ^ '''' , (JavaObject stringFromJavaString:self) , ''''
    ].

    ^ super displayString. "/ ^ 'a JavaObject(' , self class name , ')'
! !

!JavaObject methodsFor:'smalltalk interface'!

invoke:selector
    "send a message, without args"

    |method cls sel|

    method := self lookupMethod:selector numArgs:0.
    method notNil ifTrue:[
        ^ self invokeJavaMethod:method sender:thisContext
    ].

"/    sel := selector asSymbolIfInterned.
"/    sel notNil ifTrue:[
"/        cls := self class.
"/        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
"/            cls methodDictionary keysAndValuesDo:[:sel :aMethod |
"/                aMethod name == selector ifTrue:[
"/                    aMethod numArgs == 0 ifTrue:[
"/                        ^ self invokeJavaMethod:aMethod sender:thisContext
"/                    ]
"/                ]
"/            ].
"/            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') new.
     stack invoke:#isEmpty. 
    "
    "
     |stack|

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

invoke:selector sender:aContext
    "send a message, without args"

    |method cls sel|

    method := self lookupMethod:selector numArgs:0.
    method notNil ifTrue:[
        ^ self invokeJavaMethod:method sender:aContext
    ].

"/    sel := selector asSymbolIfInterned.
"/    sel notNil ifTrue:[
"/        cls := self class.
"/        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
"/            cls methodDictionary keysAndValuesDo:[:sel :aMethod |
"/                aMethod name == selector ifTrue:[
"/                    aMethod numArgs == 0 ifTrue:[
"/                        ^ self invokeJavaMethod:aMethod sender:aContext
"/                    ]
"/                ]
"/            ].
"/            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') new.
     stack invoke:#isEmpty. 
    "
    "
     |stack|

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

invoke:selector with:argument
    "send a message, with 1 argument. 
     TEMPORARY: This method needs more work."

    |sel method cls argClass jSel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        "/
        "/ hard to do - must find a matching method probably
        "/
        (argument isKindOf:JavaObject) ifTrue:[
            argClass := argument class.
        ] ifFalse:[
            "/
            "/ map to Java:
            "/   String -> [c
            "/
            (argument isMemberOf:String) ifTrue:[
                jSel := (selector , '([C)V') asSymbolIfInterned.
                jSel notNil ifTrue:[
                    ^ self invokeJava:jSel with:argument
                ]
            ]
        ].

        method := self lookupMethod:sel numArgs:1.
        method notNil ifTrue:[
            ^ self invokeJavaMethod:method with:argument
        ].

"/        cls := self class.
"/        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
"/            cls methodDictionary keysAndValuesDo:[:sel :aMethod |
"/                aMethod name == sel ifTrue:[
"/                    aMethod numArgs == 1 ifTrue:[
"/                        "/
"/                        "/ this is not completely correct:
"/                        "/ must look for the best type-match,
"/                        "/ (especially: have to look for best match
"/                        "/  over whole superclass chain ...)
"/                        "/ for now take the first with matching number of args
"/                        "/
"/                        ^ self invokeJavaMethod:aMethod with:argument
"/                    ]
"/                ]
"/            ].
"/            cls := cls superclass.
"/        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "
     |stack|

     stack := (Java at:'java/util/Stack') new.
     stack invoke:#push with:1. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') new.
     stack invoke:#push with:1. 
     stack invoke:#push with:2. 
     stack invoke:#pop. 
     stack invoke:#pop. 
     stack invoke:#pop. 
    "
!

invoke:selector with:arg1 with:arg2 with:arg3 with:arg4
    "send a message, with 4 arguments. 
     TEMPORARY: This method needs more work."

    |sel method cls argClass jSel |

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
"/        "/
"/        "/ hard to do - must find a matching method probably
"/        "/
"/        (argument isKindOf:JavaObject) ifTrue:[
"/            argClass := argument class.
"/        ] ifFalse:[
"/            "/
"/            "/ map to Java:
"/            "/   String -> [c
"/            "/
"/            (argument isMemberOf:String) ifTrue:[
"/                jSel := (selector , '([C)V') asSymbolIfInterned.
"/                jSel notNil ifTrue:[
"/                    ^ self invokeJava:jSel with:argument
"/                ]
"/            ]
"/        ].

        method := self lookupMethod:sel numArgs:4.
        method notNil ifTrue:[
            ^ self invokeJavaMethod:method with:arg1 with:arg2 with:arg3 with:arg4
        ].

"/        cls := self class.
"/        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
"/            cls methodDictionary keysAndValuesDo:[:sel :aMethod |
"/                aMethod name == sel ifTrue:[
"/                    aMethod numArgs == 1 ifTrue:[
"/                        "/
"/                        "/ this is not completely correct:
"/                        "/ must look for the best type-match,
"/                        "/ (especially: have to look for best match
"/                        "/  over whole superclass chain ...)
"/                        "/ for now take the first with matching number of args
"/                        "/
"/                        ^ self invokeJavaMethod:aMethod with:argument
"/                    ]
"/                ]
"/            ].
"/            cls := cls superclass.
"/        ].
    ].

    ^ self doesNotUnderstand:(Message selector:selector)

    "
     |stack|

     stack := (Java at:'java/util/Stack') new.
     stack invoke:#push with:1. 
    "
    "
     |stack|

     stack := (Java at:'java/util/Stack') new.
     stack invoke:#push with:1. 
     stack invoke:#push with:2. 
     stack invoke:#pop. 
     stack invoke:#pop. 
     stack invoke:#pop. 
    "
!

lookupMethod:selector numArgs:nargs
    "lookup a method"

    |method cls sel|

    sel := selector asSymbolIfInterned.
    sel notNil ifTrue:[
        cls := self class.
        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
            cls methodDictionary keysAndValuesDo:[:sel :aMethod |
                aMethod name == selector ifTrue:[
                    aMethod numArgs == nargs ifTrue:[
                        ^ aMethod
                    ]
                ]
            ].
            cls := cls superclass.
        ].
    ].

    ^ nil

    "
     |stack|

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

     stack := (Java at:'java/util/Stack') new.
     stack lookupMethod:#isEmpty numArgs:0. 
    "
! !

!JavaObject  class methodsFor:'documentation'!

version
    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaObject.st,v 1.15 1996/06/27 14:25:32 cg Exp $'
! !