no reinit - multiple browsers
authorcg
Thu, 28 Aug 1997 02:34:59 +0000
changeset 248 964ad5f9e8bc
parent 247 67dd93db3d80
child 249 94833284dec6
no reinit - multiple browsers
Java.st
JavaView.st
--- a/Java.st	Fri Aug 22 13:15:19 1997 +0000
+++ b/Java.st	Thu Aug 28 02:34:59 1997 +0000
@@ -1,8 +1,10 @@
+'From Smalltalk/X, Version:3.1.9 on 26-aug-1997 at 8:10:05 pm'                  !
+
 Object subclass:#Java
 	instanceVariableNames:''
 	classVariableNames:'Classes UnresolvedClassRefs ClassPath SourceDirectories JavaHome
 		Java_lang_String Java_lang_Class PrettyPrintStyle
-		LastArgumentString'
+		LastArgumentString Threads'
 	poolDictionaries:''
 	category:'Java-Support'
 !
@@ -17,8 +19,8 @@
 
     cls := self at:aString.
     cls isNil ifTrue:[
-        ('JAVA [info]: late class loading: ' , aString) infoPrintCR.
-        cls := JavaClassReader loadClass:aString.
+	('JAVA [info]: late class loading: ' , aString) infoPrintCR.
+	cls := JavaClassReader loadClass:aString.
     ].
     ^ cls
 
@@ -32,7 +34,7 @@
 
 java_lang_Class
     Java_lang_Class isNil ifTrue:[
-        Java_lang_Class := self at:'java.lang.Class'
+	Java_lang_Class := self at:'java.lang.Class'
     ].
     ^ Java_lang_Class
 
@@ -42,7 +44,7 @@
 
 java_lang_String
     Java_lang_String isNil ifTrue:[
-        Java_lang_String := self at:'java.lang.String'
+	Java_lang_String := self at:'java.lang.String'
     ].
     ^ Java_lang_String
 
@@ -54,13 +56,23 @@
     ^ 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
+	ClassPath add:aPath
     ]
 
     "Modified: 7.2.1997 / 19:23:55 / cg"
@@ -69,7 +81,7 @@
 
 addToSourcePath:aPath
     (SourceDirectories includes:aPath) ifFalse:[
-        SourceDirectories add:aPath
+	SourceDirectories add:aPath
     ]
 
     "Modified: 7.2.1997 / 19:23:55 / cg"
@@ -103,7 +115,7 @@
 
 removeFromClassPath:aPath
     (ClassPath includes:aPath) ifTrue:[
-        ClassPath remove:aPath
+	ClassPath remove:aPath
     ]
 
     "Modified: 7.2.1997 / 19:23:55 / cg"
@@ -112,7 +124,7 @@
 
 removeFromSourcePath:aPath
     (SourceDirectories includes:aPath) ifTrue:[
-        SourceDirectories remove:aPath
+	SourceDirectories remove:aPath
     ]
 
     "Modified: 7.2.1997 / 19:23:55 / cg"
@@ -128,9 +140,9 @@
 
     "
      Java
-        sourceDirectories:#(
-                            '/phys/ibm3/java/src'
-                           )
+	sourceDirectories:#(
+			    '/phys/ibm3/java/src'
+			   )
     "
 
 
@@ -145,14 +157,14 @@
 
      system := self classForName:'java.lang.System'.
      system isInitialized ifFalse:[
-         system classInit.
-         self initSystemClass.
+	 system classInit.
+	 self initSystemClass.
      ].
 
      self allClassesDo:[:cls |
-        cls isInitialized ifFalse:[
-            cls classInit
-        ]
+	cls isInitialized ifFalse:[
+	    cls classInit
+	]
      ]
 
     "Modified: 3.8.1997 / 19:42:15 / cg"
@@ -160,7 +172,7 @@
 
 initAllStaticFields
      self allClassesDo:[:cls |
-        cls initializeStaticFields
+	cls initializeStaticFields
      ]
 
 !
@@ -170,15 +182,15 @@
 
     system := Java at:'java.lang.System'.
     (system implements:#'initializeSystemClass()V') ifTrue:[
-        system invokeStatic:#'initializeSystemClass()V'.
+	system invokeStatic:#'initializeSystemClass()V'.
     ].
 
     "
      Java initSystemClass
 
      (Java at:'java.lang.System') 
