[squeak-dev] The Trunk: 51Deprecated-mt.34.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Jul 31 08:30:00 UTC 2016


Marcel Taeumel uploaded a new version of 51Deprecated to project The Trunk:
http://source.squeak.org/trunk/51Deprecated-mt.34.mcz

==================== Summary ====================

Name: 51Deprecated-mt.34
Author: mt
Time: 31 July 2016, 10:29:55.07349 am
UUID: 99b93939-2985-7149-9b93-1aa8b90728c7
Ancestors: 51Deprecated-mt.33

*** Widget Refactorings and UI Themes (Part 2 of 11) ***

Simplify window colors and prepare them and other properties of system windows to be themed.

=============== Diff against 51Deprecated-mt.33 ===============

Item was changed:
  SystemOrganization addCategory: #'51Deprecated-Files-Kernel'!
  SystemOrganization addCategory: #'51Deprecated-Morphic-Support'!
  SystemOrganization addCategory: #'51Deprecated-Morphic-Text Support'!
+ SystemOrganization addCategory: #'51Deprecated-PreferenceBrowser'!
+ SystemOrganization addCategory: #'51Deprecated-System-Support'!

Item was added:
+ ----- Method: Object>>defaultBackgroundColor (in category '*51Deprecated') -----
+ defaultBackgroundColor
+ 	
+ 	self deprecated: 'Implement #uniformWindowColor and #customWindowColor in your model.'.
+ 	^ Color veryVeryLightGray!

Item was added:
+ PBColorPreferenceView subclass: #PBWindowColorPreferenceView
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: '51Deprecated-PreferenceBrowser'!

Item was added:
+ ----- Method: PBWindowColorPreferenceView class>>initialize (in category 'class initialization') -----
+ initialize
+ 	self viewRegistry register: self.!

Item was added:
+ ----- Method: PBWindowColorPreferenceView class>>unload (in category 'class initialization') -----
+ unload
+ 	"Unload order is not guaranteed so guard against failure"
+ 	[self viewRegistry unregister: self] on: Error do:[]!

