[BUG][FIX][ENH] buttons overlap scrollbars (and scrollbars don't line up, either)

Jesse Welton jwelton at pacific.mps.ohio-state.edu
Sat Feb 3 15:41:57 UTC 2001


On Fri, 2 Feb 2001, Ned Konz wrote:
> On Friday 02 February 2001 15:53, Ned Konz wrote:
> > With the latest updates loaded (up to 3312), and scrollbars set to
> > "inboard" and "right", the buttons in the browser and debugger overlap the
> > scroll bars.
> >
> > Attached is a picture of the problem.
> 
> Also note that the scrollbars' horizontal positions don't line up.

The attached changeset fixes both these problems, as part of a general
cleanup of annotation panes and related window layout.  I think it
greatly improves window appearance.

What I think is worse is that with flop-out scrollbars on the right,
scroll bars for panes not at the right edge of a window are obscured
by the panes to the right.  I'm not sure what the best way to address
that is.

-Jesse

-------------- next part --------------
'From Squeak2.9alpha of 13 June 2000 [latest update: #3299] on 3 February 2001 at 10:35:28 am'!
"Change Set:		AnnotationExperiment
Date:			2 February 2001
Author:			Jesse Welton

Greatly improves the appearance and uniformity of optional annotation and button frames.  Provides easy resizing of these, as well as Browsers' switch buttons, which does not interfere with the natural resizing of the major panes.  Provides uniform scroll bar alignment for window panes.  Removes generally unnecessary dangling scroll bars on annotation panes."!

Morph subclass: #SubpaneDividerMorph
	instanceVariableNames: 'resizingEdge '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!SubpaneDividerMorph commentStamp: 'JW 2/3/2001 09:04' prior: 0!
A morph which presents a visible separator between subpanes of a SystemWindow which have zero edgeWidth.  Subpanes are submorphs of a SystemWindow's paneMorphs.

A SubpaneDividerMorph may also initiate reframe handles for the subpanes.  For resizing, it is expected that the main paneMorph has a ProportionalLayout LayoutPolicy, and that the subpanes to be resized have LayoutFrames with equal topFractions and bottomFractions, but different topOffsets and bottomOffsets.  It is the offsets that are changed, and the change is propagated through sibling morphs up to the first resizable morph (with different nominal frame fractions).

The direction of propagation is determined by the value of resizingEdge, which is one of: nil (for non-adjustible subpane divisions), #bottom or #top (which acts a though the divider is the corresponding edge of the subpane directly above or below it).  Does not currently support #left or #right binding, or subpanes in a TableLayout.
!


!CodeHolder methodsFor: 'misc' stamp: 'JW 2/3/2001 09:38'!
addLowerPanesTo: window at: nominalFractions with: editString

	| verticalOffset row innerFractions |

	row _ AlignmentMorph newColumn
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		layoutInset: 0;
		borderWidth: 1;
		borderColor: Color black;
		layoutPolicy: ProportionalLayout new.

	verticalOffset _ 0.
	innerFractions _ 0 at 0 corner: 1 at 0.
	verticalOffset _ self addOptionalAnnotationsTo: row at: innerFractions plus: verticalOffset.
	verticalOffset _ self addOptionalButtonsTo: row  at: innerFractions plus: verticalOffset.

	row 
		addMorph: ((self buildMorphicCodePaneWith: editString) borderWidth: 0)
		fullFrame: (
			LayoutFrame 
				fractions: (innerFractions withBottom: 1) 
				offsets: (0 at verticalOffset corner: 0 at 0)
		).
	window 
		addMorph: row
		frame: nominalFractions.

	row on: #mouseEnter send: #paneTransition: to: window.
	row on: #mouseLeave send: #paneTransition: to: window.! !

!CodeHolder methodsFor: 'misc' stamp: 'JW 2/3/2001 10:12'!
addOptionalAnnotationsTo: window at: fractions plus: verticalOffset
	"Add an annotation pane to the window if preferences indicate a desire for it, and return the incoming verticalOffset plus the height of the added pane, if any"

	| aTextMorph divider delta |
	self wantsAnnotationPane ifFalse: [^ verticalOffset].
	aTextMorph _ PluggableTextMorph 
		on: self
		text: #annotation 
		accept: nil
		readSelection: nil
		menu: #annotationPaneMenu:shifted:.
	aTextMorph
		askBeforeDiscardingEdits: false;
		borderWidth: 0;
		hideScrollBarIndefinitely.
	divider _ SubpaneDividerMorph forBottomEdge.
	delta _ self defaultAnnotationPaneHeight.
	window 
		addMorph: aTextMorph 
		fullFrame: (LayoutFrame 
				fractions: fractions 
				offsets: (0 at verticalOffset corner: 0@(verticalOffset + delta - 1))).
	window 
		addMorph: divider
		fullFrame: (LayoutFrame 
				fractions: fractions 
				offsets: (0@(verticalOffset + delta - 1) corner: 0@(verticalOffset + delta))).
	^ verticalOffset + delta! !

!CodeHolder methodsFor: 'misc' stamp: 'JW 2/3/2001 09:39'!
addOptionalButtonsTo: window at: fractions plus: verticalOffset
	"If the receiver wishes it, add a button pane to the window, and answer the verticalOffset plus the height added"

	| delta buttons divider |
	self wantsOptionalButtons ifFalse: [^verticalOffset].
	delta _ self defaultButtonPaneHeight.
	buttons _ self optionalButtonRow 
		color: (Display depth <= 8 ifTrue: [Color transparent] ifFalse: [Color gray alpha: 0.2]);
		borderWidth: 0.
	divider _ SubpaneDividerMorph forBottomEdge.
	window 
		addMorph: buttons
		fullFrame: (LayoutFrame 
				fractions: fractions 
				offsets: (0 at verticalOffset corner: 0@(verticalOffset + delta - 1))).
	window 
		addMorph: divider
		fullFrame: (LayoutFrame 
				fractions: fractions 
				offsets: (0@(verticalOffset + delta - 1) corner: 0@(verticalOffset + delta))).
	^ verticalOffset + delta! !


!Browser methodsFor: 'initialize-release' stamp: 'JW 2/3/2001 09:45'!
addAListPane: aListPane to: window at: nominalFractions plus: verticalOffset

	| row switchHeight |

	row _ AlignmentMorph newColumn
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		layoutInset: 0;
		borderWidth: 1;
		layoutPolicy: ProportionalLayout new.
	switchHeight _ 25.
	row 
		addMorph: aListPane
		fullFrame: (
			LayoutFrame 
				fractions: (0 at 0 corner: 1 at 1) 
				offsets: (0 at 0 corner: 0 at switchHeight negated)
		).	

	row 
		addMorph: SubpaneDividerMorph forTopEdge
		fullFrame: (
			LayoutFrame 
				fractions: (0 at 1 corner: 1 at 1) 
				offsets: (0 at switchHeight negated corner: 0@(1-switchHeight))
		).	

	self 
		addMorphicSwitchesTo: row 
		at: (
			LayoutFrame 
				fractions: (0 at 1 corner: 1 at 1) 
				offsets: (0@(1-switchHeight)  corner: 0 at 0)
		).

	window 
		addMorph: row
		fullFrame: (
			LayoutFrame 
				fractions: nominalFractions 
				offsets: (0 at verticalOffset corner: 0 at 0)
		).	
	row on: #mouseEnter send: #paneTransition: to: window.
	row on: #mouseLeave send: #paneTransition: to: window.

! !

!Browser methodsFor: 'initialize-release' stamp: 'JW 2/2/2001 16:07'!
buildMorphicClassList

	| myClassList |

	myClassList _ PluggableListMorph on: self list: #classList
			selected: #classListIndex changeSelected: #classListIndex:
			menu: #classListMenu:shifted: keystroke: #classListKey:from:.
	myClassList borderWidth: 0.
	myClassList enableDragNDrop: Preferences browseWithDragNDrop.
	myClassList highlightSelector: #highlightClassList:with:.
	^myClassList

! !

!Browser methodsFor: 'initialize-release' stamp: 'JW 2/3/2001 09:33'!
buildMorphicSwitches

	| instanceSwitch divider1 divider2 commentSwitch classSwitch row aColor |

	instanceSwitch _ PluggableButtonMorph
		on: self
		getState: #instanceMessagesIndicated
		action: #indicateInstanceMessages.
	instanceSwitch
		label: 'instance';
		askBeforeChanging: true;
		borderWidth: 0.
	commentSwitch _ PluggableButtonMorph
		on: self
		getState: #classCommentIndicated
		action: #plusButtonHit.
	commentSwitch
		label: '?' asText allBold;
		askBeforeChanging: true;
		setBalloonText: 'class comment';
		borderWidth: 0.
	classSwitch _ PluggableButtonMorph
		on: self
		getState: #classMessagesIndicated
		action: #indicateClassMessages.
	classSwitch
		label: 'class';
		askBeforeChanging: true;
		borderWidth: 0.
	divider1 := SubpaneDividerMorph vertical.
	divider2 := SubpaneDividerMorph vertical.
	row _ AlignmentMorph newRow
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		layoutInset: 0;
		borderWidth: 0;
		addMorphBack: instanceSwitch;
		addMorphBack: divider1;
		addMorphBack: commentSwitch;
		addMorphBack: divider2;
		addMorphBack: classSwitch.

	aColor _ Color colorFrom: self defaultBackgroundColor.
	{instanceSwitch. commentSwitch. classSwitch} do: [:m | 
		m 
			color: aColor;
			onColor: aColor darker offColor: aColor;
			hResizing: #spaceFill;
			vResizing: #spaceFill.
	].

	^ row
! !


!ChangeSorter methodsFor: 'creation' stamp: 'JW 2/2/2001 21:47'!
openAsMorphIn: window rect: rect
	"Add a set of change sorter views to the given top view offset by the given amount. To create a single change sorter, call this once with an offset of 0 at 0. To create a dual change sorter, call it twice with offsets of 0 at 0 and 0.5 at 0."

	| csListHeight msgListHeight csMsgListHeight |
	contents _ ''.
	csListHeight _ 0.25.
	msgListHeight _ 0.25.
	csMsgListHeight _ csListHeight + msgListHeight.
	self addDependent: window.		"so it will get changed: #relabel"

	window addMorph: ((PluggableListMorphByItem on: self
				list: #changeSetList
				selected: #currentCngSet
				changeSelected: #showChangeSetNamed:
				menu: #changeSetMenu:shifted:
				keystroke: #changeSetListKey:from:)
			autoDeselect: false)
		frame: (((0 at 0 extent: 0.5 at csListHeight)
			scaleBy: rect extent) translateBy: rect origin).

	window addMorph: (PluggableListMorphByItem on: self
				list: #classList
				selected: #currentClassName
				changeSelected: #currentClassName:
				menu: #classMenu:shifted:
				keystroke: #classListKey:from:)
		frame: (((0.5 at 0 extent: 0.5 at csListHeight)
			scaleBy: rect extent) translateBy: rect origin).

	window addMorph: (PluggableListMorphByItem on: self
				list: #messageList
				selected: #currentSelector
				changeSelected: #currentSelector:
				menu: #messageMenu:shifted:
				keystroke: #messageListKey:from:)
		frame: (((0 at csListHeight extent: 1 at msgListHeight)
			scaleBy: rect extent) translateBy: rect origin).

	 self addLowerPanesTo: window
		at: (((0 at csMsgListHeight corner: 1 at 1) scaleBy: rect extent) translateBy: rect origin)
		with: nil.! !

!ChangeSorter methodsFor: 'code pane' stamp: 'JW 2/2/2001 21:41'!
wantsOptionalButtons
	"No optional buttons for ChangeSorter"
	^false! !


!FileContentsBrowser methodsFor: 'creation' stamp: 'JW 2/3/2001 10:24'!
addLowerPanesTo: window at: nominalFractions with: editString

	| verticalOffset row innerFractions codePane infoPane infoHeight |

	row _ AlignmentMorph newColumn
		hResizing: #spaceFill;
		vResizing: #spaceFill;
		layoutInset: 0;
		borderWidth: 1;
		borderColor: Color black;
		layoutPolicy: ProportionalLayout new.

	codePane _ PluggableTextMorph on: self text: #contents accept: #contents:notifying:
			readSelection: #contentsSelection menu: #codePaneMenu:shifted:.
	infoPane _ PluggableTextMorph on: self text: #infoViewContents accept: nil
			readSelection: nil menu: nil.
	verticalOffset _ 0.
	innerFractions _ 0 at 0 corner: 1 at 0.
">>not with this browser--- at least not yet ---
	verticalOffset _ self addOptionalAnnotationsTo: row at: innerFractions plus: verticalOffset.
	verticalOffset _ self addOptionalButtonsTo: row  at: innerFractions plus: verticalOffset.
<<<<"

	infoHeight _ 20.
	row 
		addMorph: (codePane borderWidth: 0)
		fullFrame: (
			LayoutFrame 
				fractions: (0 at 0 corner: 1 at 1) 
				offsets: (0 at verticalOffset corner: 0 at infoHeight negated)
		).
	row 
		addMorph: (SubpaneDividerMorph forTopEdge)
		fullFrame: (
			LayoutFrame 
				fractions: (0 at 1 corner: 1 at 1) 
				offsets: (0 at infoHeight negated corner: 0@(1-infoHeight))
		).
	row 
		addMorph: (infoPane borderWidth: 0; hideScrollBarIndefinitely)
		fullFrame: (
			LayoutFrame 
				fractions: (0 at 1 corner: 1 at 1) 
				offsets: (0@(1-infoHeight) corner: 0 at 0)
		).
	window 
		addMorph: row
		frame: nominalFractions.

	row on: #mouseEnter send: #paneTransition: to: window.
	row on: #mouseLeave send: #paneTransition: to: window.

! !


!PackagePaneBrowser methodsFor: 'initialize-release' stamp: 'JW 2/2/2001 21:25'!
openAsMorphEditing: editString 
	"Create a pluggable version of all the views for a Browser, including views and controllers."
	"PackagePaneBrowser openBrowser"

	| listHeight window |
	listHeight _ 0.4.

	(window _ SystemWindow labelled: 'later')
		model: self.

	window addMorph: (PluggableListMorph
				on: self
				list: #packageList
				selected: #packageListIndex
				changeSelected: #packageListIndex:
				menu: #packageMenu:
				keystroke: #packageListKey:from:)
		frame: (0 @ 0 extent: 0.15 @ listHeight).

	window addMorph: (self buildMorphicSystemCatList)
		frame: (0.15 @ 0 extent: 0.2 @ listHeight).

	self addClassAndSwitchesTo: window at: (0.35 @ 0 extent: 0.25 @ listHeight) plus: 0.

	window addMorph: (self buildMorphicMessageCatList)
		frame: (0.6 @ 0 extent: 0.15 @ listHeight).

	window addMorph: (self buildMorphicMessageList)
		frame: (0.75 @ 0 extent: 0.25 @ listHeight).

	self addLowerPanesTo: window at: (0 at listHeight extent: 1 at 1) with: editString.

	window setUpdatablePanesFrom:
		#(packageList systemCategoryList classList messageCategoryList messageList ).
	^ window! !


!PackagePaneBrowser class methodsFor: 'instance creation' stamp: 'JW 2/2/2001 16:32'!
openBrowser
	"PackagePaneBrowser openBrowser"

	self openBrowserView: (self new openEditString: nil)
			label: 'Package Browser'! !


!ScrollPane methodsFor: 'geometry' stamp: 'JW 2/3/2001 09:53'!
resizeScrollBar
	| w topLeft |
	w _ self scrollbarWidth.
	topLeft _ scrollBarOnLeft
		ifTrue: [retractableScrollBar ifTrue: [bounds topLeft - (w-borderWidth at 0)]
									ifFalse: [bounds topLeft + (borderWidth-1 at 0)]]
		ifFalse: [retractableScrollBar ifTrue: [bounds topRight - (borderWidth at 0)]
									ifFalse: [bounds topRight - (w+borderWidth-1 at 0)]].
	scrollBar bounds: (topLeft extent: w @ bounds height)! !

!ScrollPane methodsFor: 'scrolling' stamp: 'JW 2/3/2001 10:22'!
hideOrShowScrollBar
	"Hide or show the scrollbar depending on if the pane is scrolled/scrollable."

	"Don't do anything with the retractable scrollbar unless we have focus"
	retractableScrollBar & self hasFocus not ifTrue: [^self].
	"Don't show it if we were told not to."
	(self valueOfProperty: #noScrollBarPlease ifAbsent: [false]) ifTrue: [^self].

	self isScrollable not & self isScrolledFromTop not ifTrue: [self hideScrollBar].
	self isScrollable | self isScrolledFromTop ifTrue: [self showScrollBar].
! !

!ScrollPane methodsFor: 'scrolling' stamp: 'JW 2/3/2001 10:19'!
hideScrollBarIndefinitely
	"Get rid of scroll bar for short panes that don't want it shown."

	self setProperty: #noScrollBarPlease toValue: true.
	self hideScrollBar.

! !


!SubpaneDividerMorph methodsFor: 'accessing' stamp: 'JW 2/3/2001 09:39'!
resizingEdge

	^resizingEdge
! !

!SubpaneDividerMorph methodsFor: 'initialization' stamp: 'JW 2/3/2001 09:26'!
firstEnter: evt
	"The first time this divider is activated, find its window and redirect further interaction there."
	| window |

	window := self firstOwnerSuchThat: [:m | m respondsTo: #secondaryPaneTransition:divider:].
	window ifNil: [ self suspendEventHandler. ^ self ]. "not working out"
	window secondaryPaneTransition: evt divider: self.
	self on: #mouseEnter send: #secondaryPaneTransition:divider: to: window.
! !

!SubpaneDividerMorph methodsFor: 'initialization' stamp: 'JW 2/3/2001 09:07'!
horizontal

	self hResizing: #spaceFill.! !

!SubpaneDividerMorph methodsFor: 'initialization' stamp: 'JW 2/3/2001 09:30'!
initialize

	super initialize.
	self extent: 1 at 1;
		color: Color black.! !

!SubpaneDividerMorph methodsFor: 'initialization' stamp: 'JW 2/3/2001 09:12'!
resizingEdge: edgeSymbol

	(#(top bottom) includes: edgeSymbol) ifFalse:
		[ self error: 'resizingEdge must be #top or #bottom' ].
	resizingEdge := edgeSymbol.
	self on: #mouseEnter send: #firstEnter: to: self.
! !

!SubpaneDividerMorph methodsFor: 'initialization' stamp: 'JW 2/3/2001 09:07'!
vertical

	self vResizing: #spaceFill.! !


!SubpaneDividerMorph class methodsFor: 'instance creation' stamp: 'JW 2/3/2001 09:35'!
forBottomEdge
	^self new horizontal resizingEdge: #bottom! !

!SubpaneDividerMorph class methodsFor: 'instance creation' stamp: 'JW 2/3/2001 09:35'!
forTopEdge
	^self new horizontal resizingEdge: #top! !

!SubpaneDividerMorph class methodsFor: 'instance creation' stamp: 'JW 2/3/2001 09:31'!
horizontal
	^self new horizontal! !

!SubpaneDividerMorph class methodsFor: 'instance creation' stamp: 'JW 2/3/2001 09:31'!
vertical
	^self new vertical! !


!SystemWindow methodsFor: 'resize/collapse' stamp: 'JW 2/3/2001 08:43'!
spawnOffsetReframeHandle: event divider: divider
	"The mouse has crossed a secondary (fixed-height) pane divider.  Spawn a reframe handle."
	"Only supports vertical adjustments."
	| siblings topAdjustees bottomAdjustees topOnly bottomOnly resizer pt delta minY maxY |
	allowReframeHandles ifFalse: [^ self].
	owner ifNil: [^ self  "Spurious mouseLeave due to delete"].
	(self isActive not or: [self isCollapsed]) ifTrue:  [^ self].
	((self world ifNil: [^ self]) firstSubmorph isKindOf: NewHandleMorph) ifTrue:
		[^ self  "Prevent multiple handles"].
	divider layoutFrame ifNil: [^ self].
	(#(top bottom) includes: divider resizingEdge) ifFalse: [^ self].

	siblings _ divider owner submorphs select: [:m | m layoutFrame notNil ].
	divider resizingEdge = #bottom ifTrue:
		[
		topAdjustees _ siblings select: [:m |
			m layoutFrame topFraction = divider layoutFrame bottomFraction and:
				[m layoutFrame topOffset >= divider layoutFrame topOffset] ].
		bottomAdjustees _ siblings select: [:m |
			m layoutFrame bottomFraction = divider layoutFrame topFraction and:
				[m layoutFrame bottomOffset >= divider layoutFrame topOffset] ].
		].
	divider resizingEdge = #top ifTrue:
		[
		topAdjustees _ siblings select: [:m |
			m layoutFrame topFraction = divider layoutFrame bottomFraction and:
				[m layoutFrame topOffset <= divider layoutFrame bottomOffset] ].
		bottomAdjustees _ siblings select: [:m |
			m layoutFrame bottomFraction = divider layoutFrame topFraction and:
				[m layoutFrame bottomOffset <= divider layoutFrame bottomOffset] ].
		].
	topOnly := topAdjustees copyWithoutAll: bottomAdjustees.
	bottomOnly := bottomAdjustees copyWithoutAll: topAdjustees.
	(topOnly isEmpty or: [bottomOnly isEmpty]) ifTrue: [^self].

	minY := bottomOnly inject: -9999 into: [:y :m | 
		y max: m top + (m minHeight max: 16) + (divider bottom - m bottom)].
	maxY := topOnly inject: 9999 into: [:y :m |
		y min: m bottom - (m minHeight max: 16) - (m top - divider top)].

	pt _ event cursorPoint.
	resizer _ NewHandleMorph new
		followHand: event hand
		forEachPointDo: [:p |
			delta := (p y min: maxY max: minY) - pt y.
			topAdjustees do:
				[:m | m layoutFrame topOffset: m layoutFrame topOffset + delta ].
			bottomAdjustees do:
				[:m | m layoutFrame bottomOffset: m layoutFrame bottomOffset + delta ].
			divider layoutChanged.
			pt := pt + delta.
		]
		lastPointDo: [:p | ].
	event hand world addMorphInLayer: resizer.
	resizer startStepping! !

!SystemWindow methodsFor: 'events' stamp: 'JW 2/2/2001 12:26'!
secondaryPaneTransition: event divider: aMorph
	"Mouse has entered or left a pane"
	^ self spawnOffsetReframeHandle: event divider: aMorph! !


!SubpaneDividerMorph reorganize!
('accessing' resizingEdge)
('initialization' firstEnter: horizontal initialize resizingEdge: vertical)
!



More information about the Squeak-dev mailing list