-        invoke:#'getProperty(Ljava/lang/String;)Ljava/lang/String;'
-        with:(Java as_String:'java.home')
+	invoke:#'getProperty(Ljava/lang/String;)Ljava/lang/String;'
+	with:(Java as_String:'java.home')
     "
 
     "Modified: 12.8.1997 / 04:30:48 / cg"
@@ -202,12 +214,11 @@
     ].
     self initializePrettyPrintStyle.
 
-
      "
       Java initialize
      "
 
-    "Modified: 18.8.1997 / 22:30:43 / cg"
+    "Modified: 26.8.1997 / 20:06:19 / cg"
 !
 
 initializePrettyPrintStyle
@@ -229,6 +240,73 @@
 reinitAllClasses
      self markAllClassesUninitialized.
      self initAllClasses
+!
+
+reinitialize
+    "/ all JavaThreads are lost on a restart (for now)
+
+    Threads := nil.
+
+     "
+      Java reinitialize
+     "
+
+    "Modified: 18.8.1997 / 22:30:43 / cg"
+    "Created: 26.8.1997 / 20:07:00 / cg"
+!
+
+startupJavaSystem
+    "/
+    "/ check if already running
+    "/
+    self threads do:[:aJavaThread |
+        aJavaThread name = 'JAVA-Screen Updater' ifTrue:[
+            "/ already running
+            ^ self
+        ]
+    ].
+
+    'JAVA [info]: (re)initializing JAVA environment completely ...' infoPrintCR.
+    JavaInterpreter releaseAllJavaResources.
+    self initAllStaticFields.
+    self markAllClassesUninitialized.
+    self initAllStaticFields.
+    self reinitAllClasses.
+    'JAVA [info]: done JAVA initialization.' infoPrintCR.
+
+     "
+      Java startupJavaSystem
+     "
+
+    "Modified: 26.8.1997 / 20:00:07 / cg"
+!
+
+terminateAllThreads
+    |myself|
+
+    Threads isNil ifTrue:[
+        ^ self
+    ].
+
+    myself := Processor activeProcess.
+
+    Threads do:[:aJavaThread |
+        aJavaThread ~~ myself ifTrue:[
+            (aJavaThread isNil or:[aJavaThread == 0]) ifFalse:[
+                (aJavaThread isMemberOf:JavaProcess) ifTrue:[
+                    aJavaThread terminate
+                ]
+            ]
+        ]
+    ].
+    Threads := nil.
+
+    "
+     Java terminateAllThreads
+    "
+
+    "Modified: 21.8.1997 / 16:25:25 / cg"
+    "Created: 26.8.1997 / 19:57:40 / cg"
 ! !
 
 !Java class methodsFor:'enumerating'!
@@ -241,7 +319,7 @@
 
 allClassesDo:aBlock
     Classes notNil ifTrue:[
-        Classes do:aBlock
+	Classes do:aBlock
     ]
 ! !
 
@@ -270,23 +348,23 @@
 
     hashTable := (self classForName:'java.util.Hashtable') new.
     aDictionary keysAndValuesDo:[:k :v |
-        |jk jv|
+	|jk jv|
 
-        jk := self as_Object:k.
-        jv := self as_Object:v.
+	jk := self as_Object:k.
+	jv := self as_Object:v.
 
-        hashTable 
-            invoke:#'put(Ljava/lang/Object;Ljava/lang/Object;)Ljava/lang/Object;'    
-            with:jk
-            with:jv.
+	hashTable 
+	    invoke:#'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)
+			   at:'hello' put:'Hallo';
+			   at:'world' put:'Welt';       
+			   yourself)
     "
 
     "Modified: 7.8.1997 / 21:23:55 / cg"
@@ -313,10 +391,10 @@
     "convert an ST-Object into a Java Object"
 
     anObject isString ifTrue:[
-        ^ self as_String:anObject
+	^ self as_String:anObject
     ].
     anObject isInteger ifTrue:[
-        ^ self as_Integer:anObject
+	^ self as_Integer:anObject
     ].
 
     self halt.
