The Trunk: System-mt.852.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: System-mt.852.mcz

commits-2
Marcel Taeumel uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-mt.852.mcz

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

Name: System-mt.852
Author: mt
Time: 31 July 2016, 10:26:23.47249 am
UUID: 2f87dcb0-45b2-4747-a5dc-2968f97a816a
Ancestors: System-mt.851

*** 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 System-mt.851 ===============

Item was removed:
- ----- Method: Object class>>windowColorSpecification (in category '*System-Support-window color') -----
- windowColorSpecification
- "Answer a WindowColorSpec object that declares my preference.
- This is a backstop for classes that don't otherwise define a preference."
-
- ^ WindowColorSpec classSymbol: self name
- wording: 'Default' brightColor: #veryVeryLightGray
- pastelColor: #veryVeryLightGray
- normalColor: #veryVeryLightGray
- helpMessage: 'Other windows without color preferences.'!

Item was removed:
- ----- Method: Preferences class>>checkForWindowColors (in category 'prefs - window colors') -----
- checkForWindowColors
- (self allPreferences noneSatisfy:  [:aPref | aPref name endsWith: 'WindowColor'])
- ifTrue: [self installBrightWindowColors].!

Item was removed:
- ----- Method: Preferences class>>darkenStandardWindowPreferences (in category 'prefs - window colors') -----
- darkenStandardWindowPreferences
- "Make all window-color preferences one shade darker"
-
- (self allPreferences
- select: [:aPref | (aPref name endsWith: 'WindowColor')
- and: [aPref preferenceValue isColor]])
- do: [:aPref | aPref preferenceValue: aPref preferenceValue darker].
-
- "Preferences darkenStandardWindowPreferences"
- !

Item was removed:
- ----- Method: Preferences class>>installBrightWindowColors (in category 'prefs - window colors') -----
- installBrightWindowColors
- "Install the factory-provided default window colors for all tools"
-
- "Preferences installBrightWindowColors"
-
- self installWindowColorsVia: [:aSpec | aSpec brightColor]!

Item was removed:
- ----- Method: Preferences class>>installNormalWindowColors (in category 'prefs - window colors') -----
- installNormalWindowColors
- "Install the factory-provided default window colors for all tools"
-
- "Preferences installNormalWindowColors"
-
- self installWindowColorsVia: [:aSpec | aSpec normalColor]!

Item was removed:
- ----- Method: Preferences class>>installPastelWindowColors (in category 'prefs - window colors') -----
- installPastelWindowColors
- "Install the factory-provided default pastel window colors for all tools"
-
- "Preferences installPastelWindowColors"
- self installWindowColorsVia: [:aSpec | aSpec pastelColor]!

Item was removed:
- ----- Method: Preferences class>>installUniformWindowColors (in category 'prefs - window colors') -----
- installUniformWindowColors
- "Install the factory-provided uniform window colors for all tools"
-
- "Preferences installUniformWindowColors"
- self installWindowColorsVia: [:aQuad | self uniformWindowColor]!

Item was removed:
- ----- Method: Preferences class>>installWindowColorsVia: (in category 'prefs - window colors') -----
- installWindowColorsVia: colorSpecBlock
- "Install windows colors using colorSpecBlock to deliver the color source for each element; the block is handed a WindowColorSpec object"
- "Preferences installBrightWindowColors"
-
- WindowColorRegistry refresh.
- self windowColorTable do:
- [:aColorSpec | | color |
- color := (Color colorFrom: (colorSpecBlock value: aColorSpec)).
- self setWindowColorFor: aColorSpec classSymbol to: color].
- SystemWindow refreshAllWindows.
- TheWorldMainDockingBar updateInstances.!

Item was removed:
- ----- Method: Preferences class>>lightenStandardWindowPreferences (in category 'prefs - window colors') -----
- lightenStandardWindowPreferences
- "Make all window-color preferences one shade darker"
-
- (self allPreferences
- select: [:aPref | (aPref name endsWith: 'WindowColor')
- and: [aPref preferenceValue isColor]])
- do: [:aPref | aPref preferenceValue: aPref preferenceValue lighter].
-
- "Preferences lightenStandardWindowPreferences"
- !

Item was removed:
- ----- Method: Preferences class>>preferencesPanelWindowColor (in category 'standard queries') -----
- preferencesPanelWindowColor
- ^ self
- valueOfFlag: #preferencesPanelWindowColor
- ifAbsent:
- [ Color
- r: 0.645
- g: 1.0
- b: 1.0 ]!

