Java.st
author cg
Thu, 03 Dec 1998 13:09:37 +0000
changeset 478 bccd73a1d975
parent 457 38a5f940feb7
child 494 77b9e9bbf79a
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.
"



Object subclass:#Java
	instanceVariableNames:''
	classVariableNames:'Classes UnresolvedClassRefs ClassPath SourceDirectories JavaHome
		Java_lang_String Java_lang_Class PrettyPrintStyle
		LastArgumentString Threads ExcludedClassPath FailedToLoadClasses'
	poolDictionaries:''
	category:'Java-Support'
!

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


! !

!Java class methodsFor:'accessing'!

classForName:aString
    "return a javaClass - either existing or loaded"

    |cls loader classURL|

    cls := self at:aString.
    cls isNil ifTrue:[
        FailedToLoadClasses notNil ifTrue:[
            (FailedToLoadClasses includes:aString) ifTrue:[
"/                ('JAVA [info]: class loading already failed: ' , aString) infoPrintCR.
                ^ nil
            ]
        ].

        ('JAVA [info]: late class loading: ' , aString) infoPrintCR.
        loader := JavaClassReader classLoaderQuerySignal raise.
        loader isNil ifTrue:[
            "/ load using default (ST/X) loader
            cls := JavaClassReader loadClass:aString.
        ] ifFalse:[
            "/ load using a Java class loader
"/            classURL := Java as_URL:('file:' , aString , '.class').
"/            loader loadClass:classURL.
            loader perform:#'loadClass(Ljava/lang/String;)Ljava/lang/Class;'
                with:(Java as_String:aString).

            cls := self at:aString.
        ].
        cls isNil ifTrue:[
            FailedToLoadClasses isNil ifTrue:[
                FailedToLoadClasses := Set new.
            ].
            FailedToLoadClasses add:aString
        ]
    ].
    ^ cls

    "Created: / 18.3.1997 / 16:45:57 / cg"
    "Modified: / 27.4.1998 / 15:00:52 / cg"
!

classNamed:aString
    ^ self at:aString
!

java_lang_Class
    Java_lang_Class isNil ifTrue:[
	Java_lang_Class := self at:'java.lang.Class'
    ].
    ^ Java_lang_Class

    "Created: 26.3.1997 / 13:42:59 / cg"
    "Modified: 26.3.1997 / 13:46:24 / cg"
!

java_lang_String
    Java_lang_String isNil ifTrue:[
	Java_lang_String := self at:'java.lang.String'
    ].
    ^ Java_lang_String

    "Created: 26.3.1997 / 13:43:17 / cg"
    "Modified: 26.3.1997 / 13:50:21 / cg"
!

prettyPrintStyle
    ^ PrettyPrintStyle

    "Created: 1.8.1997 / 10:37:57 / cg"
!

threads
    Threads isNil ifTrue:[
	Threads := WeakIdentityDictionary new.
    ].
    ^ Threads

    "Created: 26.8.1997 / 19:53:57 / cg"
    "Modified: 26.8.1997 / 19:55:27 / cg"
! !

!Java class methodsFor:'accessing paths'!

addToClassPath:aPath
    (ClassPath includes:aPath) ifFalse:[
        ClassPath add:aPath.
        FailedToLoadClasses := nil
    ]

    "Created: / 1.8.1997 / 21:10:07 / cg"
    "Modified: / 17.9.1998 / 20:43:55 / cg"
!

addToSourcePath:aPath
    (SourceDirectories includes:aPath) ifFalse:[
	SourceDirectories add:aPath
    ]

    "Modified: 7.2.1997 / 19:23:55 / cg"
    "Created: 2.8.1997 / 14:12:31 / cg"
!

classPath
    ^ ClassPath

    "Created: 7.2.1997 / 19:23:45 / cg"
    "Modified: 7.2.1997 / 19:23:55 / cg"
!

classPath:aCollectionOfPaths
    ClassPath := aCollectionOfPaths asOrderedCollection.
    FailedToLoadClasses := nil

    "Created: / 7.2.1997 / 19:23:45 / cg"
    "Modified: / 17.9.1998 / 20:44:09 / cg"
!

excludedClassPath
    ^ ExcludedClassPath

    "Modified: / 7.2.1997 / 19:23:55 / cg"
    "Created: / 27.1.1998 / 21:57:13 / cg"
!

isExcludedFromClassPath:fileName
    |nm|

    nm := fileName asFilename pathName.
    ExcludedClassPath do:[:excludedPath |
        (nm startsWith:excludedPath) ifTrue:[^ true].
    ].
    ^ false

    "Created: / 27.1.1998 / 22:00:40 / cg"
!

javaHome
    ^ JavaHome

    "Created: 6.8.1997 / 00:53:19 / cg"
!

javaHome:aPath
    JavaHome := aPath

    "Created: 6.8.1997 / 00:53:23 / cg"
!

removeFromClassPath:aPath
    (ClassPath includes:aPath) ifTrue:[
	ClassPath remove:aPath
    ]

    "Modified: 7.2.1997 / 19:23:55 / cg"
    "Created: 1.8.1997 / 21:10:21 / cg"