Item was added:
+ ----- Method: PBWindowColorPreferenceView class>>viewRegistry (in category 'class initialization') -----
+ viewRegistry
+ 	^(PreferenceViewRegistry registryOf: #windowColorPreferences)
+ 		viewOrder: 6;
+ 		yourself.!

Item was added:
+ ----- Method: PBWindowColorPreferenceView>>initialize (in category 'initialization') -----
+ initialize
+ 	super initialize.
+ 	self addActionTitled: 'Bright' target: Preferences selector: #yourself arguments: {} balloonText: 'Use standard bright colors for all windows' translated.
+ 	self addActionTitled: 'Pastel' target: Preferences selector: #yourself arguments: {} balloonText: 'Use standard pastel colors for all windows' translated.	
+ 	self addActionTitled: 'Gray' target: Preferences selector: #yourself arguments: {} balloonText: 'Use gray backgrounds for all standard windows' translated.!

Item was added:
+ ----- Method: Preferences class>>setWindowColorFor:to: (in category '*51Deprecated-window colors') -----
+ setWindowColorFor: modelSymbol to: incomingColor
+ 	
+ 	| aColor |
+ 	self deprecated: 'Configure UI themes directly.'.
+ 	aColor := incomingColor asNontranslucentColor.
+ 	(aColor = ColorPickerMorph perniciousBorderColor or: [aColor = Color black]) 
+ 		ifTrue: [^ self].
+ 	UserInterfaceTheme set: #customWindowColor for: modelSymbol to: aColor.	!

Item was added:
+ ----- Method: Preferences class>>uniformWindowColor (in category '*51Deprecated-window colors') -----
+ uniformWindowColor
+ 
+ 	self deprecated: 'Use Model >> #uniformWindowColor.'.
+ 	^Color veryVeryLightGray!

Item was added:
+ ----- Method: Preferences class>>windowColorFor: (in category '*51Deprecated-window colors') -----
+ windowColorFor: aModelClassName
+ 	
+ 	| classToCheck |
+ 	self deprecated: 'Use Model >> #customWindowColor'.	
+ 	classToCheck := Smalltalk at: aModelClassName.
+ 	^ (UserInterfaceTheme current get: #customWindowColor for: classToCheck)
+ 		ifNil: [(UserInterfaceTheme current get: #uniformWindowColor for: classToCheck)
+ 			ifNil: [Color veryVeryLightGray]]!

Item was added:
+ ----- Method: Preferences class>>windowColorTable (in category '*51Deprecated-window colors') -----
+ windowColorTable
+ 	"Answer a list of WindowColorSpec objects, one for each tool to be represented in the window-color panel"
+ 	
+ 	self deprecated: 'Consult current UI theme.'.
+ 	^ {}!

Item was added:
+ ----- Method: SystemWindow>>setLabelFont: (in category '*51Deprecated') -----
+ setLabelFont: aFont
+ 
+ 	label ifNil: [^ self].
+ 	label font: aFont.
+ !

Item was added:
+ Object subclass: #WindowColorRegistry
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: '51Deprecated-System-Support'!
+ WindowColorRegistry class
+ 	instanceVariableNames: 'registry'!
+ 
+ !WindowColorRegistry commentStamp: 'hpt 10/9/2005 22:54' prior: 0!
+ I provide to the applications developer a place where they can register their WindowColorSpecification for their application's windows.
+ !
+ WindowColorRegistry class
+ 	instanceVariableNames: 'registry'!

Item was added:
+ ----- Method: WindowColorRegistry class>>initialize (in category 'registry') -----
+ initialize
+ 	self refresh.!

Item was added:
+ ----- Method: WindowColorRegistry class>>refresh (in category 'registry') -----
+ refresh
+ 	"This is a one-time only method for bootstraping the new registry. Here we will scan all classes for #windowColorSpecification methods and register those to the registry"
+ 
+ 	registry := nil.
+ 	((self systemNavigation allClassesImplementing: #windowColorSpecification)
+ 		collect: [:aClass | aClass theNonMetaClass windowColorSpecification])
+ 		do: [:spec | self registerColorSpecification: spec toClassNamed: spec classSymbol ].!

Item was added:
+ ----- Method: WindowColorRegistry class>>registerColorSpecification:toClassNamed: (in category 'registry') -----
+ registerColorSpecification: aColorSpec toClassNamed: aClassName
+ 	self registry at: aClassName asSymbol put: aColorSpec.!

Item was added:
+ ----- Method: WindowColorRegistry class>>registeredWindowColorSpecFor: (in category 'registry') -----
+ registeredWindowColorSpecFor: aClassName
+ 	"Return the Window Color Spec for the given class. "
+ 	^self registry at: aClassName asSymbol ifAbsent: [].
+ !

Item was added:
+ ----- Method: WindowColorRegistry class>>registeredWindowColorSpecs (in category 'registry') -----
+ registeredWindowColorSpecs
+ 	^self registry values!

Item was added:
+ ----- Method: WindowColorRegistry class>>registry (in category 'registry') -----
+ registry
+ 	^registry ifNil: [registry := Dictionary new].!

Item was added:
+ ----- Method: WindowColorRegistry class>>unregisterColorSpecificationForClassNamed: (in category 'registry') -----
+ unregisterColorSpecificationForClassNamed: aClassName
+ 	
+ 	self registry removeKey: aClassName asSymbol !

Item was added:
+ Object subclass: #WindowColorSpec
+ 	instanceVariableNames: 'classSymbol wording brightColor pastelColor normalColor helpMessage'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: '51Deprecated-System-Support'!

Item was added:
+ ----- Method: WindowColorSpec class>>classSymbol:wording:brightColor:pastelColor:helpMessage: (in category 'instance creation') -----
+ classSymbol: sym wording: wrd brightColor: brCol pastelColor: paCol helpMessage: hlpMsg
+ 	"Answer a new instance of the receiver with the given slots filled in"
+ 
+ 	^ self new classSymbol: sym wording: wrd brightColor: brCol pastelColor: paCol helpMessage: hlpMsg!

Item was added:
+ ----- Method: WindowColorSpec class>>classSymbol:wording:brightColor:pastelColor:normalColor:helpMessage: (in category 'instance creation') -----
+ classSymbol: sym wording: wrd brightColor: brCol pastelColor: paCol normalColor: noCol helpMessage: hlpMsg
+ 
+ 	^ self new classSymbol: sym wording: wrd brightColor: brCol pastelColor: paCol normalColor: noCol helpMessage: hlpMsg!

Item was added:
+ ----- Method: WindowColorSpec>>brightColor (in category 'access') -----
+ brightColor
+ 	"Answer the brightColor"
+ 
+ 	^ brightColor!

Item was added:
+ ----- Method: WindowColorSpec>>classSymbol (in category 'access') -----
+ classSymbol
+ 	"Answer the classSymbol"
+ 
+ 	^ classSymbol!

Item was added:
+ ----- Method: WindowColorSpec>>classSymbol:wording:brightColor:pastelColor:helpMessage: (in category 'initialization') -----
+ classSymbol: sym wording: wrd brightColor: brCol pastelColor: paCol helpMessage: hlpMsg
+ 	"Initialize the receiver's instance variables"
+ 
+ 	self
+ 		classSymbol: sym
+ 		wording: wrd
+ 		brightColor: brCol
+ 		pastelColor: paCol
+ 		normalColor: (Color colorFrom: brCol) duller
+ 		helpMessage: hlpMsg!

Item was added:
+ ----- Method: WindowColorSpec>>classSymbol:wording:brightColor:pastelColor:normalColor:helpMessage: (in category 'initialization') -----
+ classSymbol: sym wording: wrd brightColor: brCol pastelColor: paCol normalColor: noCol helpMessage: hlpMsg
+ 	"Initialize the receiver's instance variables"
+ 
+ 	classSymbol := sym.
+ 	wording := wrd.
+ 	brightColor := brCol.
+ 	pastelColor := paCol.
+ 	normalColor := noCol.
+ 	helpMessage := hlpMsg!

Item was added:
+ ----- Method: WindowColorSpec>>helpMessage (in category 'access') -----
+ helpMessage
+ 	"Answer the helpMessage"
+ 
+ 	^ helpMessage!

Item was added:
+ ----- Method: WindowColorSpec>>normalColor (in category 'access') -----
+ normalColor
+ 
+ 	^ normalColor!

Item was added:
+ ----- Method: WindowColorSpec>>pastelColor (in category 'access') -----
+ pastelColor
+ 	"Answer the pastelColor"
+ 
+ 	^ pastelColor!

Item was added:
+ ----- Method: WindowColorSpec>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	"Print the receiver on a stream"
+ 
+ 	super printOn: aStream.
+ 	classSymbol printOn: aStream. 
+ 	aStream nextPutAll: ' bright: ', brightColor printString, ' pastel: ', pastelColor printString, ' normal: ', normalColor printString!

Item was added:
+ ----- Method: WindowColorSpec>>wording (in category 'access') -----
+ wording
+ 	"Answer the wording"
+ 
+ 	^ wording!

Item was added:
+ (PackageInfo named: '51Deprecated') postscript: 'PBWindowColorPreferenceView unload.
+ WindowColorRegistry refresh.'!



More information about the Squeak-dev mailing list