[squeak-dev] The Trunk: Morphic-mt.874.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 15 15:08:45 UTC 2015


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

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

Name: Morphic-mt.874
Author: mt
Time: 15 April 2015, 5:08:05.427 pm
UUID: bc13e9b8-2884-0449-bf15-a26307959176
Ancestors: Morphic-mt.873

Fixes in scroll bar and scroll pane. Retractable scroll bars (known from MVC) work again and can be enabled via preferences.

=============== Diff against Morphic-mt.873 ===============

Item was changed:
  ----- Method: PluggableListMorph>>extent: (in category 'geometry') -----
  extent: newExtent
  	super extent: newExtent.
  	
  	"Change listMorph's bounds to the new width. It is either the size
  	of the widest list item, or the size of self, whatever is bigger"
+ 	self listMorph width: (self width max: listMorph hUnadjustedScrollRange). 
- 	self listMorph width: ((self width max: listMorph hUnadjustedScrollRange) + 20). 
  !

Item was changed:
  ----- Method: PluggableTextMorph>>extent: (in category 'geometry') -----
+ extent: aPoint
- extent: newExtent
  
+ 	super extent: aPoint.
+ 	
+ 	"Update vertical scroll bars because if text is wrapped."
+ 	textMorph ifNotNil: [:tm |
+ 		tm isAutoFit ifTrue: [self vSetScrollDelta]].!
- 	bounds extent = newExtent ifTrue: [^ self].
- 	super extent: (newExtent max: 36 at 16).
- 	self setScrollDeltas
- !

Item was added:
+ ----- Method: PluggableTextMorph>>hasFocus (in category 'accessing') -----
+ hasFocus
+ 
+ 	^ super hasFocus or: [textMorph notNil and: [textMorph hasKeyboardFocus]]!

Item was removed:
- ----- Method: PluggableTextMorph>>resetExtent (in category 'geometry') -----
- resetExtent
- 	"Reset the extent while maintaining the current selection.  Needed when resizing while the editor is active (when inside the pane)."
- 	| tempSelection |
- 	textMorph notNil ifTrue:
- 		["the current selection gets munged by resetting the extent, so store it"
- 		tempSelection := self selectionInterval.
- 		
- 		"don't reset it if it's not active"
- 		tempSelection = (Interval from: 1 to: 0) 
- 						ifTrue: [retractableScrollBar
- 							ifTrue:[ ^ self]].
- 		self extent: self extent.
- 		self setSelection: tempSelection].
- 	super resetExtent.!

Item was changed:
  ----- Method: ScrollBar>>minExtent (in category 'geometry') -----
  minExtent
  	"The minimum extent is that of 2 or 3 buttons in a row or column,
  	the 'up' and 'down' button and optionally the 'menu' button."
  
  	| btns cnt |
+ 	btns := {
+ 		upButton visible.
+ 		downButton visible.
+ 		self menuButton visible. } count: [:ea | ea].
+ 	cnt := 0 @ btns. "assume vertical layout"
- 	btns := 2.
- 	self menuButton visible ifTrue: [
- 		btns := btns + 1].
- 	cnt := 1 at btns. "assume vertical layout"
  	self bounds isWide
  		ifTrue: [cnt := cnt transposed].
+ 	^ (upButton minExtent * cnt) + (self sliderThickness @ self sliderThickness)!
- 	^ upButton minExtent * cnt!

Item was changed:
  ----- Method: ScrollBar>>sliderColor: (in category 'access') -----
  sliderColor: aColor 
  	"Change the color of the scrollbar to go with aColor."
  	| buttonColor |
  	super sliderColor: aColor.
  	self updateSliderColor: aColor.
  	buttonColor := self thumbColor.
- 	self menuButton color: buttonColor.
- 	upButton color: buttonColor.
- 	downButton color: buttonColor.
  	
+ 	self menuButton color: aColor.
+ 	upButton color: aColor.
+ 	downButton color: aColor.
- 	self class updateScrollBarButtonsAspect: {self menuButton. upButton. downButton} color: buttonColor.
  	
+ 	self class updateScrollBarButtonsAspect: {self menuButton. upButton. downButton} color: aColor.
+ 	
  	self updateMenuButtonImage.
  	self updateUpButtonImage.
  	self updateDownButtonImage.!

Item was changed:
  MorphicModel subclass: #ScrollPane
  	instanceVariableNames: 'scrollBar scroller retractableScrollBar scrollBarOnLeft getMenuSelector getMenuTitleSelector scrollBarHidden hasFocus hScrollBar lockOffset'
+ 	classVariableNames: 'UseRetractableScrollBars'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Morphic-Windows'!
  
  !ScrollPane commentStamp: 'mk 8/9/2005 10:34' prior: 0!
  The scroller (a transform) of a scrollPane is driven by the scrollBar.  The scroll values vary from 0.0, meaning zero offset to 1.0 meaning sufficient offset such that the bottom of the scrollable material appears 3/4 of the way down the pane.  The total distance to achieve this range is called the totalScrollRange.
  
  Basic clue about utilization of the ScrollPane class is given in:
  	ScrollPane example1.
  	ScrollPane example2.!

