Color and HTTP Proxy preferences

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Tue Jan 4 21:18:13 UTC 2005


On 04/01/05 13:13, "Doug Way" <dway at mailcan.com> wrote:

> 
> Thanks for the preferences work.  Boolean, Numeric, Text, and Color all
> sound like good fundamental preferences "types" to have.
> 
> One fundamental preferences type that is still needed, though, is some
> sort of multiple-choice or radio-button type.  Maybe call it "Choice" or
> something.  It could be represented as a set of Symbols, one of which is
> currently "selected".  It would show up in the PreferencesBrowser as a
> set of radio buttons, only one of which can be selected at a time.
> 
> You mentioned in the other thread that you have a "Halos" preferences
> type (based on the previously existing Halos preference)... this one
> should really be implemented as a Choice type instead.
> 
> There are a few current Boolean preferences which should really be
> Choice preferences, such as the
> swapCtrlAndAltKeys/dupCtrlAndAltKeys/dupAllCtrlAndAltKeys combo.  Right
> now we have to have an ugly hack which prevents you from selecting more
> than one of these.  Also browseWithPrettyPrint/colorPrettyPrint, and
> there may be others.
> 
> - Doug
> 
> 
> On Tue, 04 Jan 2005 08:37:17 -0300, "Hernan Tylim" <htylim at yahoo.com.ar>
> said:
>> Hi,
>>     I just wanted to advertise that I added to PreferenceBrowser support
>> for Windows Colors and HTTP Proxy settings. The required refactoring for
>> them are waiting on Mantis. If you are interested,  please review them
>> and ask for their inclusion on 3.9a.
>> 
>> There are 3 .cs
>> 
>> The Window Color refactorings:
>> http://bugs.impara.de/view.php?id=634
>> ( WindowColorPrefs-hpt.2.cs )
>> 
>> A 2 methods .cs that adds numeric preferences support to the base image
>> to the already present text, color, and boolean preferences :
>> http://bugs.impara.de/view.php?id=646
>> ( NumericPrefs-hpt.1.cs )
>> 
>> HTTPSocket refactoring to use Preferences instead of a class variables
>> to store the HTTP Proxy Settings:
>> http://bugs.impara.de/view.php?id=648
>> ( HTTPProxyPrefs-hpt.1.cs )
>> 
>> Regards,
>> Hernán
> 
Hernan:
For radio button selection tool. Here is something Ned do some time ago ,
just in case you do not write your own.
And not forgive the long needed Fonts preference.

Edgar

-------------- next part --------------
'From Squeak3.2gamma of 15 January 2002 [latest update: #4913] on 25 July 2002 at 4:51:14 pm'!
"Change Set:		RadioButtonGroupMorph-nk
Date:			25 July 2002
Author:			Ned Konz

This is a simple radio button group that takes a single target and sets buttons based on the return value of performing a selector on that target.

See the class side for examples of its use.

It includes the UpdatingThreePhaseButtonMorphEnhanced from Stephan B. Wessels' IRC Enhancements change set.

RadioButtonGroupMorph example1
"!

BorderedMorph subclass: #RadioButtonGroupMorph
	instanceVariableNames: 'values target getSelector getArgument setSelector setArgument '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'People-nk-Demo'!

!RadioButtonGroupMorph commentStamp: 'nk 7/25/2002 16:02' prior: 0!
This is a simple radio button group that takes a single target and sets buttons based on the return value of performing a selector on that target.

See the class side for examples of its use.

initializeWithValues: anArrayOfValues
	this constructs the buttons, and makes them each correspond to a value in anArrayOfValues.

target:
	this sets the object that is queried and set.

getSelector:
getArgument:
	these set the selector and argument that is sent to the target to get the current value.
	
setSelector:
setArgument:
	these set the selector and argument that is sent to the target to set the value when a button is pushed.
!

UpdatingThreePhaseButtonMorph subclass: #UpdatingThreePhaseButtonMorphEnhanced
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!UpdatingThreePhaseButtonMorphEnhanced commentStamp: '<historical>' prior: 0!
allows for the #getSelector to use the get argument value if needed.!


!RadioButtonGroupMorph methodsFor: 'private' stamp: 'nk 7/25/2002 16:01'!
isValue: aValue
	"Answer true if the result of performing my getSelector is aValue."
	(getSelector isNil or: [ target isNil ]) ifTrue: [ ^false ].
	
	^(getArgument
		ifNil: [ target perform: getSelector ]
		ifNotNil: [ target perform: getSelector withArguments: { getArgument } ]) = aValue
! !

!RadioButtonGroupMorph methodsFor: 'private' stamp: 'nk 7/25/2002 16:01'!
setValue: aValue
	(setSelector isNil or: [ target isNil ]) ifTrue: [ ^self ].

	^(setArgument
		ifNil: [ target perform: setSelector withArguments: { aValue } ]
		ifNotNil: [ target perform: setSelector withArguments: { setArgument. aValue } ]) = aValue
	
! !

