[Pkg] The Trunk: System-mt.903.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Aug 19 16:22:49 UTC 2016


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

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

Name: System-mt.903
Author: mt
Time: 19 August 2016, 6:22:24.593803 pm
UUID: e2088c5d-74c3-0b48-ad04-ee30a6f5c1ce
Ancestors: System-mt.902

Fixes the demo/hi-dpi mode. Copies the current UI theme and installs large fonts there. Restoring fonts means looking for the UI that was copied from, by name for now.

=============== Diff against System-mt.902 ===============

Item was changed:
  ----- Method: CommunityTheme class>>addDarkFonts: (in category 'instance creation') -----
  addDarkFonts: aUserInterfaceTheme
  	"Set-up fonts."
  	aUserInterfaceTheme
  		set: #balloonHelpFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7 emphasized: TextEmphasis italic emphasisCode);
  		set: #standardButtonFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7);
  		set: #standardCodeFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
- 		set: #standardDefaultTextFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardFlapFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7 emphasized: TextEmphasis bold emphasisCode);
  		set: #haloLabelFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardListFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardMenuFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardSystemFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #windowTitleFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9 emphasized: TextEmphasis bold emphasisCode)!

Item was changed:
  ----- Method: MonokaiTheme class>>addDarkFonts: (in category 'instance creation') -----
  addDarkFonts: theme
  
  	"Set-up fonts."
  	theme
  		set: #balloonHelpFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7);
  		set: #standardButtonFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7);
  		set: #standardCodeFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
- 		set: #standardDefaultTextFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardFlapFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7 emphasized: TextEmphasis bold emphasisCode);
  		set: #haloLabelFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardListFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardMenuFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardSystemFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #windowTitleFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9).!

Item was added:
+ ----- Method: Preferences class>>chooseFixedFont (in category 'prefs - fonts') -----
+ chooseFixedFont
+ 	self 
+ 		chooseFontWithPrompt: 'Default fixed font...' translated
+ 		andSendTo: self 
+ 		withSelector: #setFixedFontTo: 
+ 		highlightSelector: #standardFixedFont!

Item was changed:
  ----- Method: Preferences class>>fontConfigurationMenu: (in category 'prefs - fonts') -----
  fontConfigurationMenu: aMenu
  
  	aMenu removeAllMorphs.
  	aMenu addTitle: 'Standard System Fonts' translated.
  	aMenu addStayUpIcons.
  	
  	aMenu add: 'default text font...' translated action: #chooseSystemFont.
+ 	aMenu lastItem font: Preferences standardSystemFont.
- 	aMenu lastItem font: Preferences standardDefaultTextFont.
  	aMenu balloonTextForLastItem: 'Choose the default font to be used for code and  in workspaces, transcripts, etc.' translated.
  	
+ 	aMenu add: 'default fixed font...' translated action: #chooseFixedFont.
+ 	aMenu lastItem font: Preferences standardFixedFont.
+ 	aMenu balloonTextForLastItem: 'Choose the default font to be used for text that needs fixed width characters for layouting etc.' translated.
  	
  	aMenu add: 'list font...' translated action: #chooseListFont.
  	aMenu lastItem font: Preferences standardListFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used in list panes' translated.
  	
  	aMenu add: 'flaps font...' translated action: #chooseFlapsFont.
  	aMenu lastItem font: Preferences standardFlapFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used on textual flap tabs' translated.
  
  	aMenu add: 'eToys font...' translated action: #chooseEToysFont.
  	aMenu lastItem font: Preferences standardEToysFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used on eToys environment' translated.
  
  	aMenu add: 'eToys title font...' translated action: #chooseEToysTitleFont.
  	aMenu lastItem font: Preferences standardEToysTitleFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used in titles on eToys environment' translated.
  
  	aMenu add: 'halo label font...' translated action: #chooseHaloLabelFont.
  	aMenu lastItem font: Preferences standardHaloLabelFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used on labels ih halo' translated.
  
  	aMenu add: 'menu font...' translated action: #chooseMenuFont.
  	aMenu lastItem font: Preferences standardMenuFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used in menus' translated.
  	
  	aMenu add: 'window-title font...' translated action: #chooseWindowTitleFont.
  	aMenu lastItem font: Preferences windowTitleFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used in window titles.' translated.
  
  	aMenu add: 'balloon-help font...' translated action: #chooseBalloonHelpFont.
  	aMenu lastItem font: Preferences standardBalloonHelpFont.
  	aMenu balloonTextForLastItem: 'choose the font to be used when presenting balloon help.' translated.
  	
  	aMenu add: 'code font...' translated action: #chooseCodeFont. 
  	aMenu lastItem font: Preferences standardCodeFont. 
  	aMenu balloonTextForLastItem: 'Choose the font to be used in code panes.' translated.
  
  	aMenu add: 'button font...' translated action: #chooseStandardButtonFont.
  	aMenu lastItem font: Preferences standardButtonFont.
  	aMenu balloonTextForLastItem: 'Choose the font to be used in buttons.' translated.
  
  	aMenu addLine.