!

removeFromSourcePath:aPath
    (SourceDirectories includes:aPath) ifTrue:[
	SourceDirectories remove:aPath
    ]

    "Modified: 7.2.1997 / 19:23:55 / cg"
    "Created: 2.8.1997 / 14:13:01 / cg"
!

sourceDirectories
    ^ SourceDirectories
!

sourceDirectories:aCollectionOfPaths
    SourceDirectories := aCollectionOfPaths asOrderedCollection

    "
     Java
	sourceDirectories:#(
			    '/phys/ibm3/java/src'
			   )
    "


!

sourcePath
    ^ SourceDirectories

    "Created: / 16.1.1998 / 13:26:55 / cg"
! !

!Java class methodsFor:'class initialization'!

initAllClasses
    |system|

    FailedToLoadClasses := nil.
    self initAllStaticFields.

    system := self classForName:'java.lang.System'.
    system isInitialized ifFalse:[
        self initSystemClass.
    ].

    self allClassesDo:[:cls |
       cls isInitialized ifFalse:[
           cls classInit
       ]
    ]

    "Modified: / 10.11.1998 / 12:39:52 / cg"
!

initAllStaticFields
     self allClassesDo:[:cls |
	cls initializeStaticFields
     ]

!

initSystemClass
    |system|

    system := Java at:'java.lang.System'.
    system isNil ifTrue:[
        JavaVM initializeVM.
        system := Java at:'java.lang.System'.
        system isNil ifTrue:[
            self error:'no ''java.lang.System'' class'.
            ^ self
        ].
    ].

    system classInit.
    (system implements:#'initializeSystemClass()V') ifTrue:[
        system perform: "invokeStatic:" #'initializeSystemClass()V'.
    ].

    "
     Java initSystemClass

     (Java at:'java.lang.System') 
        perform:#'getProperty(Ljava/lang/String;)Ljava/lang/String;'
        with:(Java as_String:'java.home')
    "

    "Modified: / 10.11.1998 / 12:39:58 / cg"
!

initialize
    |tryJDK1_2 tryJDK1_16 tryJDK1_15 tryJDK1_13 tryJDK1_11 tryJDK1_103 directoriesToSearch 
     jHome jClasses jSources mozillaHome tryNetscape4_0
     tryMS tryBorland tryVA fn|

    FailedToLoadClasses := nil.

    "/ cannot use JDK1.2 yet (they made so many changes ...)
    tryVA := false. "/ true.    
    tryNetscape4_0 := false.
    tryMS := false.
    tryBorland := true.
    tryJDK1_2 := false.
    tryJDK1_16 := true.
    tryJDK1_15 := true.
    tryJDK1_13 := true.
    tryJDK1_11 := true.
    tryJDK1_103 := false.

