How to add preferences (was Re: [NOTBUG] HandMorph missing menu actions)

Rob Withers slosher2 at home.com
Mon Jul 17 17:53:07 UTC 2000


Ned Konz wrote:
> 
> Sigh. No, that wasn't the trick. I forgot why the prior version was the way it
> was:
> it allowed (as did the original) for a missing key in FlagDictionary, as well.
> I found this out when I did the file-out (checkForSlips wasn't defined). The
> enclosed
> version does what you want, I think.
> 

Ok, I fixed my clock first of all  :-/

The trick which worked was the external setting of a preference.  I used
#addPreference:category:default:baloonHelp:   It works great as I'm not
stepping on the Preferences class any more!  Any new windows that I open
after setting the flag for this preference works perfectly.  I had also
stepped on noteThatFlag:justChangedTo: so I could setup all existing
Windows to do this also.   You are using a modified changed, update
protocol.  Wouldn't it be faster and better for passing arguments if we
used the #when:send:to: event mechanism?

Here is a changeset with the modified noteThatFlag:changedTo:   I also
included the 2.8 version of my window raiser which uses this event
registration and doesn't touch the Preferences class now.   Which do you
prefer as far as the events go?  The only thing left is the catching of
a #windowOpened event (from the class side of SystemWindow or something
I can register against), so I don't have to hack into Morph methods...


cheers,
Rob
-------------- next part --------------
'From Squeak2.8 of 16 July 2000 [latest update: #2348] on 17 July 2000 at 10:34:14 am'!

!Preferences class methodsFor: 'preferences dictionary' stamp: 'rww 7/17/2000 10:33'!
noteThatFlag: prefSymbol justChangedTo: aBoolean
	"Provides a hook so that a user's toggling of a preference might precipitate some immediate action"
	| keep |
	self trigger: prefSymbol with: aBoolean.
	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:
		[Smalltalk isMorphic ifTrue: [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 == #annotationPanes]) ifTrue:
		[Utilities replaceBrowserInToolsFlap].

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

-------------- next part --------------
'From Squeak2.8 of 16 July 2000 [latest update: #2348] on 17 July 2000 at 10:47:58 am'!
Object subclass: #WindowRaiser
	instanceVariableNames: 'view isRaising '
	classVariableNames: 'EventRegister '
	poolDictionaries: ''
	category: 'Morphic-Support'!

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

!Morph methodsFor: 'event handling' stamp: 'rww 7/14/2000 02:13'!
cancelAutoRiseOnMouseEntry
	WindowRaiser deinstallOnMorph: self.
! !


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

!SystemWindow methodsFor: 'open/close' stamp: 'rww 7/15/2000 20:12'!
openInWorld: aWorld extent: extent
	"This msg and its callees result in the window being activeOnlyOnTop"
	self position: (RealEstateAgent initialFrameFor: self) topLeft; extent: extent.
	self autoRiseOnMouseEntry.
	aWorld addMorph: self.
	self activate.
	aWorld startSteppingSubmorphsOf: self.! !


!WindowRaiser methodsFor: 'initialize' stamp: 'rww 7/14/2000 02:13'!
initializeOn: aView

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

!WindowRaiser methodsFor: 'action' stamp: 'rww 7/14/2000 02:13'!
raiseInMilliseconds: millisecondTime

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

!WindowRaiser methodsFor: 'action' stamp: 'rww 7/14/2000 02:13'!
raiseView

	self view ifNotNil: [self view activate].
	! !

!WindowRaiser methodsFor: 'action' stamp: 'rww 7/14/2000 02:13'!
stop

	self isRaising: false.! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 7/14/2000 02:13'!
isRaising
	"Answer the receiver's instance variable isRaising."

	^isRaising! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 7/14/2000 02:13'!
isRaising: aBoolean
	"Set the receiver's instance variable isRaising to aBoolean."

	isRaising := aBoolean! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 7/14/2000 02:13'!
view
	"Answer the receiver's instance variable view."

	^view! !

!WindowRaiser methodsFor: 'accessing' stamp: 'rww 7/14/2000 02:13'!
view: anObject
	"Set the receiver's instance variable view to anObject."

	view := anObject! !


!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/17/2000 10:44'!
autoRaiseStateChanged: aBool
	aBool
		ifTrue: [WindowRaiser startAutoRise]
		ifFalse: [WindowRaiser stopAutoRise].
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/14/2000 02:13'!
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 7/14/2000 02:13'!
eventRegister
	^EventRegister.
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/17/2000 10:45'!
initialize
	EventRegister := Dictionary new.
	Preferences addPreference: #autoRaiseWindows category: #windows default: false
balloonHelp: 'Turns on the auto raising of windows'.
	Preferences when: #autoRaiseWindows send: #autoRaiseStateChanged: to: WindowRaiser.
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/14/2000 02:13'!
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: [|raiser|
					raiser _ self eventRegister removeKey: aMorph ifAbsent: [nil].
					raiser ifNotNil: [raiser stop]]].! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/14/2000 02:13'!
newOn: aView

	^super new initializeOn: aView
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/14/2000 02:13'!
startAutoRise
	SystemWindow allSubInstancesDo: [:aWindow | aWindow autoRiseOnMouseEntry].
! !

!WindowRaiser class methodsFor: 'as yet unclassified' stamp: 'rww 7/14/2000 02:13'!
stopAutoRise
	SystemWindow allSubInstancesDo: [:aWindow | aWindow cancelAutoRiseOnMouseEntry].
! !

WindowRaiser initialize!


More information about the Squeak-dev mailing list