@@ -342,7 +420,7 @@
 
     "/ ^ ((aJavaString instVarNamed:'value') copyFrom:start to:stop) asString
     ^ ((aJavaString instVarAt:(JavaSlotIndexCache string_slot_value)) 
-                copyFrom:start to:stop) asString
+		copyFrom:start to:stop) asString
 
     "Modified: 8.2.1997 / 13:46:22 / cg"
     "Created: 8.8.1997 / 12:02:55 / cg"
@@ -406,7 +484,7 @@
 
 smalltalkDerefType:typeString
     (typeString startsWith:'[') ifTrue:[
-        ^ typeString copyFrom:2
+	^ typeString copyFrom:2
     ].
     self halt.
 
@@ -428,30 +506,30 @@
 
     sym := aJavaName asSymbolIfInterned.
     sym notNil ifTrue:[
-        cls := Classes at:sym ifAbsent:nil.
-        cls notNil ifTrue:[^ cls].
+	cls := Classes at:sym ifAbsent:nil.
+	cls notNil ifTrue:[^ cls].
     ].
 
     nm := aJavaName.
     (nm includes:$.) ifTrue:[
-        nm := (nm asString copy replaceAll:$. by:$/).
-        sym := nm asSymbolIfInterned.
-        sym notNil ifTrue:[
-            cls := Classes at:sym ifAbsent:nil.
-            cls notNil ifTrue:[^ cls].
-        ].
+	nm := (nm asString copy replaceAll:$. by:$/).
+	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].
-        ].
+	"/
+	"/ 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
@@ -469,18 +547,18 @@
     |nameSymbol|
 
     Classes isNil ifTrue:[
-        Classes := IdentityDictionary new.
+	Classes := IdentityDictionary new.
     ].
 
     nameSymbol := aJavaName asSymbol.
     (Classes includesKey:nameSymbol) ifTrue:[
-        ('JAVA: class ' , aJavaName , ' is already loaded') infoPrintCR.
-        self updateClassRefsFrom:(Classes at:nameSymbol) to:aJavaClass.
+	('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
+	Java_lang_String := aJavaClass
     ].
 
 "/    UnresolvedClassRefs notNil ifTrue:[
@@ -498,21 +576,21 @@
     self flushClasses.
 
     ObjectMemory allObjectsDo:[:someObject |
-        someObject isBehavior ifTrue:[
-            someObject isJavaClass ifTrue:[
-                someObject setConstantPool:nil.
-                someObject setInterfaces:nil.
-                someObject setMethodDictionary:(MethodDictionary new).
+	someObject isBehavior ifTrue:[
+	    someObject isJavaClass ifTrue:[
+		someObject setConstantPool:nil.
+		someObject setInterfaces:nil.
+		someObject setMethodDictionary:(MethodDictionary new).
 someObject fullName printCR.
-            ]
-        ].
-        (someObject isMemberOf:JavaMethod) ifTrue:[
-            someObject setJavaClass:nil.
-            someObject setExceptionTable:nil.
-        ].
-        (someObject isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
-            someObject constantPool:nil
-        ].
+	    ]
+	].
+	(someObject isMemberOf:JavaMethod) ifTrue:[
+	    someObject setJavaClass:nil.
+	    someObject setExceptionTable:nil.
+	].
+	(someObject isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
+	    someObject constantPool:nil
+	].
     ].
     self flushClasses
 
@@ -526,7 +604,7 @@
 flushClasses
     Classes := UnresolvedClassRefs := nil.
     Smalltalk keys copy do:[:aKey | 
-        (aKey startsWith:'JAVA::') ifTrue:[ Smalltalk removeKey:aKey ]
+	(aKey startsWith:'JAVA::') ifTrue:[ Smalltalk removeKey:aKey ]
     ].
     Java_lang_String := Java_lang_Class := nil.
     JavaInterpreter releaseAllJavaResources.
@@ -541,7 +619,7 @@
 
 markAllClassesUninitialized
     self allClassesDo:[:aJavaClass |
-        aJavaClass markUninitialized
+	aJavaClass markUninitialized
     ].
 
     "
@@ -553,7 +631,7 @@
     ('JAVA: remember unresolved class: ' , anUnresolvedClassRef fullName) infoPrintCR.
 
     UnresolvedClassRefs isNil ifTrue:[
-        UnresolvedClassRefs := Set new.
+	UnresolvedClassRefs := Set new.
     ].
     UnresolvedClassRefs add:anUnresolvedClassRef
 
@@ -570,24 +648,24 @@
 
     sym := javaName asSymbolIfInterned.
     sym notNil ifTrue:[
-        cls := Classes at:sym ifAbsent:nil.
+	cls := Classes at:sym ifAbsent:nil.
     ].
     cls isNil ifTrue:[
-        nm := javaName.
-        (nm includes:$.) ifTrue:[
-            "/
-            "/ try pckg/.../name
-            "/
-            nm := (nm asString copy replaceAll:$. by:$/).
-            sym := nm asSymbolIfInterned.
-            sym notNil ifTrue:[
-                cls := Classes at:sym ifAbsent:nil.
-            ].
-        ].
+	nm := javaName.
+	(nm includes:$.) ifTrue:[
+	    "/
+	    "/ try pckg/.../name
+	    "/
+	    nm := (nm asString copy replaceAll:$. by:$/).
+	    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.
+	Classes removeKey:sym.
+	self updateClassRefsFrom:aJavaClass to:nil.
     ].
     Smalltalk removeKey:('JAVA::' , aJavaClass fullName) asSymbol.
 
@@ -604,15 +682,15 @@
      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.
+	"/
+	"/ 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
+	aJavaClass updateClassRefsFrom:oldClass to:newClass
     ].
 
     "Created: 26.3.1997 / 13:49:20 / cg"
@@ -625,7 +703,7 @@
     |package dirName binary sourceFileName sourceFile dirHolder fileName path|
 
     aClass isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
     package := aClass package.
 
@@ -634,77 +712,77 @@
 
     binary := aClass binaryFile.
     binary notNil ifTrue:[
-        binary := binary asFilename.
-        sourceFileName := binary withSuffix:'java'.
-        sourceFile := sourceFileName asFilename.
+	binary := binary asFilename.
+	sourceFileName := binary withSuffix:'java'.
+	sourceFile := sourceFileName asFilename.
     ].
 
     sourceFile notNil ifTrue:[
-        sourceFile exists ifFalse:[
-            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.
-                ].
-            ].
-        ].
+	sourceFile exists ifFalse:[
+	    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.
-        ].
+	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:[
-        sourceFileName := aClass sourceFile.
-        sourceFile := sourceFileName asFilename.
-        sourceFile exists ifFalse:[
-            "/
-            "/ mhmh - look for its directory
-            "/
-            dirName := sourceFile directoryName.
-            fileName := sourceFile baseName.
+	sourceFileName := aClass sourceFile.
+	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 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.
-                ].
-            ].
+	    (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
-            ].
+	    (path notNil and:[path exists]) ifFalse:[
+		^ nil
+	    ].
 