Item was removed:
- ----- Method: Preferences class>>setWindowColorFor:to: (in category 'prefs - window colors') -----
- setWindowColorFor: modelSymbol to: incomingColor
- | aColor aPrefSymbol aColorSpec |
- aColorSpec := WindowColorRegistry registeredWindowColorSpecFor: modelSymbol.
- aColorSpec ifNil: [^self].
- aColor := incomingColor asNontranslucentColor.
- (aColor = ColorPickerMorph perniciousBorderColor or: [aColor = Color black])
- ifTrue: [^ self].
- aPrefSymbol :=  self windowColorPreferenceForClassNamed: aColorSpec classSymbol.
- self
- addPreference: aPrefSymbol  
- categories:  { #'window colors' }
- default:  aColor
- balloonHelp: aColorSpec helpMessage translated
- projectLocal: false
- changeInformee: nil
- changeSelector: nil
- type: #WindowColor!

Item was removed:
- ----- Method: Preferences class>>uniformWindowColor (in category 'prefs - window colors') -----
- uniformWindowColor
- ^Color veryVeryLightGray!

Item was removed:
- ----- Method: Preferences class>>windowColorFor: (in category 'prefs - window colors') -----
- windowColorFor: aModelClassName
- | classToCheck prefSymbol |
- self checkForWindowColors.
- classToCheck := Smalltalk at: aModelClassName.
- prefSymbol := self windowColorPreferenceForClassNamed: classToCheck name.
- [(classToCheck ~~ Object) and: [(self preferenceAt: prefSymbol) isNil]]
- whileTrue:
- [classToCheck := classToCheck superclass.
- prefSymbol := self windowColorPreferenceForClassNamed: classToCheck name].
- ^self valueOfPreference: prefSymbol ifAbsent: [self uniformWindowColor].!

Item was removed:
- ----- Method: Preferences class>>windowColorHelp (in category 'prefs - window colors') -----
- windowColorHelp
- "Provide help for the window-color panel"
-
- | helpString |
- helpString :=
- 'The "Window Colors" panel lets you select colors for many kinds of standard Squeak windows.
-
- You can change your color preference for any particular tool by clicking on the color swatch and then selecting the desired color from the resulting color-picker.
-
- The three buttons entitled "Bright", "Pastel", and "Gray" let you revert to any of three different standard color schemes.  
-
- The choices you make in the Window Colors panel only affect the colors of new windows that you open.
-
- You can make other tools have their colors governed by this panel by simply implementing #windowColorSpecification on the class side of the model -- consult implementors of that method to see examples of how to do this.'.
-
- (StringHolder new contents: helpString)
- openLabel: 'About Window Colors'
-
- "Preferences windowColorHelp"!

Item was removed:
- ----- Method: Preferences class>>windowColorPreferenceForClassNamed: (in category 'prefs - window colors') -----
- windowColorPreferenceForClassNamed: aClassName
- | aColorSpec wording |
- aColorSpec := WindowColorRegistry registeredWindowColorSpecFor: aClassName.
- wording := aColorSpec ifNil: [aClassName] ifNotNil: [aColorSpec wording].
- ^(wording, 'WindowColor') asLegalSelector asSymbol.!

Item was removed:
- ----- Method: Preferences class>>windowColorTable (in category 'prefs - window colors') -----
- windowColorTable
- "Answer a list of WindowColorSpec objects, one for each tool to be represented in the window-color panel"
- ^ (WindowColorRegistry registeredWindowColorSpecs
- asSortedCollection:
- [:specOne :specTwo | specOne wording < specTwo wording]) asArray.
-
- "Preferences windowColorTable"!

Item was removed:
- ----- Method: StringHolder class>>windowColorSpecification (in category '*System-Support-window colorwindow color') -----
- windowColorSpecification
- "Answer a WindowColorSpec object that declares my preference"
-
- ^ WindowColorSpec classSymbol: self name wording: 'Workspace' brightColor: #lightYellow pastelColor: #paleYellow helpMessage: 'A place for text in a window.'!

Item was removed:
- Object subclass: #WindowColorRegistry
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: '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 removed:
- ----- Method: WindowColorRegistry class>>initialize (in category 'registry') -----
- initialize
- self refresh.!

Item was removed:
- ----- 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 removed:
- ----- Method: WindowColorRegistry class>>registerColorSpecification:toClassNamed: (in category 'registry') -----
- registerColorSpecification: aColorSpec toClassNamed: aClassName
- self registry at: aClassName asSymbol put: aColorSpec.!

Item was removed:
- ----- 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 removed:
- ----- Method: WindowColorRegistry class>>registeredWindowColorSpecs (in category 'registry') -----
- registeredWindowColorSpecs
- ^self registry values!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: WindowColorSpec>>brightColor (in category 'access') -----
- brightColor
- "Answer the brightColor"
-
- ^ brightColor!

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: WindowColorSpec>>helpMessage (in category 'access') -----
- helpMessage
- "Answer the helpMessage"
-
- ^ helpMessage!

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: WindowColorSpec>>wording (in category 'access') -----
- wording
- "Answer the wording"
-
- ^ wording!

Item was changed:
+ (PackageInfo named: 'System') postscript: 'Preferences allPreferences
+ select: [:ea | ea name endsWith: #WindowColor]
+ thenDo: [:ea | Preferences removePreference: ea name].'!
- (PackageInfo named: 'System') postscript: 'Preferences removePreference: #roundedWindowCorners.
- Preferences removePreference: #gradientScrollBars.'!