[GOODIE] Re: autoRise (was Re: woohoo! ...)

Robert Withers withers at vnet.net
Sun Jan 30 18:00:33 UTC 2000


Torge Husfeldt wrote:
> 
> Hi Robert,
> ----- Original Message -----
> From: Robert Withers <withers at vnet.net>
> To: <squeak at cs.uiuc.edu>
> Sent: Sunday, January 30, 2000 9:38 AM
> Subject: Re: autoRise (was Re: woohoo! It's my first squeak/morphic alpha
> code!)
> 
> > Robert Withers wrote:
> > >
> > > I'm glad you like it.  I can't take any credit for the idea; it comes
> > > from Linux/XFree86.  Let me say that I think the list is the best place
> > > for this exchange because someone may take your additions and add their
> > > own.  I'm not worried about ownership issues; it's all of ours.   So
> > > it's not less than polite, but rather asynchronous pair programming.
> > >
> > > Your fixes make a lot of sense.  Thanks!  I was wondering how to bring
> > > this to all Morphic windows, but I'm not familiar enough with the
> > > Classes yet.  I especially like your #autoRiseOnMouseEntry and your
> > > placement of the Register dictionary as a class var in WindowRaiser (we
> > > could call it a Necromancer if you wish! :)  ).  I don't know what I was
> > > thinking, putting it in the Smalltalk dictionary.  Just hacking, you
> > > know?
> > >
> > > Could you post your changeset, please?   I want to build on it.   I'd
> > > like to figure out how to install a start/stop menu item in the World
> > > popup (or preferences).  I believe this would require removing the event
> > > registrations from the windows that are active
> > > (#cancelAutoRiseOnMouseEntry) and setting a class side flag in
> > > WindowRaiser to not install the events for new windows.  Finally, have
> > > #autoRiseOnMouseEntry and #cancelAutoRiseOnMouseEntry defer ot class
> > > methods on the WindowRaiser for installation/deinstallation of the
> > > events.  I also found that I like a 50 millisecond delay or none at
> > > all.  It's more immediate.
> > >
> >
> > Here's an update.  I incorporated most of Stan's recommendations and
> > extended a few others so that you can turn it on and off.  It defaults
> > to off.  See the class comment of WindowRaiser, which is now in
> > Morphic-Support, for instructions on turning this on and off.  I changed
> > the delay, and my previous change to 400 milliseconds.  It isn't as
> > immediate as I would like but it is more forgiving than 50!
> >
> > I would love to put this into the Preferences, but, first, I wasn't sure
> No need to hesitate here! Adding an entry to Preferences that defaults to
> false is very easy and polite and IMO the widely agreed way to do it.
> Look at the #doesNotUnderstand: in Preferences and you'll see.
> You just ask:
>     Preferences autoRiseWindows
> and it answers false. To enable autoRising it suffices to send:
>     Preferences enable: autoRiseWindows
> > how, and second, it's prolly best to let it ripen a bit and see if y'all
> > find it useful.  I sure do!
> On the contrary I think that using the Preferences for this can even help
> the overall acceptance of your goodie. (don't forget to include [GOODIE]
> in the subject line next time you post it with .cs).

Ok, I had to change Preferences class>>noteThatFlag:justChangedTo:, so
that I could (de)install all of the event registrations for existing
windows.  This brings to two the core classes I have modified
(Morphic>>openInWorld:)

It defaults to disabled.  You should go into the preferences window and
click on the false next to autoRaiseWindows.  Now you can save you're
fingers for better things.  It is quite a productivity boost.  ;-)   

Thanks again Stan and Torge!

Rob

> >
> > Enjoy!  (thanks again Stan!)
> > Rob
> >
> > >
> > > --
> 
> Regards,
> Torge.

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

Beta:  Ok folks.  We are into the Preferences now.  On load the WindowRaiser installs a preference which defaults to disabled.  You have to enable it in help...preferences...   Special thanks goes to Stan Heckman, and Torge Husfeldt.

Special Warning: This changeset modifies Morph>>#openInWorld: aWorld, which is a core Morphic method.  It also modifies Preferences class>>noteThatFlag:justChangedTo:"!

Object subclass: #WindowRaiser
	instanceVariableNames: 'view isRaising '
	classVariableNames: 'EventRegister '
	poolDictionaries: ''
	category: 'Morphic-Support'!

!Morph methodsFor: 'event handling' stamp: 'rww 1/30/2000 02:14'!
autoRiseOnMouseEntry
	WindowRaiser installOnMorph: self.
! !

!Morph methodsFor: 'event handling' stamp: 'rww 1/30/2000 02:18'!
cancelAutoRiseOnMouseEntry
	WindowRaiser deinstallOnMorph: self.
! !