-            sourceFile := path asFilename.
-        ].
+	    sourceFile := path asFilename.
+	].
     ].
     ^ (sourceFile contentsOfEntireFile).
 
@@ -713,16 +791,16 @@
 
 findSourceDirOf:fileName inPackage:aPackage
     SourceDirectories notNil ifTrue:[
-        SourceDirectories do:[:aDir |
-            (aDir asFilename construct:('/' , aPackage , '/' , fileName))
-            asFilename exists ifTrue:[
-                ^ aDir 
-            ].
-            (aDir asFilename construct:('/' , fileName))
-            asFilename exists ifTrue:[
-                ^ aDir 
-            ].
-        ]
+	SourceDirectories do:[:aDir |
+	    (aDir asFilename construct:('/' , aPackage , '/' , fileName))
+	    asFilename exists ifTrue:[
+		^ aDir 
+	    ].
+	    (aDir asFilename construct:('/' , fileName))
+	    asFilename exists ifTrue:[
+		^ aDir 
+	    ].
+	]
     ].
     ^ nil
 
@@ -739,9 +817,9 @@
     |args|
 
     args := Dialog 
-                request:'argument string:' 
-                initialAnswer:LastArgumentString
-                onCancel:nil.
+		request:'argument string:' 
+		initialAnswer:LastArgumentString
+		onCancel:nil.
     args isNil ifTrue:[^ nil].
 
     LastArgumentString := args.