+ 	aMenu add: 'demo/hi-dpi mode' translated action: #setDemoFonts.
- 	aMenu add: 'demo mode' translated action: #setDemoFonts.
  	aMenu balloonTextForLastItem: 'Set Fonts usable for giving a presentation' translated.
  
  	aMenu addLine.
  	aMenu add: 'restore default font choices' translated action: #restoreDefaultFonts.
  	aMenu balloonTextForLastItem: 'Use the standard system font defaults' translated.
  	
+ 	aMenu add: 'print current font choices' translated action: #printStandardSystemFonts.
- 	aMenu add: 'print default font choices' translated action: #printStandardSystemFonts.
  	aMenu balloonTextForLastItem: 'Print the standard system font defaults to the Transcript' translated.
  	
  	aMenu addLine.
  	aMenu add: 'refresh this menu' translated target: self selector: #fontConfigurationMenu:  argument: aMenu.
  	aMenu balloonTextForLastItem: 'Update this menu to reflect the current fonts' translated.
  	MenuIcons decorateMenu: aMenu.
  	^ aMenu!

Item was changed:
  ----- Method: Preferences class>>restoreDefaultFonts (in category 'prefs - fonts') -----
  restoreDefaultFonts
  	"Since this is called from menus, we can take the opportunity to prompt for missing font styles."
  	"
  	Preferences restoreDefaultFonts
  	"
+ 	
+ 	UserInterfaceTheme allThemes
+ 		detect: [:ea | UserInterfaceTheme current name ~= ea name
+ 			and: [UserInterfaceTheme current name includesSubstring: ea name]]
+ 		ifFound: [:ea | 
+ 			(Project current uiManager
+ 				confirm: ('Do you want to apply\"{1}"?' translated withCRs format: {ea name})
+ 				title: 'Apply UI Theme' translated) ifTrue: [ea apply]]
+ 		ifNone: [self inform: 'Sorry, could not revert font choices.\Please apply a UI theme with smaller fonts.' translated withCRs].!
- 
- 	self setDefaultFonts: #(
- 		(setSystemFontTo:			'Bitmap DejaVu Sans'		9)
- 		(setListFontTo:				'Bitmap DejaVu Sans'		9)
- 		(setFlapsFontTo:			Accushi						12)
- 		(setEToysFontTo:			BitstreamVeraSansBold		9)
- 		(setPaintBoxButtonFontTo:	BitstreamVeraSansBold		9)
- 		(setMenuFontTo:			'Bitmap DejaVu Sans'		9)
- 		(setWindowTitleFontTo:		'Bitmap DejaVu Sans Bold'	9)
- 		(setBalloonHelpFontTo:		'Bitmap DejaVu Sans'		7)
- 		(setCodeFontTo:			'Bitmap DejaVu Sans'		9)
- 		(setButtonFontTo:			'Bitmap DejaVu Sans'	7)
- 	)!

Item was changed:
  ----- Method: Preferences class>>setDemoFonts (in category 'prefs - fonts') -----
  setDemoFonts
  	"Preferences setDemoFonts"
  