!Preferences class methodsFor: 'preferences dictionary' stamp: 'rww 1/30/2000 12:39'!
noteThatFlag: prefSymbol justChangedTo: aBoolean
	"Provides a hook so that a user's toggling of a preference might precipitate some immediate action"
	| keep | 
	prefSymbol == #useGlobalFlaps ifTrue:
		[aBoolean
			ifFalse:		"Turning off use of flaps"
				[keep _ self confirm:
'Do you want to preserve the existing
global flaps for future use?'.
				Utilities globalFlapTabsIfAny do:
					[:aFlapTab | Utilities removeFlapTab: aFlapTab keepInList: keep.
					aFlapTab isInWorld ifTrue: [self error: 'Flap problem']].
				keep ifFalse: [Utilities clobberFlapTabList]]

			ifTrue:		"Turning on use of flaps"
				[Smalltalk isMorphic ifTrue:
					[self currentWorld addGlobalFlaps]]].

	prefSymbol == #roundedWindowCorners ifTrue:
		[World ifNotNil: [World fullRepaintNeeded]].

	prefSymbol == #optionalButtons ifTrue:
		[Utilities replacePartSatisfying: [:el |  (el isKindOf: MorphThumbnail) and: [(el morphRepresented isKindOf: SystemWindow) and: [el morphRepresented model isKindOf: FileList]]]
inGlobalFlapSatisfying: [:f1 | f1 wording = 'Tools'] with:  FileList openAsMorph applyModelExtent].

	(prefSymbol == #optionalButtons  or: [prefSymbol == #useAnnotationPanes]) ifTrue:
		[Utilities replaceBrowserInToolsFlap].

	(prefSymbol == #smartUpdating) ifTrue:
		[SystemWindow allSubInstancesDo:
			[:aWindow | aWindow amendSteppingStatus]].

	(prefSymbol == #autoRaiseWindows) ifTrue:
		['blah2' print. aBoolean 
			ifTrue: [WindowRaiser startAutoRise]
			ifFalse: [WindowRaiser stopAutoRise]]! !


!SystemWindow methodsFor: 'open/close' stamp: 'rww 1/30/2000 02:29'!
openInWorld: aWorld
	"This msg and its callees result in the window being activeOnlyOnTop"
	self autoRiseOnMouseEntry.
	self bounds: (RealEstateAgent initialFrameFor: self).
	aWorld addMorph: self.
	self activate.
	aWorld startSteppingSubmorphsOf: self! !


!WindowRaiser commentStamp: 'rww 1/30/2000 03:19' prior: 0!
To turn on window raising:
	WindowRaiser startAutoRise.

To turn window raising off again:
	WindowRaiser stopAutoRise.!

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 1/30/2000 02:41'!
isRaising
	"Answer the receiver's instance variable isRaising."

	^isRaising! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 1/30/2000 02:41'!
isRaising: aBoolean
	"Set the receiver's instance variable isRaising to aBoolean."

	isRaising := aBoolean! !

!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/30/2000 02:39'!
raiseInMilliseconds: millisecondTime

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

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

	self view activate
	! !

!WindowRaiser methodsFor: 'action' stamp: 'rww 1/30/2000 02:39'!
stop

	self isRaising: false.! !

!WindowRaiser methodsFor: 'initialize' stamp: 'rww 1/30/2000 02:40'!
initializeOn: aView

	self view: aView.
	self isRaising: false.! !


!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/30/2000 02:24'!
deinstallOnMorph: aMorph
	|raiser|
	raiser := self eventRegister removeKey: aMorph ifAbsent: [nil].
	raiser ifNotNil: [raiser stop].

	aMorph 
		on: #mouseEnter 
		send: nil 
		to: nil.
	aMorph 
		on: #mouseLeave 
		send: nil 
		to: nil.

! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/30/2000 02:10'!
eventRegister
	^EventRegister.
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/30/2000 10:48'!
initialize
	EventRegister := Dictionary new.
	Preferences disable: #autoRaiseWindows.! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/30/2000 12:40'!
installOnMorph: aMorph
	(Preferences autoRaiseWindows)
		ifTrue: [
			aMorph 
				on: #mouseEnter 
				send: #value 
				to:  [self eventRegister at: aMorph put: ((WindowRaiser newOn: aMorph) raiseInMilliseconds: 400)].
		        aMorph
				on: #mouseLeave 
				send: #value 
				to: [(self eventRegister removeKey: aMorph ifAbsent: [^ self]) stop]].! !

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

	^super new initializeOn: aView
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/30/2000 10:44'!
startAutoRise
	SystemWindow allSubInstancesDo: [:aWindow | aWindow autoRiseOnMouseEntry].
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 1/30/2000 10:44'!
stopAutoRise
	SystemWindow allSubInstancesDo: [:aWindow | aWindow cancelAutoRiseOnMouseEntry].
! !


WindowRaiser removeSelector: #timer:!
WindowRaiser removeSelector: #waitFor:!
WindowRaiser removeSelector: #timer!
WindowRaiser initialize!
WindowRaiser class removeSelector: #IsActive!


More information about the Squeak-dev mailing list