Skip to content

Commit

Permalink
Working cell selection
Browse files Browse the repository at this point in the history
  • Loading branch information
jecisc committed Feb 4, 2019
1 parent ab704d3 commit e58ee3b
Show file tree
Hide file tree
Showing 8 changed files with 161 additions and 159 deletions.
7 changes: 1 addition & 6 deletions src/Morphic-Widgets-FastTable/FTCellMorph.class.st
Expand Up @@ -30,18 +30,13 @@ Internal Representation and Key Implementation Points.
"
Class {
#name : #FTCellMorph,
#superclass : #Morph,
#superclass : #FTSelectableMorph,
#instVars : [
'topSeparator'
],
#category : #'Morphic-Widgets-FastTable'
}

{ #category : #initialize }
FTCellMorph >> defaultColor [
^ Color transparent
]

{ #category : #drawing }
FTCellMorph >> drawOn: aCanvas [
super drawOn: aCanvas.
Expand Down
46 changes: 19 additions & 27 deletions src/Morphic-Widgets-FastTable/FTMultipleSelection.class.st
Expand Up @@ -14,51 +14,43 @@ FTMultipleSelection >> isMultiple [
]

{ #category : #private }
FTMultipleSelection >> selectAppendingRowIndex: rowIndex [
FTMultipleSelection >> selectAppendingIndex: index [
| currentSelection newSelection |
currentSelection := self table selectedIndexes.

newSelection := (currentSelection includes: rowIndex)
ifTrue: [ currentSelection copyWithout: rowIndex ]
ifFalse: [ currentSelection copyWithFirst: rowIndex].
newSelection := (currentSelection includes: index)
ifTrue: [ currentSelection copyWithout: index ]
ifFalse: [ currentSelection copyWithFirst: index].

self table selectIndexes: newSelection
]

{ #category : #accessing }
FTMultipleSelection >> selectRowIndex: rowIndex event: event [
event shiftPressed ifTrue: [ ^ self selectRowIndexesUpTo: rowIndex ].
event commandKeyPressed ifTrue: [ ^ self selectAppendingRowIndex: rowIndex ].
self toggleRowIndex: rowIndex

FTMultipleSelection >> selectIndex: index event: event [
event shiftPressed ifTrue: [ ^ self selectIndexesUpTo: index ].
OSPlatform current isMacOS
ifTrue: [ event commandKeyPressed ifTrue: [ ^ self selectAppendingIndex: index ] ]
ifFalse: [ event controlKeyPressed ifTrue: [ ^ self selectAppendingIndex: index ] ].
self toggleIndex: index
]

{ #category : #private }
FTMultipleSelection >> selectRowIndexes: rowIndex previous: oldSelection [
"I ensure the selected row index is the first in selection range so I can handle it better.
FTMultipleSelection >> selectIndexes: index previous: oldSelection [
"I ensure the selected index is the first in selection range so I can handle it better.
I do not like to assume and probably I will need the concept of 'selection', but for now
let's not abuse :)"
self table selectIndexes: (((oldSelection includes: rowIndex)
ifTrue: [ oldSelection copyWithout: rowIndex ]
ifFalse: [ oldSelection] )
copyWithFirst: rowIndex)

self table selectIndexes: (((oldSelection includes: index) ifTrue: [ oldSelection copyWithout: index ] ifFalse: [ oldSelection ]) copyWithFirst: index)
]

{ #category : #private }
FTMultipleSelection >> selectRowIndexesUpTo: endIndex [
"Selects a range of rows, from what is already selected to a new rowIndex.
FTMultipleSelection >> selectIndexesUpTo: endIndex [
"Selects a range of selectables, from what is already selected to a new index.
This is used in case of multiple selections (when holding shift)"
| oldSelected firstIndex step |

| oldSelected firstIndex |
oldSelected := self table selectedIndexes.
firstIndex := oldSelected
ifNotEmpty: [ oldSelected first ]
ifEmpty: [ endIndex ].
step := firstIndex <= endIndex
ifTrue: [ 1 ]
ifFalse: [ -1 ].
firstIndex := oldSelected ifNotEmpty: [ oldSelected first ] ifEmpty: [ endIndex ].

self
selectRowIndexes: endIndex
previous: (oldSelected union: (firstIndex to: endIndex by: step))
self selectIndexes: endIndex previous: (oldSelected union: (self table selectionModeStrategy indexesToSelectInMultipleSelectionFrom: firstIndex to: endIndex))
]
10 changes: 4 additions & 6 deletions src/Morphic-Widgets-FastTable/FTSelectableMorph.class.st
Expand Up @@ -7,12 +7,12 @@ Class {
#category : #'Morphic-Widgets-FastTable'
}

{ #category : #initialize }
{ #category : #initialization }
FTSelectableMorph >> defaultColor [
^ Color transparent
]

{ #category : #'as yet unclassified' }
{ #category : #initialization }
FTSelectableMorph >> initialize [
super initialize.
selectionColor := self defaultColor
Expand All @@ -33,15 +33,13 @@ FTSelectableMorph >> mouseOverColor [
^ self theme lightBackgroundColor
]

{ #category : #initialize }
{ #category : #initialization }
FTSelectableMorph >> selectionColor [

^selectionColor
^ selectionColor
]

{ #category : #accessing }
FTSelectableMorph >> selectionColor: aColor [

selectionColor := aColor.
self color: selectionColor
]
Expand Down
15 changes: 10 additions & 5 deletions src/Morphic-Widgets-FastTable/FTSelectionStrategy.class.st
Expand Up @@ -29,10 +29,15 @@ FTSelectionStrategy >> isSimple [
]

{ #category : #accessing }
FTSelectionStrategy >> selectRowIndex: rowIndex event: event [
FTSelectionStrategy >> selectIndex: rowIndex event: event [
self subclassResponsibility
]

{ #category : #accessing }
FTSelectionStrategy >> selectionModeStrategy [
^ self table selectionModeStrategy
]

{ #category : #accessing }
FTSelectionStrategy >> table [
^ table
Expand All @@ -44,8 +49,8 @@ FTSelectionStrategy >> table: aTable [
]

{ #category : #private }
FTSelectionStrategy >> toggleRowIndex: rowIndex [
((self table selectedIndexes includes: rowIndex) and: [ self table selectedIndexes size = 1 and: [ self table allowsDeselection ] "just one selected" ])
ifTrue: [ self table selectIndexes: #() ]
ifFalse: [ self table selectIndex: rowIndex ]
FTSelectionStrategy >> toggleIndex: index [
((self table selectedIndexes includes: index) and: [ self table selectedIndexes size = 1 and: [ self table allowsDeselection ] "just one selected" ])
ifTrue: [ self table deselectAll ]
ifFalse: [ self table selectIndex: index ]
]
4 changes: 2 additions & 2 deletions src/Morphic-Widgets-FastTable/FTSimpleSelection.class.st
Expand Up @@ -14,6 +14,6 @@ FTSimpleSelection >> isMultiple [
]

{ #category : #accessing }
FTSimpleSelection >> selectRowIndex: rowIndex event: event [
self toggleRowIndex: rowIndex
FTSimpleSelection >> selectIndex: rowIndex event: event [
self toggleIndex: rowIndex
]
43 changes: 20 additions & 23 deletions src/Morphic-Widgets-FastTable/FTTableContainerMorph.class.st
Expand Up @@ -177,15 +177,15 @@ FTTableContainerMorph >> defaultColor [

{ #category : #drawing }
FTTableContainerMorph >> drawOn: canvas [
| x y cellWidth cellHeight rowsToDisplay rowSubviews highligtedRowIndexes primarySelectionIndex |
| x y cellWidth cellHeight rowsToDisplay rowSubviews highligtedIndexes primarySelectionIndex |
super drawOn: canvas.
self canRefreshValues ifFalse: [ ^ self ]. "Nothing to update yet"

x := self left + self class rowLeftMargin.
y := self top.
cellWidth := self width - self class rowLeftMargin.
cellHeight := self table rowHeight rounded.
highligtedRowIndexes := self table selectedIndexes , self table highlightedIndexes.
highligtedIndexes := self table selectedIndexes , self table highlightedIndexes.
primarySelectionIndex := self table selectedIndex.

"For some superweird reason, calling #calculateExposedRows here instead in #changed (where
Expand All @@ -196,28 +196,25 @@ FTTableContainerMorph >> drawOn: canvas [

rowsToDisplay := self exposedRows.
rowSubviews := OrderedCollection new: rowsToDisplay size + 1.
headerRow ifNotNil: [
headerRow bounds: (self left@y extent: self width@cellHeight).
y := y + cellHeight + self table intercellSpacing y.
rowSubviews add: headerRow ].
headerRow
ifNotNil: [ headerRow bounds: (self left @ y extent: self width @ cellHeight).
y := y + cellHeight + self table intercellSpacing y.
rowSubviews add: headerRow ].

rowsToDisplay keysAndValuesDo: [ :rowIndex :row | | visibleHeight |
visibleHeight := cellHeight min: (self bottom - y).
row bounds: (x@y extent: cellWidth@visibleHeight).
y := y + visibleHeight + self table intercellSpacing y.

"rowSubviews add: row.
(self table selectionMode == #column)
ifTrue: [row submorphs withIndexDo: [ :each :columnIndex |
(SelectedCellIndexes includes: (Array with:rowIndex with:columnIndex))
ifTrue: [ each columnSelectionColor: (self table colorForSelection:(primarySelectionCellIndex first = rowIndex and:primarySelectionCellIndex second = columnIndex )) ]]]
ifFalse:[(highligtedRowIndexes includes: rowIndex) ifTrue: [
row selectionColor: (self table colorForSelection: primarySelectionIndex = rowIndex) ]]. "


(highligtedRowIndexes includes: rowIndex) ifTrue: [
row selectionColor: (self table colorForSelection: primarySelectionIndex = rowIndex) ].
rowSubviews add: row ].
rowsToDisplay
keysAndValuesDo: [ :rowIndex :row |
| visibleHeight |
visibleHeight := cellHeight min: self bottom - y.
row bounds: (x @ y extent: cellWidth @ visibleHeight).
y := y + visibleHeight + self table intercellSpacing y.

rowSubviews add: row.

(self table selectionModeStrategy
selectablesToHighlightFromRow: row
at: rowIndex
withHighlightedIndexes: highligtedIndexes
andPrimaryIndex: primarySelectionIndex) keysAndValuesDo: [ :morph :isPrimary | morph selectionColor: (self table colorForSelection: isPrimary) ] ].

"We should notify existing rows about deletion and new rows about insertion.
It is required to correctly manage stepping animation of cells"
Expand Down

0 comments on commit e58ee3b

Please sign in to comment.