"/    tryBorland := false.
"/    tryJDK1_16 := false.
"/    tryJDK1_15 := false.
"/    tryJDK1_13 := false.
"/    tryJDK1_11 := false.
"/    tryMS := true.

    ExcludedClassPath := OrderedCollection new.

    directoriesToSearch := OrderedCollection new.

    tryVA ifTrue:[        
        directoriesToSearch add:'C:\IBMVJava\EAB\jdk'.
    ].
    tryBorland ifTrue:[        
        directoriesToSearch add:'c:\jbuilder2\java'.
    ].

    tryMS ifTrue:[        
"/        (fn := 'c:\windows\java\classes' asFilename) exists ifTrue:[
"/            directoriesToSearch add:'c:\windows\java\classes'.
"/            fn directoryContents do:[:f |
"/                (f asFilename hasSuffix:'zip') ifTrue:[
"/                    directoriesToSearch add:(fn construct:f) pathName                    
"/                ]
"/            ]
"/        ].
        (fn := 'c:\windows\java\packages' asFilename) exists ifTrue:[
            fn directoryContents do:[:f |
                (f asFilename hasSuffix:'zip') ifTrue:[
                    directoriesToSearch add:(fn construct:f) pathName                    
                ]
            ]
        ].
        (fn := 'c:\windows\java\trustlib' asFilename) exists ifTrue:[
            fn directoryContents do:[:f |
                (f asFilename hasSuffix:'zip') ifTrue:[
                    directoriesToSearch add:(fn construct:f) pathName                    
                ]
            ]
        ]
    ].

    tryJDK1_2 ifTrue:[        
        directoriesToSearch addAll:
                                #(
                                    '/phys/idefix/home2/java/jdk1.2'
                                    '/usr/local/java/jdk1.2'
                                    '/usr/local/jdk1.2'
                                    '/usr/java/jdk1.2'
                                    '/usr/jdk1.2'
                                    'c:\jdk1.2'
                                    'c:\java\jdk1.2'
                                )
    ].

    tryJDK1_16 ifTrue:[
        directoriesToSearch addAll:
                                #(
                                    '/phys/idefix/home2/java/jdk116'
                                    '/usr/local/java/jdk116'
                                    '/usr/local/java/jdk1.1.6'
                                    '/usr/local/jdk116'
                                    '/usr/local/jdk1.1.6'
                                    '/usr/java/jdk116'
                                    '/usr/java/jdk1.1.6'
                                    '/usr/jdk116'
                                    '/usr/jdk1.1.6'
                                    'c:\jdk116'
                                    'c:\jdk1.1.6'
                                    'c:\java\jdk1.1.6'
                                ) 
    ].

    tryJDK1_15 ifTrue:[        
        directoriesToSearch addAll:
                                #(
                                    '/phys/idefix/home2/java/jdk115'
                                    '/usr/local/java/jdk115'
                                    '/usr/local/java/jdk1.1.5'
                                    '/usr/local/jdk115'
                                    '/usr/local/jdk1.1.5'
                                    '/usr/java/jdk115'
                                    '/usr/java/jdk1.1.5'
                                    '/usr/jdk115'
                                    '/usr/jdk1.1.5'
                                    'c:\jdk115'
                                    'c:\jdk1.1.5'
                                    'c:\java\jdk1.1.5'
                                )
    ].

    tryJDK1_13 ifTrue:[        
        directoriesToSearch addAll:
                                #(
                                    '/phys/idefix/home2/java/jdk113'
                                    '/usr/local/java/jdk113'
                                    '/usr/local/java/jdk1.1.3'
                                    '/usr/local/jdk113'
                                    '/usr/local/jdk1.1.3'
                                    '/usr/java/jdk113'
                                    '/usr/java/jdk1.1.3'
                                    '/usr/jdk113'
                                    '/usr/jdk1.1.3'
                                    'c:\jdk113'
                                    'c:\jdk1.1.3'
                                    'c:\java\jdk1.1.3'
                                )
    ].

    tryJDK1_11 ifTrue:[        
        directoriesToSearch addAll:
                                #(
                                    '/phys/idefix/home2/java/jdk111'
                                    '/usr/local/java/jdk111'
                                    '/usr/local/java/jdk1.1.1'
                                    '/usr/local/jdk111'
                                    '/usr/local/jdk1.1.1'
                                    '/usr/java/jdk111'
                                    '/usr/java/jdk1.1.1'
                                    '/usr/jdk111'
                                    '/usr/jdk1.1.1'
                                    'c:\jdk111'
                                    'c:\jdk1.1.1'
                                    'c:\java\jdk1.1.1'
                                )
    ].

    tryJDK1_103 ifTrue:[        
        directoriesToSearch addAll:
                                #(
                                    '/phys/idefix/home2/java/jdk103'
                                    '/usr/local/java/jdk103'
                                    '/usr/local/java/jdk1.0.3'
                                    '/usr/local/jdk103'
                                    '/usr/local/jdk1.0.3'
                                    '/usr/java/jdk103'
                                    '/usr/java/jdk1.0.3'
                                    '/usr/jdk103'
                                    '/usr/jdk1.0.3'
                                    'c:\jdk103'
                                    'c:\jdk1.0.3'
                                    'c:\java\jdk1.0.3'
                                )
    ].

    jClasses := OrderedCollection new.

    directoriesToSearch do:[:aPath | 
        |dir libDir|

        dir := aPath asFilename.
        (jHome isNil and:[dir exists]) ifTrue:[
            ((dir hasSuffix:'jar')
            or:[dir hasSuffix:'zip']) ifTrue:[
                jClasses add:dir.
            ] ifFalse:[

                "/ there must be either a classes directory,
                "/ or a classes.zip file ...
                (libDir := dir construct:'lib') exists ifTrue:[
                    (libDir construct:'classes.zip') exists ifTrue:[
                        jHome := aPath.
                        jClasses add:(libDir constructString:'classes.zip').
                    ] ifFalse:[
                        (libDir construct:'classes') exists ifTrue:[
                            (libDir construct:'classes') isDirectory ifTrue:[
                                jHome := aPath.
                                jClasses add:(libDir construct:'classes').
                            ]
                        ]
                    ]
                ].
            ].
        ].
    ].

    self javaHome:jHome.
    self classPath:jClasses.

    jHome isNil ifTrue:[
        Transcript showCR:'no java home directory found'.
    ] ifFalse:[
        Transcript showCR:'Found javaHome in: ' , jHome.

        (jSources := jHome asFilename construct:'source') exists ifFalse:[
            (jSources := jHome asFilename construct:'src') exists ifFalse:[
                (jSources := jHome asFilename construct:'sources') exists ifFalse:[
                    jSources := nil.
                ]
            ]
        ].

        jSources isNil ifTrue:[
            Transcript showCR:'no java source directory found'.
        ] ifFalse:[
            Transcript showCR:'Found javaSources in: ' , jSources pathName.
            self sourceDirectories:(Array with:jSources pathName).
        ].
    ].

    directoriesToSearch := OrderedCollection new.
    directoriesToSearch add:'/usr/local/java/moz3_0/lib_unix'.

    tryVA ifTrue:[        
        directoriesToSearch add:'C:\IBMVJava\EAB\bdk'.
    ].
    tryNetscape4_0 ifTrue:[        
        directoriesToSearch add:'C:\Programme\Netscape\Communicator\Program\Java\Classes\java40.jar'.
    ].
    tryBorland ifTrue:[        
        directoriesToSearch addAll:#(
                                        'C:\jbuilder2\lib\jbuilder.zip'
                                        'C:\jbuilder2\lib\jbcl2.0.jar'
                                        'C:\jbuilder2\lib\jbcl2.0-res.jar'
                                        'C:\jbuilder2\lib\swingall.jar'
                                        'C:\jbuilder2\lib\jgl3.1.0.jar'
                                        'C:\jbuilder2\lib\jctable.jar'
                                        'C:\jbuilder2\lib\jcchart.jar'
                                        'C:\jbuilder2\lib\jcbwt.jar'
                                    )
    ].

    directoriesToSearch do:[:aPath |
        |dir classDir|

        dir := aPath asFilename.
        (mozillaHome isNil and:[dir exists]) ifTrue:[
            ((dir hasSuffix:'jar') 
            or:[dir hasSuffix:'zip']) ifTrue:[
                Java addToClassPath:dir.
            ] ifFalse:[
                mozillaHome := dir.
                classDir := (dir construct:'classes').
                Java addToClassPath:classDir pathName.
                "/
                "/ care to only load mozilla classes from there ...
                "/ i.e. ignore the java/sun stuff found there.
                "/
                ExcludedClassPath add:(classDir construct:'java') pathName.
                ExcludedClassPath add:(classDir construct:'sun') pathName.
            ]
        ]
    ].
    self initializePrettyPrintStyle.

    "
     Java initialize.
     JavaVM initializeVM
    "

    "Modified: / 18.11.1998 / 01:30:55 / cg"