Item was added:
+ ----- Method: ScrollPane class>>useRetractableScrollBars (in category 'preferences') -----
+ useRetractableScrollBars
+ 	
+ 	<preference: 'Use retractable scrollbars'
+ 		category: #scrolling
+ 		description: 'When enabled, scrollbars are hidden when scroll pane is not focused.'
+ 		type: #Boolean>
+ 	^ UseRetractableScrollBars ifNil: [false]!

Item was added:
+ ----- Method: ScrollPane class>>useRetractableScrollBars: (in category 'preferences') -----
+ useRetractableScrollBars: aBoolean
+ 	
+ 	UseRetractableScrollBars = aBoolean ifTrue: [^ self].
+ 	UseRetractableScrollBars := aBoolean.
+ 	ScrollPane allSubInstances do: [:pane | 
+ 		pane retractable: aBoolean.
+ 		pane setScrollDeltas].!

Item was changed:
  ----- Method: ScrollPane>>extent: (in category 'geometry') -----
  extent: newExtent
  	
+ 	| oldW oldH |
- 	| oldW oldH wasHShowing wasVShowing noVPlease noHPlease minH minW |
- 	
  	oldW := self width.
  	oldH := self height.
+ 	
+ 	super extent: (newExtent max: self minScrollbarExtent).
- 	wasHShowing := self hIsScrollbarShowing.
- 	wasVShowing := self vIsScrollbarShowing.
  
- 	"Figure out the minimum width and height for this pane so that scrollbars will appear"
- 	noVPlease := self valueOfProperty: #noVScrollBarPlease ifAbsent: [false]. 
- 	noHPlease := self valueOfProperty: #noHScrollBarPlease ifAbsent: [false]. 
- 	minH := self scrollBarThickness + 16.
- 	minW := self scrollBarThickness + 20.
- 	noVPlease ifTrue:[ 
- 		noHPlease
- 			ifTrue:[minH := 1. minW := 1 ]
- 			ifFalse:[minH := self scrollBarThickness ].
- 	] ifFalse:[
- 		noHPlease
- 			ifTrue:[minH := self scrollBarThickness + 5].
- 	].
- 	super extent: (newExtent max: (minW at minH)).
- 
  	"Now reset widget sizes"
+ 	self
+ 		resizeScrollBars;
+ 		resizeScroller;
+ 		hideOrShowScrollBars.
- 	self resizeScrollBars; resizeScroller; hideOrShowScrollBars.
  	
+ 	"Now resetScrollDeltas where appropriate."
- 	"Now resetScrollDeltas where appropriate, first the vScrollBar..."
  	self height ~~ oldH ifTrue: [self vSetScrollDelta].
- 			
- 	"...then the hScrollBar"
  	self width ~~ oldW ifTrue: [self hSetScrollDelta].
  
  !