@@ -759,23 +837,23 @@
     |p argStringArray t|
 
     argString isEmpty ifTrue:[
-        argStringArray := #()
+	argStringArray := #()
     ] ifFalse:[
-        argStringArray := argString asCollectionOfWords asArray 
-                                collect:[:s | Java as_String:s].
+	argStringArray := argString asCollectionOfWords asArray 
+				collect:[:s | Java as_String:s].
     ].
 
     (Java at:'java.lang.System') instVarNamed:'security' put:nil.
 
     p := JavaProcess 
-            for:[
+	    for:[
 
-                    aJavaClass 
-                        invoke:#'main'
-                        signature:#'([Ljava/lang/String;)V'
-                        with:argStringArray
-                ]
-            priority:(Processor activePriority - 1).
+		    aJavaClass 
+			invoke:#'main'
+			signature:#'([Ljava/lang/String;)V'
+			with:argStringArray
+		]
+	    priority:(Processor activePriority - 1).
 
     p name:(aJavaClass fullName , '::main()').
     ^ p
@@ -787,6 +865,6 @@
 !Java class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.44 1997/08/18 20:32:30 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.45 1997/08/28 02:33:53 cg Exp $'
 ! !
 Java initialize!
--- a/JavaView.st	Fri Aug 22 13:15:19 1997 +0000
+++ b/JavaView.st	Thu Aug 28 02:34:59 1997 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.1.9 on 23-aug-1997 at 4:27:17 pm'                  !
+
 View subclass:#JavaView
 	instanceVariableNames:'eventReceiver updateRegions javaPeer'
 	classVariableNames:''
@@ -46,18 +48,68 @@
 
 !JavaView methodsFor:'event handling'!
 
+buttonMotion:state x:x y:y
+    |ev|
+
+    eventReceiver notNil ifTrue:[
+        ev := WindowEvent buttonEvent
+                 for:self
+                 type:#buttonMotion:x:y:
+                 arguments:(Array with:state with:x with:y).
+        eventReceiver processEvent:ev.
+    ].
+
+    "Modified: 21.8.1997 / 19:40:40 / cg"
+    "Created: 23.8.1997 / 03:13:38 / cg"
+!
+
+buttonPress:button x:x y:y
+    |ev|
+
+    eventReceiver notNil ifTrue:[
+        ev := WindowEvent buttonEvent
+                 for:self
+                 type:#buttonPress:x:y:
+                 arguments:(Array with:button with:x with:y).
+        eventReceiver processEvent:ev.
+    ].
+
+    "Created: 21.8.1997 / 19:37:57 / cg"
+    "Modified: 21.8.1997 / 19:40:40 / cg"
+!
+
+buttonRelease:button x:x y:y
+    |ev|
+
+    eventReceiver notNil ifTrue:[
+        ev := WindowEvent buttonEvent
+                 for:self
+                 type:#buttonRelease:x:y:
+                 arguments:(Array with:button with:x with:y).
+        eventReceiver processEvent:ev.
+    ].
+
+    "Modified: 21.8.1997 / 19:40:40 / cg"
+    "Created: 23.8.1997 / 02:22:23 / cg"
+!
+
 exposeX:x y:y width:w height:h
+    |ev|
+
     updateRegions isNil ifTrue:[
         updateRegions := OrderedCollection new.
     ].
     updateRegions add:(Rectangle left:x top:y width:w height:h).
     eventReceiver notNil ifTrue:[
-        eventReceiver exposeX:x y:y width:w height:h view:self
+        ev := WindowEvent 
+                damageFor:self 
+                rectangle:(Rectangle left:x top:y width:w height:h). 
+        eventReceiver processEvent:ev.
     ].
     super exposeX:x y:y width:w height:h
 
     "Created: 18.8.1997 / 15:00:24 / cg"
-    "Modified: 18.8.1997 / 18:14:53 / cg"
+    "Modified: 21.8.1997 / 19:39:06 / cg"
 ! !
 
 !JavaView methodsFor:'initialization'!
@@ -75,5 +127,5 @@
 !JavaView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaView.st,v 1.5 1997/08/21 15:00:45 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaView.st,v 1.6 1997/08/28 02:34:59 cg Exp $'
 ! !