!

initializePrettyPrintStyle
    PrettyPrintStyle := IdentityDictionary new.
    PrettyPrintStyle  at:#accessAttribute put:(#color -> (Color red:0 green:0 blue:25)).
    PrettyPrintStyle  at:#className       put:(Array with:(#color -> Color black) with:#bold).
    PrettyPrintStyle  at:#methodName      put:(Array with:(#color -> Color black) with:#bold).
    PrettyPrintStyle  at:#code            put:(#color -> Color black).


     "
      Java initializePrettyPrintStyle
     "

    "Created: 1.8.1997 / 11:08:43 / cg"
    "Modified: 1.8.1997 / 11:09:58 / cg"
!

reinitAllClasses
     self markAllClassesUninitialized.
     self initAllClasses

     "
      Java reinitAllClasses
     "

    "Modified: / 4.1.1998 / 00:34:29 / cg"
!

reinitialize
    "/ all JavaThreads are lost on a restart (for now)

    FailedToLoadClasses := nil.
    Threads := nil.

    "
     Java reinitialize
    "

    "Created: / 26.8.1997 / 20:07:00 / cg"
    "Modified: / 27.4.1998 / 14:57:23 / cg"
!

startupJavaSystem
    |haveEventThread haveScreenUpdater|

    FailedToLoadClasses := nil.

    "/
    "/ check if already running
    "/

    haveEventThread := true.
    (JavaEventThread isNil or:[JavaEventThread isDead]) ifTrue:[
        haveEventThread := false
    ].

    haveScreenUpdater := false.
    haveEventThread ifTrue:[
        self threads do:[:aJavaThread |
            aJavaThread name = 'JAVA-Screen Updater' ifTrue:[
                aJavaThread isDead ifFalse:[
                    "/ already running
                    haveScreenUpdater := true
                ]
            ]
        ].
    ].

    (haveEventThread and:[haveScreenUpdater]) ifTrue:[
        ^ self
    ].

    JavaClass orderOfClassInits isNil ifTrue:[
        "/ the very first start ...
        'JAVA [info]: (re)initializing JAVA environment completely ...' infoPrintCR.

        JavaVM initializeVM.

    ] ifFalse:[
        (JavaEventThread isNil or:[JavaEventThread isDead]) ifTrue:[
            JavaVM initializeVM
"/        ] ifFalse:[
"/          'JAVA [info]: re-initializing JAVA classes ...' infoPrintCR.
"/          JavaVM reinitializeVM.
        ].
    ].    
    'JAVA [info]: done JAVA initialization.' infoPrintCR.

    "
     Java startupJavaSystem
    "

    "Modified: / 17.11.1998 / 21:43:27 / cg"
!

terminateAllThreads
    |myself threadsToKill|

    Threads isNil ifTrue:[
        ^ self
    ].

    myself := Processor activeProcess.

    threadsToKill := IdentitySet new.
    Threads do:[:aJavaThread |
        aJavaThread ~~ myself ifTrue:[
            (aJavaThread isNil or:[aJavaThread == 0]) ifFalse:[
                (aJavaThread isMemberOf:JavaProcess) ifTrue:[
                    aJavaThread isDead ifFalse:[
                        threadsToKill add:aJavaThread
                    ]
                ]
            ]
        ]
    ].
    threadsToKill do:[:aThread |
        aThread terminate
    ].
    Threads := nil.

    "
     Java terminateAllThreads
    "

    "Created: / 26.8.1997 / 19:57:40 / cg"
    "Modified: / 1.2.1998 / 20:11:56 / cg"
