[squeak-dev] Re: Facelifting the second

Philipp Tessenow philipp.tessenow at student.hpi.uni-potsdam.de
Wed Mar 24 16:31:44 UTC 2010


-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

Hello,

> I'm getting
> an error about ByteString DNU: #! which looks like a wrongly formatted 
> change set. Can you fix it and resend?
> 
> Cheers,
>    - Andreas

I got that too, seemed to be a formatting error.
Here is the fixed changeset.

Regards,
  Philipp
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.9 (MingW32)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iQEcBAEBAgAGBQJLqj5wAAoJEOAfEteLmwSNxhkH/31m2kgT20ZQbK7PtDmIawEN
jEcGZ1BHKzAEBmkbVQgmdp3hVN4jHSovVjxTn4lru9BYICXBsl4URtSXtfMcBUcp
Q+WvEDipCRf2DlHD9/0ayku2Yn0UROmOsKGTyhl7K4LdHmdJXq+REmyqP8+k6waw
14cJWL7axfjjccpKIHvWo1o+x7OVo6EndppNG4rXKKVBq2A60pDEIq3z3vhuJngp
6TRZ9TsCn4AcGUiTKI8oI9+/OsTgLaXilsmQ0Fd6ZxQTUALJWOnGF5CuBigqVCg7
6ENmw8KiiciNjqgBcPjP/NSQDa9GsYPy6Ig67n0D/6h+nPrn+neE1D9b1SbLcNc=
=mJGz
-----END PGP SIGNATURE-----
-------------- next part --------------
'From Squeak3.11alpha of 28 February 2010 [latest update: #9527] on 24 March 2010 at 2:29:06 pm'!
"Change Set:		Botox Facelift
Date:			27 February 2010
Author:			Tim Felgentreff