+ 	| theme base |
+ 	self inform: 'The current UI theme will be copied\and larger fonts be installed.' translated withCRs.
+ 	
+ 	(UserInterfaceTheme current name beginsWith: 'Demo')
+ 		ifFalse: [
+ 			"Create DEMO version of current theme."
+ 			theme := UserInterfaceTheme named: 'Demo'.
+ 			theme merge: UserInterfaceTheme current overwrite: true.
+ 			theme apply].
+ 
+ 	base := (TextStyle defaultFont name beginsWith: 'Darkmap')
+ 		ifTrue: ['Darkmap DejaVu Sans'] ifFalse: ['Bitmap DejaVu Sans'].
+ 
+ 	self setDefaultFonts: {
+ 		{#setSystemFontTo:. base. 14}.
+ 		{#setFixedFontTo:. 'BitstreamVeraSansMono'. 16}.
+ 		{#setListFontTo:. base. 14}.
+ 		{#setFlapsFontTo:. base. 12}.
+ 		{#setEToysFontTo:. base. 14}.
+ 		{#setPaintBoxButtonFontTo:. base. 14}.
+ 		{#setMenuFontTo:. base	. 14}.
+ 		{#setWindowTitleFontTo:. base, ' B'. 	14}.
+ 		{#setBalloonHelpFontTo:. base. 12}.
+ 		{#setCodeFontTo:. base. 14}.
+ 		{#setButtonFontTo:. base. 	12}.
+ 	}
- 	self setDefaultFonts: #(
- 		(setSystemFontTo:			BitstreamVeraSans			 		12)
- 		(setListFontTo:				BitstreamVeraSans					14)
- 		(setFlapsFontTo:				Accushi								12)
- 		(setEToysFontTo:				BitstreamVeraSansBold				9)
- 		(setPaintBoxButtonFontTo:	BitstreamVeraSansBold				9)
- 		(setMenuFontTo:				BitstreamVeraSans					14)
- 		(setWindowTitleFontTo:		BitstreamVeraSansBold				12)
- 		(setBalloonHelpFontTo:		Accujen								18)
- 		(setCodeFontTo:				BitstreamVeraSans					18)
- 		(setButtonFontTo:			BitstreamVeraSansMono				14)
- 	)
  !

Item was added:
+ ----- Method: Preferences class>>setFixedFontTo: (in category 'prefs - fonts') -----
+ setFixedFontTo: aFont
+ 	"Establish the default fixed text font and style"
+ 
+ 	| aStyle newDefaultStyle |
+ 	aFont ifNil: [^ self].
+ 	aStyle := aFont textStyle ifNil: [^ self].
+ 	
+ 	newDefaultStyle := aStyle copy.
+ 	newDefaultStyle defaultFontIndex: (aStyle fontIndexOf: aFont).
+ 
+ 	UserInterfaceTheme current
+ 		set: #standardFixedFont to: aFont;
+ 		apply.
+ 
+ 	TextStyle setDefaultFixed: newDefaultStyle.!

Item was changed:
  ----- Method: Preferences class>>setSystemFontTo: (in category 'prefs - fonts') -----
  setSystemFontTo: aFont
  	"Establish the default text font and style"
  
  	| aStyle newDefaultStyle |
  	aFont ifNil: [^ self].
  	aStyle := aFont textStyle ifNil: [^ self].
  	newDefaultStyle := aStyle copy.
  	newDefaultStyle defaultFontIndex: (aStyle fontIndexOf: aFont).
+ 
+ 	UserInterfaceTheme current
+ 		set: #standardSystemFont to: aFont;
+ 		apply.
+ 
+ 	TextStyle setDefault: newDefaultStyle.
- 	TextConstants at: #DefaultTextStyle put: newDefaultStyle.
  	Flaps replaceToolsFlap.
+ 	ScriptingSystem resetStandardPartsBin.
+ 	
+ !
- 	ScriptingSystem resetStandardPartsBin!

Item was changed:
  ----- Method: Preferences class>>standardDefaultTextFont (in category 'prefs - fonts') -----
  standardDefaultTextFont
+ 	^TextStyle defaultFont!
- 
- 	^ (UserInterfaceTheme current get: #standardDefaultTextFont)
- 		ifNil: [TextStyle defaultFont]!

Item was added:
+ ----- Method: Preferences class>>standardFixedFont (in category 'prefs - fonts') -----
+ standardFixedFont
+ 	"Answer the standard fixed font "
+ 
+ 	^ (UserInterfaceTheme current get: #standardFixedFont)
+ 		ifNil: [TextStyle defaultFixedFont]!

Item was changed:
  ----- Method: RealEstateAgent class>>initialFrameFor:initialExtent:world: (in category 'framing') -----
  initialFrameFor: aView initialExtent: initialExtent world: aWorld
  
  	| scaledExtent |
+ 	scaledExtent := (initialExtent * self scaleFactor) rounded.
- 	scaledExtent := Preferences bigDisplay
- 		ifTrue: [(initialExtent * 1.75) rounded]
- 		ifFalse: [initialExtent].
  
  	^ Preferences reverseWindowStagger
  		ifTrue: [self strictlyStaggeredInitialFrameFor: aView initialExtent: scaledExtent world: aWorld]
  		ifFalse: [self normalInitialFrameFor: aView initialExtent: scaledExtent world: aWorld]!

Item was added:
+ ----- Method: RealEstateAgent class>>scaleFactor (in category 'framing') -----
+ scaleFactor
+ 	"Use the default font height to calculate some factor. Better than nothing..."
+ 	
+ 	^ (TextStyle defaultFont height / 14 "reference value") * (Preferences bigDisplay ifTrue: [1.75] ifFalse: [1.0])!

Item was changed:
  ----- Method: SolarizedTheme class>>addDarkFonts: (in category 'instance creation') -----
  addDarkFonts: theme
  
  	"Set-up fonts."
  	theme
  		set: #balloonHelpFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7);
  		set: #standardButtonFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7);
  		set: #standardCodeFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
- 		set: #standardDefaultTextFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardFlapFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 7 emphasized: TextEmphasis bold emphasisCode);
  		set: #haloLabelFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardListFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardMenuFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #standardSystemFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9);
  		set: #windowTitleFont to: (StrikeFont familyName: 'Darkmap DejaVu Sans' pointSize: 9).!

Item was changed:
  ----- Method: SolarizedTheme class>>addLightFonts: (in category 'instance creation') -----
  addLightFonts: theme
  
  	"Set-up fonts."
  	theme
  		set: #balloonHelpFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7);
  		set: #standardButtonFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7);
  		set: #standardCodeFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
- 		set: #standardDefaultTextFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardFlapFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7 emphasized: TextEmphasis bold emphasisCode);
  		set: #haloLabelFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardListFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardMenuFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardSystemFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #windowTitleFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9 emphasized: TextEmphasis bold emphasisCode).!

Item was changed:
  ----- Method: SqueakTheme class>>addFonts: (in category 'instance creation') -----
  addFonts: theme
  
  	theme
  		set: #balloonHelpFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7);
  		set: #standardButtonFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7);
  		set: #standardCodeFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
- 		set: #standardDefaultTextFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardFlapFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 7 emphasized: TextEmphasis bold emphasisCode);
  		set: #haloLabelFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardListFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardMenuFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
  		set: #standardSystemFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9);
+ 		set: #standardFixedFont to: (TTCFont familyName: 'BitstreamVeraSansMono' pointSize: 12 emphasis: 0);
  		set: #windowTitleFont to: (StrikeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9 emphasized: TextEmphasis bold emphasisCode).
  !

Item was changed:
  ----- Method: SqueakTheme class>>addScrollables: (in category 'instance creation') -----
  addScrollables: theme
  	"self create apply"
  	
  	"Sliders"
  	theme
  		set: #borderColor for: #Slider to: Color gray;
  		set: #borderWidth for: #Slider to: 1;
  		set: #color for: #Slider to: Color lightGray;
  		set: #thumbBorderColor for: #Slider to: [Color gray: 0.6];
  		set: #thumbBorderWidth for: #Slider to: 0;
  		set: #thumbColor for: #Slider to: Color veryVeryLightGray;
  		set: #thumbShadowModifier for: #Slider to: [ [:c | c alpha: 0.7] ].
  				
  	"Scroll bars"
  	theme
  		set: #thumbBorderWidth for: #ScrollBar to: 1;
  		set: #thumbColorModifier for: #ScrollBar to: [ [:c | c] ];
  		set: #pagingAreaColorModifier for: #ScrollBar to: [ [:c | c darker alpha: 0.35] ];
  		set: #borderColorModifier for: #ScrollBar to: [ [:c | c adjustBrightness: -0.3] ].
  	
  	"Scroll panes (includes generic stuff for list widgets, tree widgets, and text widgets."
  	theme
  		set: #borderColor for: #ScrollPane to: (Color gray: 0.6);
  		set: #borderWidth for: #ScrollPane to: 1;
  		set: #borderStyle for: #ScrollPane to: BorderStyle default;
  		set: #color for: #ScrollPane to: Color white.
  		
  	"List widgets"
  	theme
  		set: #font for: #PluggableListMorph to: [Preferences standardListFont];
  		set: #textColor for: #PluggableListMorph to: Color black;
  		set: #selectionColor for: #PluggableListMorph to: (Color r: 0.72 g: 0.72 b: 0.9);
  		derive: #multiSelectionColor for: #PluggableListMorph from: #PluggableListMorph at: #selectionColor do: [:c | c lighter];
  		set: #selectionTextColor for: #PluggableListMorph to: Color black;
  		set: #filterColor for: #PluggableListMorph to: Color yellow paler;
  		set: #filterTextColor for: #PluggableListMorph to: Color black;
  		set: #preSelectionModifier for: #PluggableListMorph to: [ [:c | Color gray: 0.9] ];
  		set: #hoverSelectionModifier for: #PluggableListMorph to: [ [:c | c darker alpha: 0.3] ].
  		
  	"Tree widgets"
  	theme
  		derive: #font for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		derive: #textColor for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		derive: #selectionColor for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		derive: #selectionTextColor for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		derive: #filterColor for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		derive: #filterTextColor for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		derive: #hoverSelectionModifier for: #SimpleHierarchicalListMorph from: #PluggableListMorph;
  		
  		set: #higlightTextColor for: #SimpleHierarchicalListMorph to: Color red;
  		set: #lineColor for: #SimpleHierarchicalListMorph to: Color veryLightGray.
  	
  	"Text widgets"
  	theme
+ 		set: #font for: #PluggableTextMorph to: [Preferences standardSystemFont];
- 		set: #font for: #PluggableTextMorph to: [Preferences standardDefaultTextFont];
  		set: #textColor for: #PluggableTextMorph to: Color black;
  		set: #caretColor for: #PluggableTextMorph to: Color red;
  		set: #selectionColor for: #PluggableTextMorph to: (TranslucentColor r: 0.0 g: 0.0 b: 0.8 alpha: 0.2);
  		set: #unfocusedSelectionModifier for: #PluggableTextMorph to: [ [:c | Color gray: 0.9] ];
  		set: #adornmentReadOnly for: #PluggableTextMorph to: Color black;
  		set: #adornmentRefuse for: #PluggableTextMorph to: Color tan;
  		set: #adornmentConflict for: #PluggableTextMorph to: Color red;
  		set: #adornmentDiff for: #PluggableTextMorph to: Color green;
  		set: #adornmentNormalEdit for: #PluggableTextMorph to: Color orange;
  		set: #adornmentDiffEdit for: #PluggableTextMorph to: Color yellow;
  		set: #frameAdornmentWidth for: #PluggableTextMorph to: 1.
  	theme
  		set: #balloonTextColor for: #PluggableTextMorphPlus to: (Color gray: 0.7);
  		derive: #balloonTextFont for: #PluggableTextMorphPlus from: #PluggableTextMorph at: #font.!

Item was changed:
  Object subclass: #UserInterfaceTheme
+ 	instanceVariableNames: 'scope properties name next ignoreApply lastScaleFactor'
- 	instanceVariableNames: 'scope properties name next ignoreApply'
  	classVariableNames: 'All Current Default'
  	poolDictionaries: ''
  	category: 'System-Support'!
  
  !UserInterfaceTheme commentStamp: '<historical>' prior: 0!
  A UserInterfaceTheme is a dictionary of preferred visual-properties; colors, borderStyles, borderWidths, fonts, forms, etc. used to color and style the IDE.
  
  Accessing The Theme
  To access the proper UserInterfaceTheme instance for an object, send it #userInterfaceTheme.  The default implementation on Object provides the one instance of that is in-use by the IDE at the current time.
  
  Customizing The Theme
  We can ask the userInterfaceTheme for the value of any visual-property, by name:
  
  	mySystemWindow userInterfaceTheme closeBoxImage
  
  Initially, the above answers nil, which causes the legacy code to use whatever default it's always used.  To override various visual-properties of any kind of object, the #set: onAny: to: message can be used.  For example, 
  
  	myUserInterfaceTheme
  		set: #closeBoxImage 
  		for: SystemWindow
  		to: MenuIcons smallCancelIcon
  
  Alternatively, values may be derived based on other values in the theme, as in:
  
  	myUserInterfaceTheme
  		set: #color 
  		for: FillInTheBlankMorph
  		to: { MenuMorph->#color.  #twiceDarker }
  
  Now, the accessing expression, above, will answer will answer MenuIcons' smallCancelIcon instead of nil.  SystemWindow's code can be changed to use the expression above to access elements of the theme.
  
  Upgrading Legacy Code
  Following the introduction of this class, various client code all around the system must be modified to access it.  This variety of legacy code uses a variety of methods to specify their visual properties:
  
  	1) a hard-coded values.
  	2) a values derived from some other value.
  	3) providing local storage for a settable value which can be nil.
  	4) providing local storage for a settable value which is expected to always have a particular valid value (never nil).
  
  The requirement, for each case, is to let the value be overridden.  
  
  The solution for each of the above should be handled respectively to the above list, as follows:
  
  	1) Check the userInterfaceTheme, if that property returns nil, use the legacy hard-coded value.  (see example: SystemWindow>>#createCloseBox).
  	2) Nothing to do -- simply perform the same derivation on the result of (1).
  	3) Check the local storage, if present, use it.  If nil, then check the userInterfaceTheme, if it has this property present, use it, else return nil.
  	4) Check the userInterfaceTheme, if the property is not nil, use it, otherwise use the local value.
  
  Tool Support
  If a new access to #userInterfaceTheme is added to the code, be sure to add the property and its description to the #themeSettings for that class.  See implementors of #themeSettings for examples.!

Item was changed:
  ----- Method: UserInterfaceTheme>>apply (in category 'actions') -----
  apply
  	"Apply this theme to all affected objects. Let classes decide on how to iterate and call their instances."
  
  	ignoreApply == true ifTrue: [^ self].
+ 
- 	
  	UserInterfaceTheme current: self.
  
+ 	self fixFontsAndScaleAround: [
- 	self class clientClassesToReapply in: [:cc |
- 		cc do: [:eachClass | eachClass applyUserInterfaceTheme].
- 		Cursor wait showWhile: [
- 			SystemNavigation default allObjectsDo: [:o |
- 				((cc includes: o class)
- 					and: [o canApplyUserInterfaceTheme])
- 						ifTrue: [o applyUserInterfaceTheme]]]].
  
+ 		self class clientClassesToReapply in: [:cc |
+ 			cc do: [:eachClass | eachClass applyUserInterfaceTheme].
+ 			Cursor wait showWhile: [
+ 				SystemNavigation default allObjectsDo: [:o |
+ 					((cc includes: o class)
+ 						and: [o canApplyUserInterfaceTheme])
+ 							ifTrue: [o applyUserInterfaceTheme]]]].
+ 	]. "fix fonts"
+ 			
  	Project current restoreDisplay.!

Item was changed:
  ----- Method: UserInterfaceTheme>>applyAfter: (in category 'actions') -----
  applyAfter: block
  
  	ignoreApply := true.
+ 	lastScaleFactor := RealEstateAgent scaleFactor.
  	^ block ensure: [ignoreApply := false. self apply]!

Item was added:
+ ----- Method: UserInterfaceTheme>>fixFontsAndScaleAround: (in category 'private') -----
+ fixFontsAndScaleAround: block
+ 	"Due to the current situation with fonts and the real-estate manager, this is a small workaround to support theme switching with largely different font sizes."
+ 
+ 	lastScaleFactor ifNil: [lastScaleFactor := RealEstateAgent scaleFactor].
+ 
+ 	"Due to the current font situation, update TextConstants."
+ 	[	ignoreApply := true.
+ 		(self get: #standardSystemFont) ifNotNil: [:font | Preferences setSystemFontTo: font].
+ 		(self get: #standardFixedFont) ifNotNil: [:font | Preferences setFixedFontTo: font].
+ 	] ensure: [ignoreApply := false].
+ 
+ 	"Apply theme etc."
+ 	block value.
+ 				
+ 	"Due to the current real-estate manager situation, resize all windows. Works only for Morphic projects."
+ 	(RealEstateAgent scaleFactor - lastScaleFactor) abs > 0.5 ifTrue: [
+ 		Project current isMorphic ifTrue: [
+ 			| scale |
+ 			scale := RealEstateAgent scaleFactor / lastScaleFactor.
+ 			Project current world submorphs
+ 				select: [:ea | ea isSystemWindow]
+ 				thenDo: [:ea | ea extent: (ea extent * scale)]]].
+ 		
+ 	lastScaleFactor := nil.!



More information about the Packages mailing list