! !

!Java class methodsFor:'enumerating'!

allClasses
    ^ Classes ? #()

    "
    |if|

    if := Java at:'java.awt.GraphicsEnvironment'.
    Java allClasses select:[:aClass |
                                aClass hasInterface:if
                            ]
    "

    "Modified: / 28.1.1998 / 01:42:04 / cg"
!

allClassesDo:aBlock
    Classes notNil ifTrue:[
	Classes do:aBlock
    ]
! !

!Java class methodsFor:'object conversions'!

as_Float:aNumber
    "convert an ST-float into a Java Float"

    |i|

    i := (Java at:'java.lang.Float') new.
    i perform:#'<init>(F)V' with:(aNumber asShortFloat).
    ^ i

    "
     Java as_Float:1
     Java as_Float:3.14159
    "

    "Created: 7.8.1997 / 21:21:13 / cg"
    "Modified: 7.8.1997 / 21:22:05 / cg"
!

as_Hashtable:aDictionary
    "given a smalltalk dictionary, create and return
     a Java hashTable for it"

    |hashTable|

    hashTable := (self classForName:'java.util.Hashtable') new.
    aDictionary keysAndValuesDo:[:k :v |
	|sk sv jk jv|

	(sk := k) isSymbol ifTrue:[
	    sk := sk asString
	].
	(sv := v) isSymbol ifTrue:[
	    sv := sv asString
	].
	jk := self as_Object:sk.
	jv := self as_Object:sv.

	hashTable 
	    perform:#'put(Ljava/lang/Object;Ljava/lang/Object;)Ljava/lang/Object;'    
	    with:jk
	    with:jv.
    ].
    ^ hashTable

    "
     Java as_Hashtable:(Dictionary new
			   at:'hello' put:'Hallo';
			   at:'world' put:'Welt';       
			   yourself)
    "

    "Modified: / 14.1.1998 / 17:02:13 / cg"
!

as_Integer:anInteger
    "convert an ST-integer into a Java Integer"

    |i|

    i := (Java at:'java.lang.Integer') new.
    i perform:#'<init>(I)V' with:anInteger.
    ^ i

    "
     Java as_Integer:1
    "

    "Modified: 7.8.1997 / 21:19:37 / cg"
    "Created: 7.8.1997 / 21:21:13 / cg"
!

as_Object:anObject
    "convert an ST-Object into a Java Object"

    anObject isString ifTrue:[
	^ self as_String:anObject
    ].
    anObject isInteger ifTrue:[
	^ self as_Integer:anObject
    ].

    self halt.

    "
     Java as_Object:'hello world'
    "

    "Created: 7.8.1997 / 21:15:38 / cg"
    "Modified: 7.8.1997 / 21:20:07 / cg"
!

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

    |str count offs start stop|

    "/ count := aJavaString instVarNamed:'count'.
    count := aJavaString instVarAt:(JavaSlotIndexCache string_slot_count).

    "/ str := aJavaString instVarNamed:'value'
    str := aJavaString instVarAt:(JavaSlotIndexCache string_slot_value).

    str size == count ifTrue:[
        ^ str
    ].

    "/ offs := (aJavaString instVarNamed:'offset').
    offs := (aJavaString instVarAt:(JavaSlotIndexCache string_slot_offset)).

    "/ start := offs + 1.
    start := offs + 1.

    "/ stop := start + (aJavaString instVarNamed:'count') - 1.
    stop := start + count - 1.

    "/ ^ ((aJavaString instVarNamed:'value') copyFrom:start to:stop) asString
    ^ (str copyFrom:start to:stop) asString

    "Created: / 8.8.1997 / 12:02:55 / cg"
    "Modified: / 3.12.1998 / 13:43:51 / cg"
!

as_String:aString
    "convert an ST-String into a Java String"

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

    |s|

    s := Java_lang_String basicNew.
    s instVarNamed:'value'  put: aString.
    s instVarNamed:'offset' put: 0.
    s instVarNamed:'count'  put: aString size.
    ^ s

    "
     Java as_String:'hello world'
    "

    "Created: 7.8.1997 / 21:15:49 / cg"
    "Modified: 7.8.1997 / 21:19:37 / cg"
!

as_URL:aString
    "convert an ST-String into a Java String"

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

    |u|

    u := (self at:'java.net.URL') newCleared.
    u perform:#'<init>(Ljava/lang/String;)V' with:(self as_String:aString).
    ^ u

    "
     Java as_URL:'http://www.altavista.com'
     Java as_URL:'file:/foo/bar'
    "

    "Created: / 7.8.1997 / 21:15:49 / cg"
    "Modified: / 5.11.1998 / 08:35:28 / cg"