Trying to improve the out-of-the-box Squeak look"
Preferences setPreference: #defaultWindowColor toValue: (Color veryVeryLightGray muchLighter).
(Preferences dictionaryOfPreferences at: #defaultWindowColor) defaultValue: (Color veryVeryLightGray muchLighter).

Preferences setPreference: #menuAppearance3d toValue: true.
(Preferences dictionaryOfPreferences at: #menuAppearance3d) defaultValue: true.

Preferences setPreference: #menuColorFromWorld toValue: false.
(Preferences dictionaryOfPreferences at: #menuColorFromWorld) defaultValue: false.

Preferences setPreference: #roundedMenuCorners toValue: false.
(Preferences dictionaryOfPreferences at: #roundedMenuCorners) defaultValue: false.

Preferences setParameter: #menuColor to: (Color gray: 0.9).
Preferences setParameter: #menuTitleColor to: (Color transparent).
Preferences setParameter: #menuTitleBorderWidth to: 0.
Preferences setParameter: #defaultWorldColor to: (Color gray: 0.25).

Preferences setPreference: #showSplitterHandles toValue: true.
(Preferences dictionaryOfPreferences at: #showSplitterHandles) defaultValue: true.

Preferences setPreference: #showSharedFlaps toValue: false.
(Preferences dictionaryOfPreferences at: #showSharedFlaps) defaultValue: false.

Preferences removePreference: #clickOnLabelToEdit.!

AbstractResizerMorph subclass: #CornerGripMorph
	instanceVariableNames: 'target '
	classVariableNames: 'ActiveForm PassiveForm DrawCornerResizeHandles '
	poolDictionaries: ''
	category: 'Morphic-Windows'!
RectangleMorph subclass: #FillInTheBlankMorph
	instanceVariableNames: 'response done textPane responseUponCancel '
	classVariableNames: 'RoundedDialogCorners '
	poolDictionaries: ''
	category: 'Morphic-Windows'!
Morph subclass: #LazyListMorph
	instanceVariableNames: 'listItems font selectedRow selectedRows listSource maxWidth '
	classVariableNames: 'ListSelectionColor ListSelectionTextColor '
	poolDictionaries: ''
	category: 'Morphic-Widgets'!
AlignmentMorph subclass: #PluggableButtonMorph
	instanceVariableNames: 'model label getStateSelector actionSelector getLabelSelector getMenuSelector shortcutCharacter askBeforeChanging triggerOnMouseDown offColor onColor feedbackColor showSelectionFeedback allButtons arguments argumentsProvider argumentsSelector '
	classVariableNames: 'RoundedButtonCorners '
	poolDictionaries: ''
	category: 'Morphic-Pluggable Widgets'!
AbstractResizerMorph subclass: #ProportionalSplitterMorph
	instanceVariableNames: 'leftOrTop rightOrBottom splitsTopAndBottom oldColor traceMorph handle '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!
MorphicModel subclass: #SystemWindow
	instanceVariableNames: 'labelString stripes label closeBox collapseBox activeOnlyOnTop paneMorphs paneRects collapsedFrame fullFrame isCollapsed menuBox mustNotClose labelWidgetAllowance updatablePanes allowReframeHandles labelArea expandBox '
	classVariableNames: 'CloseBoxImage CollapseBoxImage ExpandBoxImage MenuBoxImage ReuseWindows TopWindow CloseBoxFrame DoubleClickOnLabelToExpand ExpandBoxFrame MenuBoxFrame HideExpandButton ClickOnLabelToEdit '
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!Form methodsFor: 'converting' stamp: 'tfel 3/18/2010 21:02'!
darker

	^ Form 
		extent: self extent 
		depth: self depth
		bits: (self bits collect: [:bit | 
					(Color colorFromPixelValue: bit depth: self depth) 
						darker darker
						pixelValueForDepth: self depth])! !

!Form methodsFor: 'converting' stamp: 'tfel 3/18/2010 21:02'!
lighter

	^ Form 
		extent: self extent 
		depth: self depth
		bits: (self bits collect: [:bit | 
					(Color colorFromPixelValue: bit depth: self depth) 
						lighter lighter
						pixelValueForDepth: self depth])! !


!MCTool methodsFor: 'morphic ui' stamp: 'tfel 2/27/2010 22:23'!
defaultBackgroundColor 
	^ Preferences monticelloToolWindowColor! !


!MCTool class methodsFor: 'window color' stamp: 'tfel 2/27/2010 22:21'!
windowColorSpecification

	^ WindowColorSpec 
		classSymbol: self name 
		wording: 'Monticello Tool' 
		brightColor:  (Color r: 0.627 g: 0.69 b: 0.976)
		pastelColor: (Color r: 0.65 g: 0.753 b: 0.976) paler
		helpMessage: 'A Tool Window for the Monticello VCS'! !


!Morph methodsFor: 'drawing' stamp: 'tfel 2/27/2010 16:57'!
drawDropShadowOn: aCanvas

	aCanvas 
		translateBy: self shadowOffset 
		during: [ :shadowCanvas |
			shadowCanvas shadowColor: self shadowColor.
			shadowCanvas roundCornersOf: self during: [ 
				(shadowCanvas isVisible: self bounds) ifTrue:
					[shadowCanvas fillRectangle: self bounds fillStyle: self fillStyle]]
		].
! !


!CornerGripMorph methodsFor: 'drawing' stamp: 'tfel 2/28/2010 13:43'!
drawOn: aCanvas

	self class drawCornerResizeHandles
		ifTrue: [
			bounds := self bounds.
			aCanvas 
				translucentImage: (self alphaHandle) 
				at: (bounds origin ) 
				sourceRect: (self handleOrigin extent: bounds extent)]! !


!CornerGripMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 13:42'!
drawCornerResizeHandles
	<preference: 'Draw Corner Resize Handles'
		category: 'windows'
		description: 'Governs the resize handles on windows should be drawn. This does not disable them'
		type: #Boolean>
	^ DrawCornerResizeHandles ifNil: [ false ]! !

!CornerGripMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:04'!
drawCornerResizeHandles: aBoolean
	
	DrawCornerResizeHandles := aBoolean.
	World invalidRect: World bounds from: World.! !


!FillInTheBlankMorph methodsFor: 'initialization' stamp: 'tfel 2/27/2010 16:26'!
createTextPaneExtent: answerExtent acceptBoolean: acceptBoolean topOffset: topOffset buttonAreaHeight: buttonAreaHeight 
	"create the textPane"
	| result frame |
	result := PluggableTextMorph
				on: self
				text: #response
				accept: #response:
				readSelection: #selectionInterval
				menu: #codePaneMenu:shifted:.
	result 
		extent: answerExtent;
		alwaysShowScrollBars: false;
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		borderWidth: 1;
		hasUnacceptedEdits: true;
		acceptOnCR: acceptBoolean;
		setNameTo: 'textPane'.
	frame := LayoutFrame new
				leftFraction: 0.0;
		 		rightFraction: 1.0;
		 		topFraction: 0.0;
		 		topOffset: topOffset;
		 		bottomFraction: 1.0;
		 		bottomOffset: buttonAreaHeight negated;
				yourself.
	result layoutFrame: frame.
	self addMorph: result.
	^ result! !

!FillInTheBlankMorph methodsFor: 'initialization' stamp: 'tfel 2/28/2010 13:17'!
initialize

	super initialize.
	self setDefaultParameters.
	self extent: 400 @ 150.
	responseUponCancel := ''.
	self class roundedDialogCorners ifTrue: [self useRoundedCorners].
	! !

!FillInTheBlankMorph methodsFor: 'initialization' stamp: 'tfel 2/27/2010 16:06'!
setQuery: queryString initialAnswer: initialAnswer answerExtent: answerExtent acceptOnCR: acceptBoolean 
	| query topOffset accept cancel buttonAreaHeight |
	response := initialAnswer.
	done := false.
	self removeAllMorphs.
	self layoutPolicy: ProportionalLayout new.
	query := self createQueryTextMorph: queryString.
	topOffset := query height + 4.
	accept := self createAcceptButton.
	cancel := self createCancelButton.
	buttonAreaHeight := (accept height max: cancel height)
				+ 7.
	textPane := self
				createTextPaneExtent: answerExtent
				acceptBoolean: acceptBoolean
				topOffset: topOffset
				buttonAreaHeight: buttonAreaHeight.
	self extent: (query extent x max: answerExtent x)
			+ 4 @ (topOffset + answerExtent y + 4 + buttonAreaHeight).
	! !


!FillInTheBlankMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 13:27'!
roundedDialogCorners
	<preference: 'Rounded Dialog Corners'
		category: 'windows'
		description: 'Governs whether dialog windows should have rounded corners'
		type: #Boolean>
	^ RoundedDialogCorners ifNil: [ true ]! !

!FillInTheBlankMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:05'!
roundedDialogCorners: aBoolean
	
	RoundedDialogCorners := aBoolean.
	self allInstances do: [:instance | 
		aBoolean 
			ifTrue: [instance useRoundedCorners]
			ifFalse: [instance useSquareCorners]].! !


!IconicButton methodsFor: 'accessing' stamp: 'tfel 3/18/2010 21:04'!
highlight

	self firstSubmorph form: self firstSubmorph form lighter.! !

!IconicButton methodsFor: 'as yet unclassified' stamp: 'tfel 3/18/2010 21:05'!
darken

	self firstSubmorph form: self firstSubmorph form darker.! !

!IconicButton methodsFor: 'as yet unclassified' stamp: 'tfel 3/18/2010 21:11'!
labelGraphic: aForm
	| oldLabel graphicalMorph |
	(oldLabel := self findA: SketchMorph)
		ifNotNil: [oldLabel delete].
	graphicalMorph := SketchMorph withForm: aForm.
	self extent: graphicalMorph extent + (borderWidth + 6).
	graphicalMorph position: self center - (graphicalMorph extent // 2).
	self addMorph: graphicalMorph.
	graphicalMorph 
		baseGraphic;
		lock.
! !

!IconicButton methodsFor: 'as yet unclassified' stamp: 'tfel 3/18/2010 21:05'!
restoreImage

	self firstSubmorph restoreBaseGraphic.! !

!IconicButton methodsFor: 'events' stamp: 'tfel 3/18/2010 21:34'!
handlesMouseOver: evt

	^ true! !

!IconicButton methodsFor: 'events' stamp: 'tfel 3/18/2010 21:25'!
mouseEnter: evt

	self highlight.! !

!IconicButton methodsFor: 'events' stamp: 'tfel 3/18/2010 21:30'!
mouseLeave: evt

	self restoreImage.! !

!IconicButton methodsFor: 'visual properties' stamp: 'tfel 3/18/2010 21:36'!
updateVisualState: evt

	(self containsPoint: evt cursorPoint)
		ifTrue: [self darken]
		ifFalse: [self restoreImage].! !

!IconicButton methodsFor: 'button' stamp: 'tfel 3/18/2010 21:38'!
doButtonAction

	super doButtonAction.
	self restoreImage.! !


!LazyListMorph methodsFor: 'drawing' stamp: 'tfel 2/28/2010 13:49'!
colorForRow: row
	
	^(selectedRow notNil and: [ row = selectedRow])
		ifTrue: [ self class listSelectionTextColor ]
		ifFalse: [ self color ].! !

!LazyListMorph methodsFor: 'drawing' stamp: 'tfel 2/28/2010 13:33'!
drawSelectionOn: aCanvas
	
	| selectionDrawBounds |
	selectedRow ifNil: [ ^self ].
	selectedRow = 0 ifTrue: [ ^self ].
	selectionDrawBounds := self drawBoundsForRow: selectedRow.
	selectionDrawBounds := selectionDrawBounds intersect: self bounds.
	aCanvas fillRectangle: selectionDrawBounds color: self class listSelectionColor.! !


!LazyListMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 13:46'!
listSelectionColor
	<preference: 'List Selection Color'
		category: 'colors'
		description: 'Governs the selection background in lists'
		type: #Color>
	^ ListSelectionColor ifNil: [Color r: 0.72 g: 0.72 b: 0.9]! !

!LazyListMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:04'!
listSelectionColor: aColor

	ListSelectionColor := aColor.
	World invalidRect: World bounds from: World.! !

!LazyListMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:04'!
listSelectionTextColor
	<preference: 'List Selection Text Color'
		category: 'colors'
		description: 'Governs the color of selected text in lists'
		type: #Color>
	^ ListSelectionTextColor ifNil: [Color black]! !

!LazyListMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 13:49'!
listSelectionTextColor: aColor
	
	ListSelectionTextColor := aColor.
	World invalidRect: World bounds from: World.! !


!MenuItemMorph methodsFor: 'layout' stamp: 'tfel 2/27/2010 19:27'!
minHeight
	| iconHeight |
	iconHeight := self hasIcon
				ifTrue: [self icon height + 2]
				ifFalse: [0].
	^ self fontToUse height + 2 max: iconHeight! !


!MenuMorph methodsFor: 'construction' stamp: 'tfel 2/27/2010 16:55'!
addTitle: aString icon: aForm updatingSelector: aSelector updateTarget: aTarget 
	"Add a title line at the top of this menu Make aString its initial  
	contents.  
	If aSelector is not nil, then periodically obtain fresh values for  
	its  
	contents by sending aSelector to aTarget.."
	| title titleContainer |
	title := AlignmentMorph newColumn.
	self setTitleParametersFor: title.
	""
	aForm isNil
		ifTrue: [titleContainer := title]
		ifFalse: [| pair | 
			pair := AlignmentMorph newRow.

			pair color: Color transparent.
			pair hResizing: #shrinkWrap.
			pair layoutInset: 0.
			""
			pair addMorphBack: aForm asMorph.
			""
			titleContainer := AlignmentMorph newColumn.
			titleContainer color: Color transparent.
			titleContainer vResizing: #shrinkWrap.
			titleContainer wrapCentering: #center.
			titleContainer cellPositioning: #topCenter.
			titleContainer layoutInset: 0.
			pair addMorphBack: titleContainer.
			""
			title addMorphBack: pair].
	""
	aSelector
		ifNil: [""
			aString asString
				linesDo: [:line | titleContainer 
					addMorphBack: ((StringMorph 
										contents: line 
										font: Preferences standardMenuFont)
										color: (Color gray: 0.5);
										yourself)]]
		ifNotNil: [| usm | 
			usm := UpdatingStringMorph on: aTarget selector: aSelector.
			usm font: Preferences standardMenuFont.
			usm useStringFormat.
			usm lock.
			titleContainer addMorphBack: usm].
	""
	title setProperty: #titleString toValue: aString.
	self addMorphFront: title.
	""
	title useSquareCorners.
	(self hasProperty: #needsTitlebarWidgets)
		ifTrue: [self addStayUpIcons]! !

!MenuMorph methodsFor: 'initialization' stamp: 'tfel 2/27/2010 16:28'!
setDefaultParameters
	"change the receiver's appareance parameters"

	| colorFromMenu worldColor menuColor |
	
	colorFromMenu := Preferences menuColorFromWorld
									and: [Display depth > 4
									and: [(worldColor := self currentWorld color) isColor]].

	menuColor := colorFromMenu
						ifTrue: [worldColor luminance > 0.7
										ifTrue: [worldColor mixed: 0.85 with: Color black]
										ifFalse: [worldColor mixed: 0.4 with: Color white]]
						ifFalse: [Preferences menuColor].

	self color: menuColor.
	self borderWidth: Preferences menuBorderWidth.

	Preferences menuAppearance3d ifTrue: [
		self borderStyle: BorderStyle thinGray.
		self
			addDropShadow;
			shadowColor: (TranslucentColor r: 0.0 g: 0.0 b: 0.0 alpha: 0.1);
			shadowOffset: 5 @ 5
	]
	ifFalse: [
		| menuBorderColor |
		menuBorderColor := colorFromMenu
										ifTrue: [worldColor muchDarker]
										ifFalse: [Preferences menuBorderColor].
		self borderColor: menuBorderColor.
	].


	self layoutInset: 6.
! !


!PBWindowColorPreferenceView methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:34'!
initialize
	super initialize.
	self addActionTitled: 'Bright' target: Preferences selector: #installBrightWindowColors arguments: {} balloonText: 'Use standard bright colors for all windows' translated.
	self addActionTitled: 'Pastel' target: Preferences selector: #installPastelWindowColors arguments: {} balloonText: 'Use standard pastel colors for all windows' translated.	
	self addActionTitled: 'Gray' target: Preferences selector: #installUniformWindowColors arguments: {} balloonText: 'Use gray backgrounds for all standard windows' translated.! !


!PasteUpMorph methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:56'!
defaultColor
	"answer the default color/fill style for the receiver"
	^ Preferences defaultWorldColor muchLighter.! !


!PluggableButtonMorph methodsFor: 'drawing' stamp: 'tfel 2/28/2010 13:39'!
drawOn: aCanvas 
	| cc gradient |
	cc := self color.
	cc isTransparent ifTrue:[cc := Color gray: 0.9].
	self enabled ifFalse:[cc := Color lightGray].
	cc brightness > 0.9 ifTrue:[cc := cc adjustBrightness: 0.9 - cc brightness].
	showSelectionFeedback ifTrue:[
		gradient := GradientFillStyle ramp: {
			0 -> (Color gray: 0.75).
			0.5 -> (Color gray: 0.85).
			0.51 -> (Color gray: 0.9).
			1 -> (Color gray: 1).
		}.
	] ifFalse:[
		gradient := GradientFillStyle ramp: {
			0.0 -> Color white.
			0.5 -> (cc).
			0.51-> (cc adjustBrightness: -0.1).
			1 -> (Color gray: 0.95).
		}
	].
	gradient origin: bounds topLeft.
	gradient direction: 0 at self height.
	^ self class roundedButtonCorners
		ifTrue: [aCanvas frameAndFillRoundRect: bounds radius: 8 fillStyle: gradient borderWidth: 1 borderColor: Color lightGray]
		ifFalse: [
			aCanvas 
					frameAndFillRectangle: self innerBounds fillColor: gradient asColor borderWidth: 1 borderColor: Color gray;
					fillRectangle: (self innerBounds insetBy: 1) fillStyle: gradient]! !

!PluggableButtonMorph methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:55'!
defaultColor
	"answer the default color/fill style for the receiver"
	^ Color gray: 0.7! !


!PluggableButtonMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 13:35'!
roundedButtonCorners
	<preference: 'Rounded Button Corners'
		category: 'windows'
		description: 'Governs whether pluggable buttons in system windows should be rounded'
		type: #Boolean>
	^ RoundedButtonCorners ifNil: [ true ]! !

!PluggableButtonMorph class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:06'!
roundedButtonCorners: aBoolean

	RoundedButtonCorners := aBoolean.
	World invalidRect: World bounds from: World.! !


!Preferences class methodsFor: 'window colors' stamp: 'tfel 2/28/2010 16:54'!
installUniformWindowColors
	"Install the factory-provided uniform window colors for all tools"

	"Preferences installUniformWindowColors"
	self installWindowColorsVia: [:aQuad | Color veryVeryLightGray muchLighter]! !

!Preferences class methodsFor: 'window colors' stamp: 'tfel 2/27/2010 19:34'!
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"! !


!ProportionalSplitterMorph methodsFor: 'initialization' stamp: 'tfel 2/27/2010 17:46'!
initialize

	super initialize.
	
	self hResizing: #spaceFill.
	self vResizing: #spaceFill.
	splitsTopAndBottom := false.
	
	leftOrTop := OrderedCollection new.
	rightOrBottom := OrderedCollection new.
	
	Preferences showSplitterHandles 
		ifTrue: [
			handle := CircleMorph new
					borderWidth: 0;
					extent: 4 at 4;
					yourself.
			handle fillStyle: ((GradientFillStyle 
						ramp: {0.0 -> Preferences defaultWindowColor muchLighter. 
							1.0 -> Preferences defaultWindowColor darker})
						origin: handle topLeft;
						direction: 0 @ handle bounds extent y;
						normal: handle bounds extent x @ 0;
						radial: false;
						yourself).
			self addMorphCentered: handle].! !

!ProportionalSplitterMorph methodsFor: 'events' stamp: 'tfel 2/27/2010 17:50'!
mouseMove: anEvent 
	anEvent hand temporaryCursor
		ifNil: [^ self].
	self class fastSplitterResize
		ifFalse:  [self updateFromEvent: anEvent]
		ifTrue: [traceMorph
				ifNil: [traceMorph := Morph newBounds: self bounds.
					traceMorph color: (Color gray alpha: 0.5).
					traceMorph borderWidth: 0.
					self owner addMorph: traceMorph].
			splitsTopAndBottom
				ifTrue: [traceMorph position: traceMorph position x @ (self normalizedY: anEvent cursorPoint y)]
				ifFalse: [traceMorph position: (self normalizedX: anEvent cursorPoint x) @ traceMorph position y]]! !

!ProportionalSplitterMorph methodsFor: 'layout' stamp: 'tfel 2/27/2010 17:45'!
layoutChanged	
	
	super layoutChanged.
	handle ifNotNil: [handle position: self bounds center - (2 at 2)]! !


!ServiceGui methodsFor: 'styling' stamp: 'tfel 2/27/2010 16:23'!
styleBar: aBar
	aBar setNameTo: 'button bar'.
	aBar beSticky;
		 hResizing: #spaceFill;
		wrapCentering: #center;
		cellPositioning: #leftCenter;
		clipSubmorphs: true;
		cellInset: 0;
		color: Preferences defaultWindowColor.! !


!SystemWindow methodsFor: 'events' stamp: 'tfel 2/28/2010 16:06'!
startDragFromLabel: evt
	"When label events are active, we need to pass dragging to the window explicitely
	 The window only recognizes a drag with an offset of more than 3 pixels"
	
	self setProperty: #clickPoint toValue: evt cursorPoint - 4.
	self mouseMove: evt.! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 14:12'!
addCloseBox
	"If I have a labelArea, add a close box to it"

	labelArea
		ifNil: [^ self].
	closeBox ifNotNil: [closeBox delete].
	closeBox := self createCloseBox.
	closeBox layoutFrame: self class closeBoxFrame.
	labelArea addMorphFront: closeBox! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 14:51'!
addExpandBox
	"If I have a labelArea, add a close box to it"
	
	labelArea ifNil: [^ self].
	self class hideExpandButton ifTrue: [^ self].
	expandBox ifNotNil: [expandBox delete].
	expandBox := self createExpandBox.
	expandBox layoutFrame: self class expandBoxFrame.
	labelArea addMorphBack: expandBox! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 14:14'!
addMenuControl
	"If I have a label area, add a menu control to it."
	
	labelArea ifNil: [^ self].
	"No menu if no label area"
	menuBox ifNotNil: [menuBox delete].
	menuBox := self createMenuBox.
	menuBox layoutFrame: self class menuBoxFrame.
	labelArea addMorphBack: menuBox! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 14:00'!
boxExtent
	"the label height is used to be proportional to the fonts preferences"
	
	^ self class boxExtent
		max: label height @ label height ! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 3/18/2010 21:33'!
createBox: aForm
	"create a button with a form to be used in the label area"
	
	| box |
	box := IconicButton new.
	box color: Color transparent;
		 target: self;
		 useSquareCorners;
		 borderWidth: 0;
		 labelGraphic: aForm;
		 extent: self boxExtent.
	^ box! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:09'!
createCloseBox
	^ (self createBox: self class closeBoxImage)
		actionSelector: #closeBoxHit;
		setBalloonText: 'close this window' translated! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:09'!
createCollapseBox
	^ (self createBox: self class collapseBoxImage)
		actionSelector: #collapseOrExpand;
		setBalloonText: 'collapse this window' translated.
! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:09'!
createExpandBox
	^ (self createBox: self class expandBoxImage)
		actionSelector: #expandBoxHit;
		setBalloonText: 'expand to full screen' translated! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/27/2010 22:31'!
createMenuBox
	^ (self createBox: self class menuBoxImage)
		actionSelector: #offerWindowMenu;
		setBalloonText: 'window menu' translated! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/27/2010 20:11'!
defaultBorderWidth
	"answer the default border width for the receiver"
	^ 2.! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/27/2010 19:52'!
gradientWithColor: aColor

	| gradient |
	gradient := GradientFillStyle ramp: {
		0.0 -> Color white. 
		0.2 -> (aColor mixed: 0.5 with: (Color gray: 0.9)) lighter. 
		1.0 -> aColor.
	}.
	gradient origin: self topLeft.
	gradient direction: 0 @ self labelHeight.
	^gradient! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 16:35'!
initialize
	"Initialize a system window. Add label, stripes, etc., if desired"
	super initialize.
	allowReframeHandles := true.
	labelString ifNil: [labelString := 'Untitled Window'].
	isCollapsed := false.
	activeOnlyOnTop := true.
	paneMorphs := Array new.
	borderColor := Color lightGray.
	borderWidth := 1.
	self color: Color veryVeryLightGray muchLighter.
	self layoutPolicy: ProportionalLayout new.
	
	self initializeLabelArea.
				
	self addCornerGrips.

	self extent: 300 @ 200.
	mustNotClose := false.
	updatablePanes := Array new.
		
	Preferences menuAppearance3d
		ifTrue: [
			self
				addDropShadow;
				shadowColor: (TranslucentColor r: 0.0 g: 0.0 b: 0.0 alpha: 0.333);
				shadowOffset: 1 at 1.
		].
					! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 16:18'!
initializeLabelArea
	"Initialize the label area (titlebar) for the window."
	label := StringMorph new contents: labelString;
						 font: Preferences windowTitleFont emphasis: 0.
			"Add collapse box so #labelHeight will work"
			collapseBox := self createCollapseBox.
			stripes := Array
						with: (RectangleMorph newBounds: bounds)
						with: (RectangleMorph newBounds: bounds).
			"see extent:"
			self addLabelArea.
			self setLabelWidgetAllowance.
			self addCloseBox.
			self class moveMenuButtonRight 
				ifTrue: [self addLabel. self addMenuControl]
				ifFalse: [self addMenuControl. self addLabel].
			self addExpandBox.
			labelArea addMorphBack: collapseBox.
			self setFramesForLabelArea.
			Preferences noviceMode
				ifTrue: [closeBox
						ifNotNil: [closeBox setBalloonText: 'close window'].
					menuBox
						ifNotNil: [menuBox setBalloonText: 'window menu'].
					collapseBox
						ifNotNil: [collapseBox setBalloonText: 'collapse/expand window']].
! !

!SystemWindow methodsFor: 'initialization' stamp: 'tfel 2/28/2010 14:55'!
replaceBoxes
	"Rebuild the various boxes."
	self setLabelWidgetAllowance.
	label ifNotNil: [label delete].
	labelArea ifNotNil: [labelArea delete].
	self initializeLabelArea.
	self setFramesForLabelArea.
	self setWindowColor: self paneColor.
	self isActive ifFalse: [self passivate].! !

!SystemWindow methodsFor: 'label' stamp: 'tfel 2/28/2010 16:24'!
addLabel

	(labelArea isNil or: [label isNil]) ifTrue: [^ self].
	labelArea 
		addMorphBack: (Morph new extent: self class borderWidth @ 0);
		addMorphBack: label.
	label on: #startDrag send: #startDragFromLabel: to: self.
	self class clickOnLabelToEdit
		ifTrue: [label on: #mouseUp send: #relabel to: self].
	self class doubleClickOnLabelToExpand
		ifTrue: [label on: #doubleClick send: #expandBoxHit to: self].! !

!SystemWindow methodsFor: 'resize/collapse' stamp: 'tfel 2/27/2010 20:21'!
contractToOriginalSize
	self bounds: self unexpandedFrame.
	self unexpandedFrame: nil.
	expandBox ifNotNil: [expandBox setBalloonText: 'expand to full screen' translated].! !

!SystemWindow methodsFor: 'resize/collapse' stamp: 'tfel 2/27/2010 20:21'!
expandToFullScreen
	self unexpandedFrame ifNil: [ self unexpandedFrame: fullFrame ].
	self fullScreen.
	expandBox ifNotNil: [expandBox setBalloonText: 'contract to original size' translated]! !

!SystemWindow methodsFor: 'resize/collapse' stamp: 'tfel 2/27/2010 20:20'!
wantsExpandBox
	"Answer whether I'd like an expand box"

	^ Preferences alwaysHideExpandButton not! !


!SystemWindow class methodsFor: 'initializing' stamp: 'tfel 3/24/2010 14:26'!
closeBoxImage
	"Supplied here because we don't necessarily have ComicBold"

	^ CloseBoxImage ifNil: [CloseBoxImage := (Form
	extent: 14 at 14
	depth: 32
	fromArray: #(0 0 6032910 288687365 1550655006 2844865845 3450028610 3450028610 2828088372 1550655006 288687365 5967374 0 0 1377027 15091784 844830230 3063889984 4158092147 4294153621 4294681250 4294681250 4294153364 4158091376 3047046718 844764694 14763847 1376770 7742243 861541910 3585164870 4294282123 4294943908 4294943908 4294943651 4294943651 4294943908 4294943908 4294216330 3585099848 844764694 7676450 288098055 3047109684 4294211447 4294939539 4293757578 4293363848 4294939025 4294939282 4293954186 4293560456 4294939539 4294212732 3047110455 288031748 1584209695 4158081610 4294932343 4293753466 4291733929 4291802549 4293164156 4293884281 4291666594 4291670192 4293294457 4294933885 4158018130 1567432222 2861706541 4294136145 4294924376 4292761945 4292198592 4294704894 4292064950 4291403679 4294375158 4293057499 4291846497 4294925147 4294136659 2844863789 3483644980 4294660947 4294923605 4294857555 4292566879 4292658886 4294770173 4294704380 4293452000 4291981681 4294595154 4294923605 4294660947 3466867764 3500422196 4294726483 4294923605 4294923605 4293742415 4291402908 4294836223 4294967295 4292198592 4292760660 4294923348 4294923605 4294660947 3483644980 2878484014 4294136145 4294923605 4293939794 4291728018 4294375158 4293452257 4292793042 4294704637 4292128944 4293154390 4294923605 4294136145 2878484014 1617830177 4174923591 4294923862 4292957011 4292000442 4293386721 4291915888 4292238685 4292659400 4292595406 4292303450 4294923605 4158146375 1617829920 305072650 3097572147 4294267217 4294923348 4292631901 4291781989 4294595154 4294857555 4292435036 4292238942 4294857812 4294267217 3097506611 305007114 8070437 912005658 3635624249 4294333010 4294923605 4294857555 4294923605 4294923605 4294923348 4294923348 4294333010 3635624249 895228442 8004901 1639428 16735838 912071451 3131126579 4191766343 4294267217 4294726740 4294726740 4294201681 4191766343 3131126579 895293978 16735067 1573892 0 0 6888733 322506254 1651515681 2945723950 3550885173 3550885173 2945723950 1651515681 322440718 6822940 0 0)
	offset: 0 at 0)]! !

!SystemWindow class methodsFor: 'initializing' stamp: 'tfel 3/24/2010 14:26'!
collapseBoxImage
	"Supplied here because we don't necessarily have ComicBold"

	^ CollapseBoxImage ifNil: [CollapseBoxImage := (Form
	extent: 14 at 14
	depth: 32
	fromArray: #(0 0 5854464 288568064 1550541582 2844754727 3449983798 3449983798 2827977511 1550541581 288568064 5788928 0 0 1251328 15059494 844715013 3063844916 4158047598 4294173075 4294699425 4294699425 4294172818 4158047339 3047001906 844715013 14730789 1251328 7695120 861426436 3585122108 4294238345 4294963108 4294962852 4294962595 4294962595 4294962852 4294963108 4294238345 3585056574 844649220 7629583 287911168 3047067176 4294237302 4294962067 4294961553 4294961553 4294961553 4294961553 4294961553 4294961810 4294962068 4294237563 3047067180 287910912 1584096270 4158045509 4294960759 4294960767 4294961024 4294961025 4294961025 4294961024 4294961023 4294960763 4294960505 4294961022 4158045773 1567318796 2861597216 4294169679 4294958680 4294235481 4293972830 4294038626 4294038626 4294038367 4294038106 4293972308 4294103635 4294892891 4294169682 2844820000 3483603497 4294761043 4294498129 4291279233 4292465594 4292465592 4292465592 4292465592 4292465592 4292531386 4291346328 4293643602 4294826835 3466826281 3500380713 4294761299 4294366544 4291675295 4294112246 4294111987 4294111987 4294111987 4294111987 4294243574 4292203203 4293446228 4294826835 3483603497 2878440481 4294169679 4294826836 4292526427 4292395625 4292395625 4292395625 4292395625 4292395625 4292395626 4292263777 4294366803 4294235215 2878440225 1617716496 4174888258 4294958934 4294958676 4294958675 4294958675 4294958675 4294958675 4294958675 4294958675 4294958676 4294959190 4158111042 1617716496 304951552 3097530152 4294301264 4294958677 4294958421 4294958421 4294958421 4294958421 4294958421 4294958421 4294958677 4294301264 3097464616 304886016 7958548 911889929 3635584561 4294366800 4294958934 4294958677 4294958421 4294958421 4294958677 4294958934 4294366800 3635584561 895112713 7892755 1514752 16775998 911955722 3131084841 4191796803 4294235216 4294761299 4294761299 4294235216 4191796803 3131084840 895178506 16774203 1448960 0 0 6710533 322386432 1651402770 2945615139 3550843947 3550843947 2945615139 1651402770 322320896 6644741 0 0)
	offset: 0 at 0)]! !

!SystemWindow class methodsFor: 'initializing' stamp: 'tfel 3/24/2010 14:22'!
expandBoxImage

	^ ExpandBoxImage ifNil: [ExpandBoxImage := (Form
	extent: 14 at 14
	depth: 32
	fromArray: #(0 0 1058562 285544960 1545616142 2838976800 3443812652 3443812652 2822199328 1545550349 285610496 1058562 0 0 197889 5015843 840445449 3057804586 4151680347 4288134782 4288989580 4288989580 4288134525 4151549016 3040961576 840379656 4949796 132352 2441745 857222409 3578360366 4287543665 4289187213 4289121422 4288857993 4288792456 4289121421 4289121677 4287478128 3578491696 840445193 2375953 285740802 3040304923 4286295641 4288070777 4288004983 4287543410 4288524177 4289312671 4287344755 4288004983 4288136313 4286624095 3040502048 285543680 1579236111 4149118761 4286297173 4286822495 4286888545 4286426462 4291679432 4293717227 4286752873 4286560090 4286428504 4286691421 4149578546 1562393102 2855294231 4283865130 4284326448 4284325172 4284718907 4284716865 4291416516 4293651691 4285043786 4284061998 4283996461 4284523316 4283996461 2838517015 3476513307 4284063275 4283865386 4287341947 4290759608 4290693559 4293717483 4294572537 4291153599 4290759607 4288129929 4283864876 4283997739 3459736090 3493290523 4284063275 4283799593 4289312927 4294243316 4294046193 4294769916 4294901502 4294177779 4294243316 4290364338 4283864621 4284063275 3476513306 2872071703 4283865130 4284063275 4284453693 4285176395 4285109069 4291811019 4293849070 4285962336 4285110602 4284585024 4283997227 4283799593 2872071447 1612856592 4165698852 4284195372 4284063786 4284064041 4283864620 4291285440 4293651690 4284782402 4283998248 4284063786 4284195372 4148921636 1612856336 302649860 3090571034 4283865642 4284129580 4284129580 4283930157 4289378465 4291218626 4284519486 4284064042 4284129580 4283865642 3090505498 302649604 2573587 907751437 3627904029 4283865642 4284195372 4284063275 4284060978 4284126260 4283996972 4284195372 4283865642 3627838237 890974221 2573330 263937 6533168 907817229 3124125722 4182476324 4283865386 4284063531 4284063531 4283865386 4182476324 3124125722 891040013 6335279 263937 0 0 1979406 319691015 1646476817 2939246103 3543687963 3543687963 2939246103 1646476817 319691015 1979406 0 0)
	offset: 0 at 0) ]! !

!SystemWindow class methodsFor: 'initializing' stamp: 'tfel 3/24/2010 14:20'!
menuBoxImage

	^ MenuBoxImage ifNil: [MenuBoxImage := (Form
	extent: 14 at 14
	depth: 32
	fromArray: #(0 0 7774 285216318 1544039783 2837267842 3442168720 3442168720 2820490625 1544039782 285216574 7774 0 0 2087 1532860 839001178 3056161165 4150166716 4286817494 4287738079 4287803615 4286751958 4150035131 3039252364 839001178 1467065 1831 668526 855712858 3576584601 4286029012 4287935459 4287935458 4287869666 4287869666 4287935458 4287869923 4285963476 3576715929 838935642 602733 285216827 3038463881 4284517582 4286621149 4286489564 4286489564 4286489564 4286489564 4286489564 4286489820 4286621149 4284911823 3038726794 285216058 1577594471 4147012271 4284387029 4284978391 4285043927 4285109719 4285109719 4285044183 4284978135 4284649685 4284518357 4284912599 4147603633 1560751463 2853453696 4281560257 4281888189 4283200687 4284186808 4284515256 4284515257 4284252600 4283858102 4283529653 4282740653 4282151359 4281757378 2836676480 3474606220 4281757894 4281559740 4285761703 4292993507 4293454315 4293388522 4293388522 4293454315 4292862177 4285432998 4281494205 4281692102 3457829004 3491383436 4281757638 4281758153 4281953722 4288589251 4294835708 4294967295 4294967295 4294769659 4288194752 4281887931 4281823689 4281692102 3474606220 2870296704 4281560257 4281823689 4281758153 4282215861 4289838026 4294967294 4294967038 4289377991 4282084534 4281758153 4281823689 4281560257 2870296704 1611280232 4163592111 4281823946 4281823688 4281692360 4282740914 4291152852 4290758353 4282544051 4281692361 4281823688 4281823946 4146749358 1611214696 301994814 3088664202 4281626050 4281823689 4281823688 4281692103 4282937773 4282806447 4281692360 4281823688 4281823689 4281626050 3088664202 301994814 734577 906307420 3625930390 4281626050 4281823946 4281823689 4281692360 4281692360 4281823689 4281823946 4281626050 3625930390 889530204 734576 2347 2392036 906373213 3122218634 4180369583 4281560257 4281757638 4281757638 4281560257 4180369583 3122218634 889595997 2325471 2346 0 3 76907 318773060 1644834921 2937405569 3541780621 3541780621 2937405569 1644834921 318773059 76906 2 0)
	offset: 0 at 0)]! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 13:59'!
boxExtent
	"answer the extent to use in all the buttons"
	
	^ (Preferences alternativeWindowBoxesLook
		ifTrue: [18 @ 18]
		ifFalse: [14 @ 14])! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 16:15'!
clickOnLabelToEdit

	<preference: 'Click On Label To Edit'
		category: 'windows'
		description: 'If true, a click on the label of a system window lets you edit it'
		type: #Boolean>
	^ ClickOnLabelToEdit ifNil: [false].
! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 16:17'!
clickOnLabelToEdit: aBoolean

	ClickOnLabelToEdit := aBoolean.
	self rebuildAllWindowLabels.! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:11'!
closeBoxFrame

	^ CloseBoxFrame ifNil: [
		CloseBoxFrame := (LayoutFrame new
								leftFraction: 0;
								leftOffset: 2;
								topFraction: 0;
								topOffset: 0;
								yourself)]! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 16:21'!
doubleClickOnLabelToExpand

	<preference: 'Double-Click On Label To Expand'
		category: 'windows'
		description: 'Activates expansion through double-clicking on the window label area. This mimics the behavior in many current operating systems'
		type: #Boolean>
	^ DoubleClickOnLabelToExpand ifNil: [true].
! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 16:17'!
doubleClickOnLabelToExpand: aBoolean

	DoubleClickOnLabelToExpand := aBoolean.
	self rebuildAllWindowLabels.
! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:10'!
expandBoxFrame

	^ ExpandBoxFrame ifNil: [
		ExpandBoxFrame := (LayoutFrame new
								leftFraction: 1;
								leftOffset: (self boxExtent x * 2 + 3) negated;
								topFraction: 0;
								topOffset: 0;
								yourself)]! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:27'!
hideExpandButton

	<preference: 'Hide Expand Button'
		category: 'windows'
		description: 'Hides the expand button in all windows'
		type: #Boolean>
	^ HideExpandButton ifNil: [ false ]
! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:44'!
hideExpandButton: aBoolean

	HideExpandButton := aBoolean.
	"Have the menu button frame rebuilt accordingly"
	self moveMenuButtonRight: self moveMenuButtonRight.
! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:13'!
menuBoxFrame

	^ MenuBoxFrame ifNil: [
		MenuBoxFrame := (LayoutFrame new
								leftFraction: 0;
								leftOffset: self boxExtent x + 3;
								topFraction: 0;
								topOffset: 0;
								yourself)]! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 14:21'!
moveMenuButtonRight

	<preference: 'Move Menu Button Right'
		category: 'windows'
		description: 'Moves the menu to the right side of the window label area, while traditionally it used to be on the left side'
		type: #Boolean>
	^ self menuBoxFrame leftOffset negative
! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 16:16'!
moveMenuButtonRight: aBoolean

	| absLeftOffset |
	absLeftOffset := ((self hideExpandButton and: [aBoolean])
		ifTrue: [absLeftOffset := self boxExtent x * 2]
		ifFalse: [absLeftOffset := self boxExtent x]) + 3.
	self menuBoxFrame leftOffset: (aBoolean 
										ifTrue: [absLeftOffset negated]
										ifFalse: [absLeftOffset]).
	self rebuildAllWindowLabels.! !

!SystemWindow class methodsFor: 'preferences' stamp: 'tfel 2/28/2010 17:05'!
rebuildAllWindowLabels

	self withAllSubclasses do: [:c | c allInstances do: [:w | w replaceBoxes]].! !


!TestRunner methodsFor: 'private' stamp: 'tfel 2/27/2010 22:06'!
defaultBackgroundColor
	"<lint: #expect rule: #overridesSuper rational: 'we want a different color than the parent'>"

	^ Preferences testRunnerWindowColor! !


!TestRunner class methodsFor: 'window color' stamp: 'tfel 2/27/2010 22:25'!
windowColorSpecification

	^ WindowColorSpec 
		classSymbol: self name 
		wording: 'Test Runner' 
		brightColor:  Color orange
		pastelColor: (Color r: 0.65 g: 0.753 b: 0.976)
		helpMessage: 'The Camp Smalltalk TestRunner tool for SUnit'! !


!TestRunner class reorganize!
('initialization' initialize registerInToolsFlap registerInWorldMenu)
('instance-creation' build open)
('window color' windowColorSpecification)
!


!SystemWindow class reorganize!
('initializing' borderWidth classVersion closeBoxImage collapseBoxImage expandBoxImage initialize menuBoxImage)
('instance creation' labelled:)
('new-morph participation' includeInNewMorphMenu)
('top window' clearTopWindow closeTopWindow noteTopWindowIn: sendTopWindowToBack wakeUpTopWindowUponStartup windowsIn:satisfying:)
('*services-base' topWindow)
('preferences' boxExtent clickOnLabelToEdit clickOnLabelToEdit: closeBoxFrame doubleClickOnLabelToExpand doubleClickOnLabelToExpand: expandBoxFrame hideExpandButton hideExpandButton: menuBoxFrame moveMenuButtonRight moveMenuButtonRight: rebuildAllWindowLabels reuseWindows reuseWindows:)
!

SystemWindow removeSelector: #createBox!
MorphicModel subclass: #SystemWindow
	instanceVariableNames: 'labelString stripes label closeBox collapseBox activeOnlyOnTop paneMorphs paneRects collapsedFrame fullFrame isCollapsed menuBox mustNotClose labelWidgetAllowance updatablePanes allowReframeHandles labelArea expandBox'
	classVariableNames: 'ClickOnLabelToEdit CloseBoxFrame CloseBoxImage CollapseBoxImage DoubleClickOnLabelToExpand ExpandBoxFrame ExpandBoxImage HideExpandButton MenuBoxFrame MenuBoxImage ReuseWindows TopWindow'
	poolDictionaries: ''
	category: 'Morphic-Windows'!
ProportionalSplitterMorph removeSelector: #drawOn:!
AbstractResizerMorph subclass: #ProportionalSplitterMorph
	instanceVariableNames: 'leftOrTop rightOrBottom splitsTopAndBottom oldColor traceMorph handle'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!ProportionalSplitterMorph reorganize!
('controlled morphs' addLeftOrTop: addRightOrBottom: bordersOn: commonNeighbours:with:)
('direction' beSplitsTopAndBottom splitsTopAndBottom)
('boundaries' bottomBoundary leftBoundary minimumHeightOf: minimumWidthOf: normalizedX: normalizedY: rightBoundary topBoundary)
('displaying' getOldColor handleRect handleSize isCursorOverHandle resizeCursor)
('initialization' initialize)
('events' mouseDown: mouseMove: mouseUp: updateFromEvent: wantsEveryMouseMove)
('adjacent splitters' siblingSplitters splitterAbove splitterBelow splitterLeft splitterRight)
('layout' layoutChanged)
!

Preferences class removeSelector: #clickOnLabelToEdit!
Preferences class removeSelector: #testRunnerWindowColor!
AlignmentMorph subclass: #PluggableButtonMorph
	instanceVariableNames: 'model label getStateSelector actionSelector getLabelSelector getMenuSelector shortcutCharacter askBeforeChanging triggerOnMouseDown offColor onColor feedbackColor showSelectionFeedback allButtons arguments argumentsProvider argumentsSelector'
	classVariableNames: 'RoundedButtonCorners'
	poolDictionaries: ''
	category: 'Morphic-Pluggable Widgets'!
Morph subclass: #LazyListMorph
	instanceVariableNames: 'listItems font selectedRow selectedRows listSource maxWidth'
	classVariableNames: 'ListSelectionColor ListSelectionTextColor'
	poolDictionaries: ''
	category: 'Morphic-Widgets'!
IconicButton removeSelector: #mouseDown:!
IconicButton removeSelector: #mouseUp:!

!IconicButton reorganize!
('accessing' borderInset borderRaised highlight)
('as yet unclassified' darken labelFromString: labelGraphic: restoreImage shedSelvedge)
('events' handlesMouseOver: mouseEnter: mouseLeave:)
('initialization' borderNormal borderThick buttonSetup initialize initializeWithThumbnail:withLabel:andColor:andSend:to: initializeWithThumbnail:withLabel:andSend:to: setDefaultLabel stationarySetup)
('menu' addLabelItemsTo:hand:)
('visual properties' updateVisualState:)
('*MorphicExtras-initialization' initializeToShow:withLabel:andSend:to:)
('button' doButtonAction)
!

RectangleMorph subclass: #FillInTheBlankMorph
	instanceVariableNames: 'response done textPane responseUponCancel'
	classVariableNames: 'RoundedDialogCorners'
	poolDictionaries: ''
	category: 'Morphic-Windows'!
AbstractResizerMorph subclass: #CornerGripMorph
	instanceVariableNames: 'target'
	classVariableNames: 'ActiveForm DrawCornerResizeHandles PassiveForm'
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!MCTool class reorganize!
('window color' windowColorSpecification)
!

"Postscript:"
"Re-intialize the SystemWindows"
SystemWindow initialize.
SystemWindow allInstances do: [:w | w replaceBoxes].
World invalidRect: World bounds from: World.

"Set the gray color scheme"
WindowColorRegistry refresh.
Preferences installUniformWindowColors.
SystemWindow withAllSubclasses do: [:c | 
	c allInstances do: [:w | 
		w setWindowColor: Preferences defaultWindowColor darker]].

"Set all our preferences"
CornerGripMorph drawCornerResizeHandles: false.
FillInTheBlankMorph roundedDialogCorners: true.
LazyListMorph
	listSelectionColor: LazyListMorph listSelectionColor;
	listSelectionTextColor: Color black.
PluggableButtonMorph roundedButtonCorners: true.
SystemWindow
	clickOnLabelToEdit: false;
	doubleClickOnLabelToExpand: true;
	moveMenuButtonRight: true;
	hideExpandButton: false.
!



More information about the Squeak-dev mailing list