!RadioButtonGroupMorph methodsFor: 'initialization' stamp: 'nk 7/25/2002 16:23'!
initializeWithValues: arrayOfValues
	"Given arrayOfValues, construct my buttons.
	One of the values should match the return value from performing my getSelector"
	| button |
	values _ arrayOfValues.
	
	self layoutPolicy: TableLayout new;
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		listCentering: #center;
		color: Color transparent;
		borderWidth: 1.

	self addMorphBack: (Morph new color: Color transparent; vResizing: #spaceFill).
	arrayOfValues do: [ :val | | aligner |
		aligner _ (Morph new color: Color transparent;
			layoutPolicy: TableLayout new;
			listDirection: #leftToRight;
			layoutInset: 4 at 0;
			cellInset: 2 at -2;
			hResizing: #spaceFill;
			vResizing: #shrinkWrap).
		button _ UpdatingThreePhaseButtonMorphEnhanced radioButton.
		button target: self;
			actionSelector: #setValue:;
			arguments: { val };
			getSelector: #isValue:;
			getArgument: val.
		aligner addMorphBack: button.
		aligner addMorphBack: (StringMorph contents: val asString).
		self addMorphBack: aligner.
		self addMorphBack: (Morph new color: Color transparent; vResizing: #spaceFill).
	].
	
! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'nk 7/25/2002 15:37'!
getArgument: anObject
	getArgument _ anObject
! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'nk 7/25/2002 15:36'!
getSelector: selector
	getSelector _ selector.
! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'nk 7/25/2002 15:53'!
setArgument: anObject
	setArgument _ anObject
! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'nk 7/25/2002 15:53'!
setSelector: selector
	setSelector _ selector.
! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'nk 7/25/2002 15:37'!
target: anObject
	target _ anObject
! !


!RadioButtonGroupMorph class methodsFor: 'examples' stamp: 'nk 7/25/2002 16:23'!
example1
	"RadioButtonGroupMorph example1"
	"Make a RBGM with three values"
	| assoc g |
	assoc _ 'myKey' -> #one.
	g _ RadioButtonGroupMorph new initializeWithValues: { #one. #two. #three }.
	g target: assoc;
		getSelector: #value;
		setSelector: #value:;
		extent: 55 at 62.
	g openInWorld.
! !


!UpdatingThreePhaseButtonMorph methodsFor: 'relocated from all category' stamp: 'sbw 3/3/2002 12:04'!
getNewBoolean
	^ target perform: getSelector! !

!UpdatingThreePhaseButtonMorph methodsFor: 'relocated from all category' stamp: 'sbw 3/3/2002 12:05'!
step
	| newBoolean |
	super step.
	state == #pressed
		ifTrue: [^ self].
	newBoolean _ self getNewBoolean.
	newBoolean == self isOn
		ifFalse: [self
				state: (newBoolean == true
						ifTrue: [#on]
						ifFalse: [#off])]! !


!UpdatingThreePhaseButtonMorphEnhanced methodsFor: 'as yet unclassified' stamp: 'sbw 3/3/2002 11:59'!
getArgument: aSymbol
	getArgument _ aSymbol! !

!UpdatingThreePhaseButtonMorphEnhanced methodsFor: 'as yet unclassified' stamp: 'sbw 3/3/2002 12:06'!
getNewBoolean
	^ getArgument isNil
		ifTrue: [target perform: getSelector]
		ifFalse: [target perform: getSelector with: getArgument]
! !


!RadioButtonGroupMorph class reorganize!
('examples' example1)
!

RadioButtonGroupMorph removeSelector: #initializeWithValues:getSelector:!

!RadioButtonGroupMorph reorganize!
('private' isValue: setValue:)
('initialization' initializeWithValues:)
('accessing' getArgument: getSelector: setArgument: setSelector: target:)
!

"Postscript:
Pop up a sample."
RadioButtonGroupMorph example1!

-------------- next part --------------
'From Squeak 3.2 of 11 July 2002 [latest update: #4917] on 25 July 2002 at 9:18:18 pm'!
"Change Set:		RadioButtonGrpEnh-ccn
Date:			25 July 2002
Author:			Chris Norton

Prerequisite:  RadioButtonGroupMorph-nk published by Ned Konz, July 25, 2002 at 4:51:45 pm.

This change set adds some common UI protocol methods to Ned Konz's excellent RadioButtonMorphGroup.

New protocol: 

#contents
#indexOf:
#selectedItem
#selection

Thanks Ned for providing us with a radio button group widget!!"!


!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'ccn 7/25/2002 21:11'!
contents
	"Answer the collection of objects that are associated with the radio buttons within the group."

	^values! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'ccn 7/25/2002 21:10'!
indexOf: anObject
	"Answer the index of the item anObject.  Answer zero if anObject is not found."

	^self contents indexOf: anObject! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'ccn 7/25/2002 21:09'!
selectedItem
	"Answer the selected item."

	^target value! !

!RadioButtonGroupMorph methodsFor: 'accessing' stamp: 'ccn 7/25/2002 21:09'!
selection
	"Answer the index number of the selected item."

	^self indexOf: target value! !


!RadioButtonGroupMorph reorganize!
('accessing' contents getArgument: getSelector: indexOf: selectedItem selection setArgument: setSelector: target:)
('initialization' initializeWithValues:)
('private' isValue: setValue:)
!



More information about the Squeak-dev mailing list