! !

!Java class methodsFor:'queries'!

smalltalkClassFor:typeRef
self halt.
"/    (typeString startsWith:'[[') ifTrue:[
"/        ^ Array
"/    ].
"/    (typeString startsWith:'[F') ifTrue:[
"/        ^ FloatArray
"/    ].
    self halt.

    "Modified: 7.4.1997 / 13:33:46 / cg"
!

smalltalkDerefType:typeString
    (typeString startsWith:'[') ifTrue:[
	^ typeString copyFrom:2
    ].
    self halt.

    "Modified: 7.4.1997 / 13:13:24 / cg"
! !

!Java class methodsFor:'registering java classes'!

at:aJavaName
    "search & return for a class by name;
     if there is no such class, return nil.
     The argument, aJavaName may be either an internal name
     (sep'd by slashes) or an external name (sep'd by periods).
     The 'java/lang' standard packages prefix may be ommitted."

    |sym nm cls|

    Classes isNil ifTrue:[^ nil].

    sym := aJavaName asSymbolIfInterned.
    sym notNil ifTrue:[
        cls := Classes at:sym ifAbsent:nil.
        cls notNil ifTrue:[^ cls].
    ].

    nm := aJavaName.
    (nm includes:$.) ifTrue:[
        nm := (nm asString copyReplaceAll:$. with:$/).
        sym := nm asSymbolIfInterned.
        sym notNil ifTrue:[
            cls := Classes at:sym ifAbsent:nil.
            cls notNil ifTrue:[^ cls].
        ].
    ].
        
    (nm includes:$/) ifFalse:[
        "/
        "/ try java.lang.Foo
        "/
        nm := 'java/lang/' , nm.
        sym := nm asSymbolIfInterned.
        sym notNil ifTrue:[
            cls := Classes at:sym ifAbsent:nil.
            cls notNil ifTrue:[^ cls].
        ].
    ].

    ^ nil

    "
     Java at:'java/lang/String' 
     Java at:'java.lang.String'
     Java at:'String'          
     Java at:'System'            
     Java at:'Foo'               
    "

    "Modified: / 18.7.1998 / 22:55:16 / cg"
!

at:aJavaName put:aJavaClass
    |nameSymbol|

    Classes isNil ifTrue:[
	Classes := IdentityDictionary new.
    ].

    nameSymbol := aJavaName asSymbol.
    (Classes includesKey:nameSymbol) ifTrue:[
	('JAVA: class ' , aJavaName , ' is already loaded') infoPrintCR.
	self updateClassRefsFrom:(Classes at:nameSymbol) to:aJavaClass.
    ].

    Classes at:nameSymbol put:aJavaClass.
    nameSymbol == #'java/lang/String' ifTrue:[
	Java_lang_String := aJavaClass
    ].

"/    UnresolvedClassRefs notNil ifTrue:[
"/        UnresolvedClassRefs do:[:toResolve |
"/        ]
"/    ].

    self changed:#classes

    "Created: 17.4.1996 / 23:29:31 / cg"
    "Modified: 7.8.1997 / 19:15:58 / cg"
!

flushAllJavaResources
    self flushClasses.

    ObjectMemory allObjectsDo:[:someObject |
        someObject isBehavior ifTrue:[
            someObject isJavaClass ifTrue:[
                someObject setConstantPool:nil.
                someObject setInterfaces:nil.
                someObject setMethodDictionary:(MethodDictionary new).
'JAVA [info]: flushing ' print. someObject fullName printCR.
            ]
        ].
"/        (someObject isKindOf:JavaMethod) ifTrue:[
"/            someObject setJavaClass:nil.
"/            someObject setExceptionTable:nil.
"/        ].
        (someObject isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
            someObject constantPool:nil
        ].
    ].
    self flushClasses

    "
     Java flushAllJavaResources
    "

    "Modified: / 16.10.1998 / 01:21:30 / cg"
!

flushClasses
    Classes := UnresolvedClassRefs := nil.
    Smalltalk keys copy do:[:aKey | 
        (aKey startsWith:'JAVA::') ifTrue:[ Smalltalk removeKey:aKey ]
    ].
    Java_lang_String := Java_lang_Class := nil.
    JavaVM releaseAllJavaResources.
    JavaUnresolvedConstant flushPatchLists.
    Debugger newDebugger.
    ObjectMemory flushCaches.

    "
     Java flushClasses
    "

    "Modified: / 5.11.1998 / 20:12:47 / cg"
!

markAllClassesUninitialized
    self allClassesDo:[:aJavaClass |
	aJavaClass markUninitialized
    ].

    "
     Java markAllClassesUninitialized
    "
!

rememberUnresolved:anUnresolvedClassRef
    ('JAVA: remember unresolved class: ' , anUnresolvedClassRef fullName) infoPrintCR.

    UnresolvedClassRefs isNil ifTrue:[
        UnresolvedClassRefs := Dictionary new.
    ].
    UnresolvedClassRefs 
        at:anUnresolvedClassRef fullName
        put:anUnresolvedClassRef

    "Created: / 18.4.1996 / 00:05:31 / cg"
    "Modified: / 19.10.1998 / 20:57:44 / cg"
