As a followup, attached is a changeset for Pharo8 with a simple
implementation of horizontal scrolling. I tried to keep it minimal.
It adds startColumnIndex var to FTTableContainerMorph which is being set
when  FTTableContainerMorph>>adjustToHorizontalScrollBarValue: is triggered.
The  main change is in #calculateColumnWidths - it starts distributing
space width from the startColumnIndex to ensure this area gets most
visibility. If startColumnIndex is 0, it reverts to old (current) behavior
- trying to draw columns starting from the first one as space permits.

The scrolling thus jumps to a beginning of the column and I'm not
particularly proud of the thing, but it is better then nothing and suits my
immediate needs. So may be it is worth a look for those who are interested.

To try one can use an example:
FTExamples exampleTableHorizontalScroll

Or even set trialHSB := true in FTTableMorth>>initialize (like I have to
enable it everywhere by default)
(as a side note the list is very quiet, compared to what it used to be
years ago)

пн, 4 нояб. 2019 г. в 14:14, Danil Osipchuk <danil.osipc...@gmail.com>:

> Hi all
>
> I wonder what is happening to the horizontal scrolling in FastTable, the
> stub is there for years (I've checked the latest 8.0).
> I need it rather badly, could someone advise what is the hindrance there?
> I would try doing it myself, but I've never was doing much of UI
> programming and only recently returned to Pharo again, so have to catch up
> (a lot of things changed for good).
>
> How difficult would be to adopt vertical scrolling approach (which seems
> to be the same problem already solved to layperson )
>
>
> horizontalScrollBarValue: aNumber
> trialHSB ifNotNil: [
> self inform: 'FTTableMorph>>#horizontalScrollBarValue: ', aNumber
> printString , String cr,
> 'Does nothing yet.' , String cr, 'Need some advise here.'
> ].
>
> regards,
>   Danil
>
'From Pharo8.0.0 of 7 November 2019 [Build information: Pharo-8.0.0+build.953.sha.febfc2d7be79760a59defe4725cd61822c8ddcc2 (64 Bit)] on 7 November 2019 at 7:26:53.320268 pm'!
Morph subclass: #FTTableContainerMorph
	instanceVariableNames: 'needsRefreshExposedRows headerRow exposedRows startColumnIndex'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets-FastTable'!

!FTTableContainerMorph commentStamp: 'DanilOsipchuk 11/7/2019 16:26' prior: 0!
I am a Morph that contain visible rows in a FTTableMorph. 

Description 
------------------

I am the main Morph of the FastTable that is responsible of displaying all the rows of a Table. 
My owner need to be a FTTableMorph and I will use his dataSource to display the needed informations.

Public API and Key Messages
-----------------
		
- #updateAllRows 

- #updateExposedRows

- #ipdateHeaderRow
 
Internal Representation and Key Implementation Points.
----------------

    Instance Variables
	exposedRows:		A dictionary of index/row with all the exposed rows.
	headerRow:			When not nil contains the header row of the container.
	needsRefreshExposedRows:		A boolean that is true if the container need a refresh.
	startColumnIndex: An integer - first column to start drawing when scrolling horizontally, nil/0 - old behaviour (no scrolling)

The method #drawOn: is responsible of my rendering.!

FTTableContainerMorph subclass: #FTTableContainerRowNotHomogeneousMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets-FastTable'!

!FTFunctionWithField methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 18:29'!
resizeWidget
	| topLeft bottomRight |
	self flag: #pharoTodo.	"Maybe it could be cool to let the user choose if the field need to be at the top or the bottom."
	topLeft := table bounds left @ (table bounds bottom - self fieldHeigh - table horizontalScrollBarHeight ).
	bottomRight := (table bounds right - table verticalScrollBarWidth) @ (table bottom - table horizontalScrollBarHeight).
	field bounds: (topLeft corner: bottomRight)! !


!FTFilterFunctionWithAction methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 18:30'!
resizeButton
	| topLeft bottomRight |
	self flag: #pharoTodo.	"Maybe it could be cool to let the user choose if the field need to be at the top or the bottom."
	bottomRight := (table bounds right - table verticalScrollBarWidth) @ (table bottom - table horizontalScrollBarHeight).
	topLeft := (bottomRight x - actionButton width) @ (table bounds bottom - self fieldHeigh - table horizontalScrollBarHeight).
	actionButton bounds: (topLeft corner: bottomRight)! !

!FTFilterFunctionWithAction methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 18:30'!
resizeField
	| topLeft bottomRight |
	self flag: #pharoTodo.	"Maybe it could be cool to let the user choose if the field need to be at the top or the bottom."
	topLeft := table bounds left @ (table bounds bottom - self fieldHeigh - table horizontalScrollBarHeight).
	bottomRight := (table bounds right - table verticalScrollBarWidth - (actionButton width + 5))
		@ (table bottom - table horizontalScrollBarHeight).
	field bounds: (topLeft corner: bottomRight)! !


!FTTableContainerMorph methodsFor: 'initialization' stamp: 'DanilOsipchuk 11/7/2019 15:11'!
initialize 
	super initialize.
	needsRefreshExposedRows := false.
	startColumnIndex :=0.! !

!FTTableContainerMorph methodsFor: 'updating' stamp: 'DanilOsipchuk 11/7/2019 13:50'!
updateExposedRows
	| visibleRows numberOfColumns columns columnWidths startIndex |
	
	self canRefreshValues ifFalse: [ ^ self ].

	visibleRows := self calculateMaxVisibleRows.
	startIndex := self calculateStartIndexWhenShowing: visibleRows.
	numberOfColumns := self table numberOfColumns.
	columns := self table columns. 
	columnWidths := self calculateColumnWidths.

	exposedRows := SmallDictionary new.
	startIndex to: ((startIndex + visibleRows - 1) min: self table numberOfRows) do: [ :rowIndex | 
		| row |
		row := FTTableRowMorph table: self table.
		(self exposedColumnsRange: columnWidths) do: [ :columnIndex | | cell |
			cell := (self table dataSource 
				cellColumn: (columns at: columnIndex)
				row: rowIndex).  
			cell width: (columnWidths at: columnIndex).
			row addMorphBack: cell ].
		row privateOwner: self.
		exposedRows at: rowIndex put: row ]! !

!FTTableContainerMorph methodsFor: 'updating' stamp: 'DanilOsipchuk 11/7/2019 16:02'!
adjustToHorizontalScrollBarValue: aNumber 
	| newStartColumnIndex | 
	newStartColumnIndex := (self table numberOfColumns * aNumber) rounded 
		min: self table numberOfColumns 
		max: 1 .
	newStartColumnIndex ~= self startColumnIndex 
		ifTrue: [ 
			self startColumnIndex: newStartColumnIndex.
			self changed  ]
! !

!FTTableContainerMorph methodsFor: 'updating' stamp: 'DanilOsipchuk 11/7/2019 15:41'!
updateHeaderRow
	"Recalculates the header row if they are defined. 
	 Please, note that If one of the headers is nil, I assume all are nil and I return. 
	 This is probably not the best approach, but like that I enforce people defines at least 
	 a default if they want headers."
	| columns columnHeaders columnWidths |

	self canRefreshValues ifFalse: [ ^ self ].

	headerRow := nil.
	columns := self table columns.	
	columnHeaders := OrderedCollection new.
	columnWidths := self calculateColumnWidths.
	
	(self exposedColumnsRange: columnWidths)  do: [ :index | | column headerCell columnWidth|
		column := columns at: index.
		columnWidth := columnWidths at: index.
		headerCell :=  self table dataSource headerColumn: column. 
		headerCell ifNil: [ ^ self ]. 
		headerCell 
			color: self table headerColor;
			width: columnWidth.
		columnHeaders addLast: headerCell.
		FTDisplayColumn column: column width: columnWidth ].
	 
	headerRow := (FTTableHeaderRowMorph table: self table)
		privateOwner: self;
		addAllMorphs: columnHeaders;
		yourself! !

!FTTableContainerMorph methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 16:13'!
calculateColumnWidths

	"do three runs 
	- first collect defined columnwidth that fit
	- collect remaining undefined columnwidth 
	- return if all fit 
	  or collect and distribute remaining width.
	
 	DanilOsipchuk: the method was adjusted to distribute space starting from startColumnIndex 
	to enable horizontal scrolling when columns do not fit the window,
	see #columnOrderOfWidthDistribution"
	

	| undefinedColumnWidths widths remainingWidth |
	remainingWidth := self table bounds width.

	widths := Array new: self table numberOfColumns withAll: 0.
	self columnOrderOfWidthDistribution do: [ :idx || column columnWidth |
		column := self table columns at: idx. 
		columnWidth := column acquireWidth: remainingWidth.
		widths at: idx put: columnWidth.
		remainingWidth := remainingWidth - columnWidth ].

	undefinedColumnWidths := widths count: #isZero.
	undefinedColumnWidths isZero
		ifTrue: [ widths size > 1 ifTrue: [ "Set the remaining space to the last column" widths at: widths size put: widths last + remainingWidth ].
			^ widths ].


	"collect and distribute remaining space"
	self columnOrderOfWidthDistribution do: [ :idx | 
		(widths at: idx) = 0 	ifTrue: [ widths at: idx put: (remainingWidth / undefinedColumnWidths) ] ].
	^widths! !

!FTTableContainerMorph methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 16:07'!
columnOrderOfWidthDistribution
	"returns column indexes ordered by priority to available width"
	| idxToLast idxToFirstReversed |
	self startColumnIndex isZero "a special case implementing old behaviour -- all columns as they are present"
		ifTrue: [ ^(1 to: self table numberOfColumns) ].
	"new behaviour intended to garantee the visibility of columns around startColumnIndex
		first give width starting from startColumnIndex towards end,
		then from previous available column towards beginning"
	idxToLast := startColumnIndex to: self table numberOfColumns.
	idxToFirstReversed := startColumnIndex>1 ifTrue: [startColumnIndex-1 to: 1 by: -1] ifFalse: [#()].
	^idxToLast,idxToFirstReversed! !

!FTTableContainerMorph methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 16:01'!
exposedColumnsRange: columnWidths
	"Return a subset of indexes for columns which are to be drawn.
	startColumnIndex=0 means old behaviour -- try all of them
	otherwise we select only indexes of columns having non-zero width"
	
	^self startColumnIndex isZero
		ifTrue: [1 to: self table numberOfColumns] 
		ifFalse: [(1 to: columnWidths size) select: [ :idx | (columnWidths at: idx)>0 ]  ]
! !

!FTTableContainerMorph methodsFor: 'accessing' stamp: 'DanilOsipchuk 11/7/2019 16:00'!
startColumnIndex
	startColumnIndex ifNil: [ startColumnIndex := 0 ].
	^startColumnIndex! !

!FTTableContainerMorph methodsFor: 'accessing' stamp: 'DanilOsipchuk 11/7/2019 15:53'!
startColumnIndex: anObject
	startColumnIndex := anObject! !


!FTTableMorph methodsFor: 'private' stamp: 'DanilOsipchuk 11/7/2019 14:50'!
horizontalScrollBarValue: aNumber
	trialHSB ifNotNil: [ 
	self container adjustToHorizontalScrollBarValue: aNumber.
	].! !


FTTableContainerMorph subclass: #FTTableContainerRowNotHomogeneousMorph
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Morphic-Widgets-FastTable'!
Morph subclass: #FTTableContainerMorph
	instanceVariableNames: 'needsRefreshExposedRows headerRow exposedRows startColumnIndex'
	classVariableNames: ''
	package: 'Morphic-Widgets-FastTable'!

Reply via email to