woohoo! It's my first squeak/morphic alpha code!

Robert Withers withers at vnet.net
Fri Jan 28 07:06:02 UTC 2000


And it prolly isn't very nice, so be a bit careful if you are inclined
to try it.  Like use a scratch image, right?  I'd love some feedback on
proper cleanup etc.  

This changeset modifies the Browser class such that 500 ms after your
mouse enters the window, it will auto raise to the top.  I believe
that's #activate in morphic.  I had to mod a method in Browser to hook. 
Browser class>>#openBrowserView:label: is changed so that it registers
two callbacks to the view.  That's the 'be careful' part as it
overwrites the other one.  I used a Global Dictionary (I didn't want to
add yet another ivar to Browser) to register the view and the
WindowRaiser, which is the Handler object, upon #mouseEnter event for
that view.  When #mouseLeave event occurs, I stop the WindowRaiser and
remove the entry from the dictionary.  I am currently not removing the
event registrations.  Do they auto clean up?  I don't think I have an
external reference to it.

I hope y'all like it!

Rob

-- 
--------------------------------------------------
Smalltalking by choice.  Isn't it nice to have one!
-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1762] on 28 January 2000 at 1:52:59 am'!
"Change Set:		WindowRaiserTool
Date:			28 January 2000
Author:			Robert Withers

ALPHA This is a hack to raise the window when the activeHand Enters the SystemWindow.  It probably isn't cleaning up after itself.   It is changing the method Browser class>>#openBrowserView:label:   Please be careful"!

Object subclass: #WindowRaiser
	instanceVariableNames: 'view timer '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Slosher-Tools-Extensions'!

!Browser class methodsFor: 'instance creation' stamp: 'rww 1/28/2000 01:36'!
openBrowserView: aBrowserView label: aString 
	"Schedule aBrowserView, labelling the view aString."
	
	aBrowserView isMorph
		ifTrue:  [
			Smalltalk at: #WindowRaiserEventRegister ifAbsentPut: [Dictionary new].
			aBrowserView on: #mouseEnter send: #value to: [(Smalltalk at: #WindowRaiserEventRegister) at: aBrowserView put: ((WindowRaiser newOn: aBrowserView) waitFor: 500)].
			aBrowserView on: #mouseLeave send: #value to: [|raiser| 
						raiser _ (Smalltalk at: #WindowRaiserEventRegister) at: aBrowserView ifAbsent: [nil].
						raiser ifNotNil: [
							raiser stop.
							(Smalltalk at: #WindowRaiserEventRegister) removeKey: aBrowserView.]].
			(aBrowserView setLabel: aString) openInWorld]
		ifFalse: [aBrowserView label: aString.
				aBrowserView minimumSize: 300 @ 200.
				aBrowserView subViews do: [:each | each controller].
				aBrowserView controller open]! !


!WindowRaiser methodsFor: 'accessing' stamp: 'rww 1/28/2000 01:33'!
timer
	"Answer the receiver's instance variable timer."

	^timer! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 1/28/2000 01:33'!
timer: anObject
	"Set the receiver's instance variable timer to anObject."

	timer := anObject! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 1/28/2000 01:33'!
view
	"Answer the receiver's instance variable view."

	^view! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 1/28/2000 01:33'!
view: anObject
	"Set the receiver's instance variable view to anObject."

	view := anObject! !

!WindowRaiser methodsFor: 'action' stamp: 'rww 1/28/2000 01:41'!
raiseView

	self view activate
	! !

!WindowRaiser methodsFor: 'action' stamp: 'rww 1/28/2000 01:45'!
stop

	self timer: false.! !

!WindowRaiser methodsFor: 'action' stamp: 'rww 1/28/2000 01:44'!
waitFor: millisecondTime

	self timer: true.
	[(Delay forMilliseconds: millisecondTime) wait.
	self timer ifTrue: [self raiseView]] fork.! !

!WindowRaiser methodsFor: 'initialize' stamp: 'rww 1/28/2000 01:44'!
initializeOn: aView

	self view: aView.
	self timer: false.! !


!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/28/2000 01:32'!
newOn: aView

	^super new initializeOn: aView
! !




More information about the Squeak-dev mailing list