!

removeClass:aJavaClass
    "/ remove it from myself

    |javaName sym nm cls p ns|

    javaName := aJavaClass fullName.

    sym := javaName asSymbolIfInterned.
    sym notNil ifTrue:[
        cls := Classes at:sym ifAbsent:nil.
    ].
    cls isNil ifTrue:[
        nm := javaName.
        (nm includes:$.) ifTrue:[
            "/
            "/ try pckg/.../name
            "/
            nm := (nm asString copyReplaceAll:$. with:$/).
            sym := nm asSymbolIfInterned.
            sym notNil ifTrue:[
                cls := Classes at:sym ifAbsent:nil.
            ].
        ].
    ].
    (cls notNil and:[cls == aJavaClass]) ifTrue:[
        Classes removeKey:sym.
        self updateClassRefsFrom:aJavaClass to:nil.
    ].
    Smalltalk removeKey:('JAVA::' , javaName) asSymbol.

    "/ remove myself from the JAVA::-::-:: namespace
    "/ (which exists for convenient smalltalk access only)

    p := aJavaClass nameSpacePath.
    p knownAsSymbol ifTrue:[
        ns := Smalltalk at:p asSymbol.
        (ns notNil and:[ns isNamespace]) ifTrue:[
            Smalltalk removeKey:(p , '::' , aJavaClass name) asSymbol
        ]
    ].

    "Modified: / 19.10.1998 / 20:58:49 / cg"
!

unresolvedClassRefFor:aClassName
    UnresolvedClassRefs isNil ifTrue:[^ nil].
    ^ UnresolvedClassRefs at:aClassName ifAbsent:nil.

    "Modified: / 19.10.1998 / 20:56:46 / cg"
!

updateClassRefsFrom:oldClass to:newClass
    "update all references to oldClass to now refer to newClass.
     sent, when a class is reloaded"

    newClass notNil ifTrue:[
	"/
	"/ kludge: the new class might have been resolved with the oldClass ...
	"/
	newClass constantPool 
	    updateClassRefsFrom:oldClass to:newClass.
    ].

    self allClassesDo:[:aJavaClass |
	aJavaClass updateClassRefsFrom:oldClass to:newClass
    ].

    "Created: 26.3.1997 / 13:49:20 / cg"
    "Modified: 12.8.1997 / 03:04:44 / cg"
! !

!Java class methodsFor:'source management'!

