[FIX] LayoutFix

Jesse Welton jwelton at pacific.mps.ohio-state.edu
Thu Feb 1 22:22:02 UTC 2001


Changes LayoutFrames so that all offsets are properly treated as such.
Changes SystemWindows to lay out their panes in a frame enclosing just
the pane region and not the label area, eliminating odd offsets and
some attendant display errors.

-Jesse

-------------- next part --------------
'From Squeak2.9alpha of 24 August 2000 [latest update: #3193] on 1 February 2001 at 2:53:49 pm'!
"Change Set:		LayoutFix
Date:			1 February 2001
Author:			Jesse Welton

Changes LayoutFrames so that positive right and bottom offsets represent offsets to the right and down from the lower right corner of the frame.  Eliminates special treatment of the bottom offset in Morph>>addMorph:fullFrame:.  Offsets are now treated the same however a submorph is added.  Changes the few direct calls to #rightOffset: and #bottomOffset: to comply with the new, consistent sign convention.

Changes SystemWindows' pane layouts to be based on just the pane region, eliminating the need to offset panes by the labelHeight.  This makes it easier to divide panes as intended, in particular fixing the layout of the bottom (info) pane of FileContentsBrowsers.  The various title bar components are placed in a labelArea submorph to minimize code changes and simplify the layout logic.

There may exist problems with some subclasses, but none that I am aware of.  Existing subclasses in the image do not use the layout mechanism to align additional labelArea items, so it is not problematic for these items to be direct submorphs, rather than living in the titleArea.

Fixes a mistake made in the preliminary changeset: Now converts all instances of SystemWindow subclasses, not just direct SystemWindow instances."!

MorphicModel subclass: #SystemWindow
	instanceVariableNames: 'labelString stripes label closeBox collapseBox activeOnlyOnTop paneMorphs paneRects collapsedFrame fullFrame isCollapsed menuBox mustNotClose labelWidgetAllowance updatablePanes allowReframeHandles labelArea '
	classVariableNames: 'TopWindow '
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!LayoutFrame methodsFor: 'layout' stamp: 'JW 2/1/2001 13:04'!
layout: oldBounds in: newBounds
	"Return the proportional rectangle insetting the given bounds"
	| left right top bottom |
	leftFraction ifNotNil:[
		left _ newBounds left + (newBounds width * leftFraction).
		leftOffset ifNotNil:[left _ left + leftOffset]].
	rightFraction ifNotNil:[
		right _ newBounds right - (newBounds width * (1.0 - rightFraction)).
		rightOffset ifNotNil:[right _ right + rightOffset]].
	topFraction ifNotNil:[
		top _ newBounds top + (newBounds height * topFraction).
		topOffset ifNotNil:[top _ top + topOffset]].
	bottomFraction ifNotNil:[
		bottom _ newBounds bottom - (newBounds height * (1.0 - bottomFraction)).
		bottomOffset ifNotNil:[bottom _ bottom + bottomOffset]].
	left ifNil:[ right 
			ifNil:[left _ oldBounds left. right _ oldBounds right]
			ifNotNil:[left _ right - oldBounds width]].
	right ifNil:[right _ left + oldBounds width].
	top ifNil:[ bottom 
			ifNil:[top _ oldBounds top. bottom _ oldBounds bottom]
			ifNotNil:[top _ bottom - oldBounds height]].
	bottom ifNil:[bottom _ top + oldBounds height].
	^(left rounded @ top rounded) corner: (right rounded @ bottom rounded)! !

!LayoutFrame methodsFor: 'objects from disk' stamp: 'JW 2/1/2001 13:33'!
convertToCurrentVersion: varDict refStream: smartRefStrm
	| className oldClassVersion |

	"JW 2/1/2001"
	"Since class version isn't passed in varDict, look it up through smartRefSrm."
	className := varDict at: #ClassName.
	oldClassVersion := (smartRefStrm structures at: className) first.
	(oldClassVersion = 0) ifTrue: [ self negateBottomRightOffsets ].
	^super convertToCurrentVersion: varDict refStream: smartRefStrm.
! !

!LayoutFrame methodsFor: 'objects from disk' stamp: 'JW 2/1/2001 14:37'!
negateBottomRightOffsets

	bottomOffset ifNotNil: [ bottomOffset := bottomOffset negated ].
	rightOffset ifNotNil: [ rightOffset := rightOffset negated ].

! !