Item was added:
+ ----- Method: ScrollPane>>extentToFit (in category 'geometry') -----
+ extentToFit
+ 	"Resize scroll pane to exactly fit its contents."
+ 	
+ 	| offset |
+ 	offset := 0 at 0.
+ 	(retractableScrollBar not and: [self hasProperty: #vScrollBarAlways])
+ 		ifTrue: [offset := (self scrollBarThickness - self borderWidth) @ offset y].
+ 	(retractableScrollBar not and: [self hasProperty: #hScrollBarAlways])
+ 		ifTrue: [offset := offset x @ (self scrollBarThickness - self borderWidth)].
+ 		
+ 	^ scroller submorphBounds extent + offset + (2* (self borderWidth @ self borderWidth))!

Item was added:
+ ----- Method: ScrollPane>>fit (in category 'geometry') -----
+ fit
+ 	"Resize scroll pane to exactly fit its contents."
+ 	
+ 	self extent: self extentToFit.!

Item was changed:
  ----- Method: ScrollPane>>hResizeScrollBar (in category 'geometry') -----
  hResizeScrollBar
  
  	| topLeft h border offset |
  
  "TEMPORARY: IF OLD SCROLLPANES LYING AROUND THAT DON'T HAVE A hScrollBar, INIT THEM"
  	hScrollBar ifNil: [ self hInitScrollBarTEMPORARY].
  	
  	(self valueOfProperty: #noHScrollBarPlease ifAbsent: [false]) ifTrue: [^self].
  	bounds ifNil: [ self fullBounds ].
  	
  	h := self scrollBarThickness.
  	border := borderWidth.
+ 	offset := (scrollBarOnLeft and: [self vIsScrollbarShowing and: [retractableScrollBar not]])
- 	offset := (scrollBarOnLeft and: [self vIsScrollbarShowing])
  		ifTrue: [h]
  		ifFalse: [0].
  	
  	topLeft := retractableScrollBar
+ 				ifTrue: [bounds bottomLeft + (offset @ border negated)]
+ 				ifFalse: [bounds bottomLeft + (offset @ h negated)].
- 				ifTrue: [bounds bottomLeft + (border + offset @ border negated)]
- 				ifFalse: [bounds bottomLeft + (border + offset @ (h + border) negated)].
  
+ 	hScrollBar bounds: (topLeft extent: self hScrollBarWidth@ h)
- 	hScrollBar bounds: (topLeft + (border negated @ border) extent: self hScrollBarWidth@ h)
  !

Item was changed:
  ----- Method: ScrollPane>>hShowScrollBar (in category 'scrolling') -----
  hShowScrollBar
  
  	self hIsScrollbarShowing ifTrue: [^self].
  	self hResizeScrollBar.
  	self privateAddMorph: hScrollBar atIndex: 1.
+ 	retractableScrollBar
+ 		ifTrue: [self comeToFront]
+ 		ifFalse: [self resetExtent].
- 	retractableScrollBar ifFalse: [self resetExtent].
  !

Item was removed:
- ----- Method: ScrollPane>>hideOrShowScrollBar (in category 'scrolling') -----
- 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 vIsScrollable not & self isScrolledFromTop not ifTrue: [self vHideScrollBar].
- 	self vIsScrollable | self isScrolledFromTop ifTrue: [self vShowScrollBar].
- !

Item was changed:
  ----- Method: ScrollPane>>hideOrShowScrollBars (in category 'scrolling') -----
  hideOrShowScrollBars
  
- 	| wasHShowing wasVShowing |
- 
- 	wasVShowing := self vIsScrollbarShowing.
- 	wasHShowing := self hIsScrollbarShowing.
- 
  	self 
  		vHideOrShowScrollBar; 
  		hHideOrShowScrollBar; 
+ 		resizeScrollBars.!
- 		resizeScrollBars.
- 
- 	(wasVShowing and: [self vIsScrollbarShowing not]) ifTrue:
- 		["Make sure the delta is 0"
- 		(scroller offset y = 0) 
- 				ifFalse:[ scroller offset: (scroller offset x at 0) ]].
- 			
- 	(wasHShowing and: [self hIsScrollbarShowing not]) ifTrue:
- 		[(scroller offset x <= 0)
- 				ifFalse:[ scroller offset: (self hMargin negated at scroller offset y)]].
- !

Item was changed:
  ----- Method: ScrollPane>>initializePreferences (in category 'initialization') -----
  initializePreferences
  	"initialize the receiver's Preferences"
+ 	retractableScrollBar := self class useRetractableScrollBars.
- 	retractableScrollBar := false.
  	scrollBarOnLeft := (Preferences valueOfFlag: #scrollBarsOnRight) not.
  	
  
  !

Item was changed:
  ----- Method: ScrollPane>>retractableOrNot (in category 'menu') -----
  retractableOrNot
  	"Change scroll bar operation"
  
  	retractableScrollBar := retractableScrollBar not.
  	retractableScrollBar
+ 		ifTrue: [
+ 			scrollBar disableTableLayout: true.
+ 			hScrollBar disableTableLayout: true.
+ 			self removeMorph: scrollBar; removeMorph: hScrollBar]
- 		ifTrue: [self removeMorph: scrollBar]
  		ifFalse: [(submorphs includes: scrollBar) 
  					ifFalse: 
  						[self privateAddMorph: scrollBar atIndex: 1.
  						self privateAddMorph: hScrollBar atIndex: 1]].
+ 	self extent: self extent.!
- 	self extent: self extent.
- !

Item was changed:
  ----- Method: ScrollPane>>vResizeScrollBar (in category 'geometry') -----
  vResizeScrollBar
  	| w topLeft border |
  	w := self scrollBarThickness.
  	border := self borderWidth.
  	topLeft := scrollBarOnLeft 
  		ifTrue: [retractableScrollBar 
+ 			ifTrue: [bounds topLeft - ((w - border) @ 0)]
+ 			ifFalse: [bounds topLeft]]
- 			ifTrue: [bounds topLeft - ((w - border) @ border negated)]
- 			ifFalse: [bounds topLeft + (border @ border)]]
  		ifFalse: [retractableScrollBar 
+ 			ifTrue: [bounds topRight - (border @ 0)]
+ 			ifFalse: [bounds topRight - (w @ 0)]].
- 			ifTrue: [bounds topRight - (border @ border negated)]
- 			ifFalse: [bounds topRight - ((w + border) @ border negated)]].
  			
+ 	scrollBar bounds: (topLeft extent: w @ self vScrollBarHeight)
- 	scrollBar 
- 		bounds: (topLeft + ((scrollBarOnLeft ifTrue: [border negated] ifFalse: [border]) @ border negated)
- 			extent: w @ self vScrollBarHeight)
  	
  !

Item was changed:
  ----- Method: ScrollPane>>vShowScrollBar (in category 'scrolling') -----
  vShowScrollBar
  
  	self vIsScrollbarShowing ifTrue: [^ self].
  	self vResizeScrollBar.
  	self privateAddMorph: scrollBar atIndex: 1.
+ 	retractableScrollBar
+ 		ifTrue: [self comeToFront]
+ 		ifFalse: [self resetExtent]
- 	retractableScrollBar ifFalse: [self resetExtent]
  !



More information about the Squeak-dev mailing list