classSourceOf:aClass
    |package dirName binary sourceFileName sourceFile dirHolder fileName path
     loader codeBaseURL protocol dir file|

    aClass isNil ifTrue:[
        ^ nil
    ].

    "/ first, look in the directory, where the binary
    "/ was loaded from.

    binary := aClass binaryFile.
    binary notNil ifTrue:[
        binary := binary asFilename.
        aClass sourceFile notNil ifTrue:[
            sourceFileName := binary directory constructString:(aClass sourceFile).
            sourceFileName asFilename exists ifFalse:[
                sourceFileName := nil.
            ]
        ].
        sourceFileName isNil ifTrue:[
            sourceFileName := binary withSuffix:'java'.
        ].
        sourceFile := sourceFileName asFilename.
    ] ifFalse:[
        "/ maybe it was loaded by a java classLoader ...
        (loader := aClass classLoader) notNil ifTrue:[
            (codeBaseURL := loader instVarNamed:'codeBaseURL') notNil ifTrue:[
                (protocol := codeBaseURL instVarNamed:'protocol') notNil ifTrue:[
                    (Java as_ST_String:protocol) = 'file' ifTrue:[
                        dirName := Java as_ST_String:(codeBaseURL instVarNamed:'file').
                        dirName asFilename exists ifTrue:[
                            aClass sourceFile notNil ifTrue:[
                                sourceFileName := dirName asFilename construct:aClass sourceFile.
                                sourceFile := sourceFileName asFilename.
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ].
    sourceFile notNil ifTrue:[
        sourceFile exists ifFalse:[
            binary notNil ifTrue:[
                sourceFileName := binary withSuffix:'jav'.
                sourceFile := sourceFileName asFilename.
                sourceFile exists ifFalse:[
                    sourceFileName := binary withSuffix:'JAV'.
                    sourceFile := sourceFileName asFilename.
                    sourceFile exists ifFalse:[
                        sourceFileName := binary withSuffix:'JAVA'.
                        sourceFile := sourceFileName asFilename.
                    ].
                ].
            ]
        ].
    ].

    "/ special case: there were multiple classes in a single
    "/ source file.

    binary notNil ifTrue:[
        binary withoutSuffix baseName ~= aClass sourceFile asFilename withoutSuffix baseName ifTrue:[
            'JAVA: trouble extracting fileName: ' print.
            binary withoutSuffix baseName print. ' vs. ' print.
            aClass sourceFile asFilename withoutSuffix baseName printCR.
        ].
    ].

    "/ if that fails, look in standard places

    (sourceFile isNil or:[sourceFile exists not]) ifTrue:[
        package := aClass package.

        sourceFileName := aClass sourceFile.
        sourceFileName isNil ifTrue:[^nil].

        sourceFile := sourceFileName asFilename.
        sourceFile exists ifFalse:[
            "/
            "/ mhmh - look for its directory
            "/
            dirName := sourceFile directoryName.
            fileName := sourceFile baseName.

            (dirName asFilename exists 
            and:[(dirName asFilename construct:(package , '/' , fileName)) exists])
            ifFalse:[
                (dirName asFilename exists 
                and:[(dirName asFilename construct:(fileName)) exists])
                ifFalse:[
                    dirName := self findSourceDirOf:fileName inPackage:package.

    "/                [dirName isNil] whileTrue:[
    "/                    dirName := Dialog requestDirectoryName:'top directory for ' , package , '/' , fileName.
    "/                    (dirName isNil or:[dirName isEmpty]) ifTrue:[^ self].
    "/                ].
                ].
            ].

            (dirName notNil and:[dirName asFilename exists]) ifTrue:[
                path := (dirName asFilename construct:(package , '/' , fileName)) asFilename.
                path exists ifFalse:[
                    path := (dirName asFilename construct:(fileName)) asFilename.
                ].
            ].

            (path notNil and:[path exists]) ifFalse:[
                ^ nil
            ].

            sourceFile := path asFilename.
        ].
    ].
    ^ (sourceFile contentsOfEntireFile).

    "Modified: / 15.10.1998 / 23:38:18 / cg"
!

findSourceDirOf:fileName inPackage:aPackage
    SourceDirectories notNil ifTrue:[
        SourceDirectories do:[:aDir |
            aPackage notNil ifTrue:[
                (aDir asFilename construct:('/' , aPackage , '/' , fileName))
                asFilename exists ifTrue:[
                    ^ aDir 
                ].
            ].
            (aDir asFilename construct:('/' , fileName))
            asFilename exists ifTrue:[
                ^ aDir 
            ].
        ]
    ].
    ^ nil

    "Modified: / 29.3.1998 / 21:46:40 / cg"
! !

!Java class methodsFor:'starting apps'!

executeMainOf:aClass
    "execute main of aClass in a separate thread and wait until that thread
     has terminated."

    |p|

    p := self javaProcessForMainOf:aClass.
    p notNil ifTrue:[
        p resume.
        Object abortSignal handle:[:ex |
            p terminate.
            ex reject.
        ] do:[
            p waitUntilTerminated
        ].
    ]

    "Modified: / 15.1.1998 / 02:15:13 / cg"
    "Created: / 15.1.1998 / 17:14:55 / cg"
!

executeMainOf:aClass withArgumentString:commandLineString
    "execute main of aClass in a separate thread and wait until that thread
     has terminated."

    |p|

    p := self javaProcessForMainOf:aClass argumentString:commandLineString.
    p notNil ifTrue:[
        p resume.
        Object abortSignal handle:[:ex |
            p terminate.
            ex reject.
        ] do:[
            p waitUntilTerminated
        ].
    ]

    "Modified: / 5.2.1998 / 00:38:22 / cg"
    "Created: / 5.2.1998 / 00:40:38 / cg"
!

javaProcessForMainOf:aJavaClass
    "ask for a commandLine, create a java process to invoke
     its main and return it. The process is not scheduled for
     execution."

    |args|

    args := Dialog 
		request:'argument string:' 
		initialAnswer:LastArgumentString ? ''
		onCancel:nil.
    args isNil ifTrue:[^ nil].

    LastArgumentString := args.

    ^ self javaProcessForMainOf:aJavaClass argumentString:args.

    "Created: / 15.8.1997 / 04:51:46 / cg"
    "Modified: / 9.1.1998 / 18:01:47 / cg"
!

javaProcessForMainOf:aJavaClass argumentString:argString
    "create a java process, ready to invoke the classes main
     method. Returns the process - ready to run but not yet resumed"

    |p argStringArray t|

    JavaVM initializeVMIfNoEventThreadRunning.
    (Java at:'java.lang.System') instVarNamed:'security' put:nil.

    argString isEmpty ifTrue:[
        argStringArray := #()
    ] ifFalse:[
        argStringArray := argString asCollectionOfWords asArray 
                                collect:[:s | Java as_String:s].
    ].

    p := JavaProcess 
            for:[
                    aJavaClass 
                        perform:#'main([Ljava/lang/String;)V'
                        with:argStringArray.
                ]
            priority:(Processor activePriority - 1).

    p name:(aJavaClass fullName , '::main()').
    ^ p

    "Created: / 15.8.1997 / 04:41:20 / cg"
    "Modified: / 5.11.1998 / 21:00:09 / cg"
! !

!Java class methodsFor:'documentation'!

version
    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.82 1998/12/03 13:09:37 cg Exp $'
! !
Java initialize!