!LayoutFrame class methodsFor: 'as yet unclassified' stamp: 'JW 2/1/2001 12:48'!
classVersion
	^1 "changed treatment of bottomOffset and rightOffset"
! !


!Morph methodsFor: 'submorphs-add/remove' stamp: 'JW 2/1/2001 12:52'!
addMorph: aMorph fullFrame: aLayoutFrame

	aMorph layoutFrame: aLayoutFrame.
	aMorph hResizing: #spaceFill; vResizing: #spaceFill.
	self addMorph: aMorph.

! !


!FillInTheBlankMorph methodsFor: 'initialization' stamp: 'JW 2/1/2001 13:28'!
setQuery: queryString initialAnswer: initialAnswer answerHeight: answerHeight acceptOnCR: acceptBoolean
	| query frame topOffset accept cancel buttonAreaHeight |
	response _ initialAnswer.
	done _ false.
	self removeAllMorphs.

	self layoutPolicy: ProportionalLayout new.

	query _ TextMorph new contents: queryString.
	query setNameTo: 'query'.
	query lock.
		frame _ LayoutFrame new.
		frame topFraction: 0.0; topOffset: 2.
		frame leftFraction: 0.5; leftOffset: (query width // 2) negated.
	query layoutFrame: frame.
	self addMorph: query.
	topOffset _ query height + 4.

	accept _ SimpleButtonMorph new target: self; color: Color veryLightGray.
	accept label: 'Accept(s)'; actionSelector: #accept.
	accept setNameTo: 'accept'.
		frame _ LayoutFrame new.
		frame rightFraction: 0.5; rightOffset: -10; bottomFraction: 1.0; bottomOffset: -2.
	accept layoutFrame: frame.
	self addMorph: accept.

	cancel _ SimpleButtonMorph new target: self; color: Color veryLightGray.
	cancel label: 'Cancel(l)'; actionSelector: #cancel.
	cancel setNameTo: 'cancel'.
		frame _ LayoutFrame new.
		frame leftFraction: 0.5; leftOffset: 10; bottomFraction: 1.0; bottomOffset: -2.
	cancel layoutFrame: frame.
	self addMorph: cancel.
	buttonAreaHeight _ (accept height max: cancel height) + 4.

	textPane _ PluggableTextMorph on: self
		text: #response
		accept: #response:
		readSelection: #selectionInterval
		menu: #codePaneMenu:shifted:.
	textPane hResizing: #spaceFill; vResizing: #spaceFill.
	textPane borderWidth: 2.
	textPane hasUnacceptedEdits: true.
	textPane acceptOnCR: acceptBoolean.
	textPane setNameTo: 'textPane'.
		frame _ LayoutFrame new.
		frame leftFraction: 0.0; rightFraction: 1.0; topFraction: 0.0; topOffset: topOffset; bottomFraction: 1.0; bottomOffset: buttonAreaHeight negated.
	textPane layoutFrame: frame.
	self addMorph: textPane.

	self extent: (200 max: query width) + 4 @ (topOffset + answerHeight + 4 + buttonAreaHeight).
! !


!SystemWindow methodsFor: 'initialization' stamp: 'JW 1/30/2001 23:11'!
addCloseBox
	| frame |
	closeBox _ SimpleButtonMorph new borderWidth: 0;
			label: 'X' font: Preferences standardButtonFont; color: Color transparent;
			actionSelector: #closeBoxHit; target: self; extent: 14 at 14.
	frame _ LayoutFrame new.
	frame leftFraction: 0; leftOffset: 4; topFraction: 0; topOffset: 1.
	closeBox layoutFrame: frame.
	labelArea addMorph: closeBox.! !

!SystemWindow methodsFor: 'initialization' stamp: 'JW 1/31/2001 07:36'!
addLabelArea

	labelArea := (AlignmentMorph newSpacer: Color transparent) vResizing: #shrinkWrap;
			layoutPolicy: ProportionalLayout new.
	self addMorph: labelArea.! !

!SystemWindow methodsFor: 'initialization' stamp: 'JW 1/30/2001 23:11'!
addMenuControl
"NB: for the moment, we always supply balloon help for this control, until people get used to it; eventually, we mays switch to showing this balloon help only in novice mode, as we do for the other standard window controls."
	| frame |
	menuBox _ IconicButton new borderWidth: 0;
			labelGraphic: (ScriptingSystem formAtKey: 'TinyMenu'); color: Color transparent; 
			actWhen: #buttonDown;
			actionSelector: #offerWindowMenu; target: self;
			setBalloonText: 'window menu'.
	frame _ LayoutFrame new.
	frame leftFraction: 0; leftOffset: 19; topFraction: 0; topOffset: 1.
	menuBox layoutFrame: frame.
	labelArea addMorph: menuBox.

! !

!SystemWindow methodsFor: 'initialization' stamp: 'JW 1/31/2001 07:37'!
initialize
	| aFont |
	super initialize.
	allowReframeHandles := true.
	labelString ifNil: [labelString _ 'Untitled Window'].
	isCollapsed _ false.
	activeOnlyOnTop _ true.
	paneMorphs _ Array new.
	borderColor _ #raised.
	borderWidth _ 1.
	color _ Color black.
	self layoutPolicy: ProportionalLayout new.

	label _ StringMorph new contents: labelString;
			font: Preferences windowTitleFont emphasis: 1.

	"Add collapse box so #labelHeight will work"
	aFont _ Preferences standardButtonFont.
	collapseBox _ SimpleButtonMorph new borderWidth: 0;
			label: 'O' font: aFont; color: Color transparent;
			actionSelector: #collapseOrExpand; target: self; extent: 14 at 14.

	stripes _ Array with: (RectangleMorph newBounds: bounds)  "see extent:"
				with: (RectangleMorph newBounds: bounds).

	self addLabelArea.

	labelArea addMorph: (stripes first borderWidth: 1).
	labelArea addMorph: (stripes second borderWidth: 2).
	self setLabelWidgetAllowance.
	self addCloseBox.
	self addMenuControl.
	labelArea addMorph: label.
	labelArea addMorph: 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']].
	self on: #mouseEnter send: #spawnReframeHandle: to: self.
	self on: #mouseLeave send: #spawnReframeHandle: to: self.
	label on: #mouseDown send: #relabelEvent: to: self.
	self extent: 300 at 200.
	mustNotClose _ false.
	updatablePanes _ Array new.! !

!SystemWindow methodsFor: 'initialization' stamp: 'JW 2/1/2001 13:35'!
setFramesForLabelArea

	"an aid to converting old instances, but then I found convertAlignment"

	| frame |

	frame _ LayoutFrame new.
	frame leftFraction: 0.5; topFraction: 0; leftOffset: label width negated // 2.
	label layoutFrame: frame.

	frame _ LayoutFrame new.
	frame rightFraction: 1; topFraction: 0; rightOffset: -1; topOffset: 1.
	collapseBox layoutFrame: frame.

	frame _ LayoutFrame new.
	frame leftFraction: 0; topFraction: 0; rightFraction: 1;
			leftOffset: 1; topOffset: 1; rightOffset: -1.
	stripes first layoutFrame: frame.
	stripes first height: self labelHeight - 2.
	stripes first hResizing: #spaceFill.

	frame _ LayoutFrame new.
	frame leftFraction: 0; topFraction: 0; rightFraction: 1;
			leftOffset: 3; topOffset: 3; rightOffset: -3.
	stripes last layoutFrame: frame.
	stripes last height: self labelHeight - 6.
	stripes last hResizing: #spaceFill.

	frame _ LayoutFrame new.
	frame leftFraction: 0; topFraction: 0; rightFraction: 1;
			topOffset: self labelHeight negated.
	labelArea layoutFrame: frame.

! !

!SystemWindow methodsFor: 'geometry' stamp: 'JW 2/1/2001 13:15'!
setPaneRectsFromBounds
	"Reset proportional specs from actual bounds, eg, after reframing panes"
	| layoutBounds box frame left right top bottom |
	layoutBounds _ self layoutBounds.
	paneMorphs do:[:m|
		frame _ m layoutFrame.
		box _ m bounds.
		frame ifNotNil:[
			left _ box left - layoutBounds left - (frame leftOffset ifNil:[0]).
			right _ box right - layoutBounds left - (frame rightOffset ifNil:[0]).
			top _ box top - layoutBounds top - (frame topOffset ifNil:[0]).
			bottom _ box bottom - layoutBounds top - (frame bottomOffset ifNil:[0]).
			frame leftFraction: (left / layoutBounds width asFloat).
			frame rightFraction: (right / layoutBounds width asFloat).
			frame topFraction: (top / layoutBounds height asFloat).
			frame bottomFraction: (bottom / layoutBounds height asFloat).
		].
	].! !

!SystemWindow methodsFor: 'panes' stamp: 'JW 1/30/2001 23:13'!
addMorph: aMorph fullFrame: aLayoutFrame

	super addMorph: aMorph fullFrame: aLayoutFrame.

	paneMorphs _ paneMorphs copyReplaceFrom: 1 to: 0 with: (Array with: aMorph).
	aMorph borderWidth: 1.
	aMorph color: self paneColor.
! !

!SystemWindow methodsFor: 'object fileIn' stamp: 'JW 1/31/2001 08:57'!
convertToCurrentVersion: varDict refStream: smartRefStrm
	
	allowReframeHandles ifNil: [allowReframeHandles := true].
	self layoutPolicy ifNil: [self convertAlignment].
	labelArea ifNil: [self convertAlignment].
	^super convertToCurrentVersion: varDict refStream: smartRefStrm.

! !

!SystemWindow methodsFor: 'layout' stamp: 'JW 2/1/2001 13:43'!
convertAlignment
	| frame |
	self layoutPolicy: ProportionalLayout new.
	(paneMorphs == nil or:[paneRects == nil or:[paneMorphs size ~= paneRects size]]) ifFalse:[
		self addLabelArea.
		self putLabelItemsInLabelArea.
		self setFramesForLabelArea.
		paneMorphs with: paneRects do:[:m :r|
			frame _ LayoutFrame new.
			frame leftFraction: r left; rightFraction: r right; topFraction: r top; bottomFraction: r bottom.
			m layoutFrame: frame.
			m hResizing: #spaceFill; vResizing: #spaceFill.
		].
	].
	labelArea ifNil: [
		self addLabelArea.
		self putLabelItemsInLabelArea.
		self setFramesForLabelArea.
		paneMorphs ifNotNil: [
			paneMorphs do: [:m |
				frame := m layoutFrame ifNil: [LayoutFrame new].
				frame topOffset: (frame topOffset ifNil: [0]) - self labelHeight.
				(frame bottomFraction ~= 1.0) ifTrue:
					[ frame bottomOffset: (frame bottomOffset ifNil: [0]) - self labelHeight ].
			].
		].
	].
	label ifNotNil:[
		frame _ LayoutFrame new.
		frame leftFraction: 0.5; topFraction: 0; leftOffset: label width negated // 2.
		label layoutFrame: frame].
	collapseBox ifNotNil:[
		frame _ LayoutFrame new.
		frame rightFraction: 1; topFraction: 0; rightOffset: -1; topOffset: 1.
		collapseBox layoutFrame: frame].
	stripes ifNotNil:[
		frame _ LayoutFrame new.
		frame leftFraction: 0; topFraction: 0; rightFraction: 1;
				leftOffset: 1; topOffset: 1; rightOffset: -1.
		stripes first layoutFrame: frame.
		stripes first height: self labelHeight - 2.
		stripes first hResizing: #spaceFill.
		frame _ LayoutFrame new.
		frame leftFraction: 0; topFraction: 0; rightFraction: 1;
				leftOffset: 3; topOffset: 3; rightOffset: -3.
		stripes last layoutFrame: frame.
		stripes last height: self labelHeight - 6.
		stripes last hResizing: #spaceFill].
	menuBox ifNotNil:[
		frame _ LayoutFrame new.
		frame leftFraction: 0; leftOffset: 19; topFraction: 0; topOffset: 1.
		menuBox layoutFrame: frame].
	closeBox ifNotNil:[
		frame _ LayoutFrame new.
		frame leftFraction: 0; leftOffset: 4; topFraction: 0; topOffset: 1.
		closeBox layoutFrame: frame].
! !

!SystemWindow methodsFor: 'layout' stamp: 'JW 1/30/2001 22:45'!
layoutBounds
	"Bounds of pane area only."
	| box |

	box := super layoutBounds.
	^box withTop: box top + self labelHeight! !

!SystemWindow methodsFor: 'layout' stamp: 'JW 1/31/2001 08:49'!
putLabelItemsInLabelArea

	stripes ifNotNil: [ stripes do: [:stripe | labelArea addMorph: stripe] ].
	closeBox ifNotNil: [ labelArea addMorph: closeBox ].
	menuBox ifNotNil: [ labelArea addMorph: menuBox ].
	collapseBox ifNotNil: [ labelArea addMorph: collapseBox ].
	label ifNotNil: [ labelArea addMorph: label ].

! !

"Postscript:
Convert all existing LayoutFrames and SystemWindows."

LayoutFrame allInstances do: [:each | each negateBottomRightOffsets].
SystemWindow allSubInstances do: [:each | each convertAlignment].
!



More information about the Squeak-dev mailing list