Skip to content

Commit

Permalink
BoundedEnum for Columns & Rows
Browse files Browse the repository at this point in the history
  • Loading branch information
albertprz committed Nov 11, 2023
1 parent 0b93d98 commit 76969dd
Show file tree
Hide file tree
Showing 13 changed files with 126 additions and 129 deletions.
1 change: 0 additions & 1 deletion src/Components/Table.purs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ initialState = const
, tableDependencies: HashMap.empty
, tableFormulas: HashMap.empty
, formulaCache: HashMap.empty
, columns: bottom .. top
, rows: bottom .. Row 100
, multiSelection: NoSelection
, selectionState: NotStartedSelection
Expand Down
48 changes: 25 additions & 23 deletions src/Components/Table/Cell.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module App.Components.Table.Cell where
import FatPrelude
import Prim hiding (Row)

import App.Utils.Bounded (newtypeCardinality, newtypeFromEnum, newtypeToEnum)
import App.Utils.HashMap (swapKey) as HashMap
import Bookhound.Parser (Parser, runParser)
import Bookhound.ParserCombinators (is)
Expand Down Expand Up @@ -54,27 +55,27 @@ getColumnCell
-> Cell
-> Maybe Cell
getColumnCell f { column, row } =
({ column: _, row }) <$> getElemSat (f column)
({ column: _, row }) <$> getInBoundedRange (f column)

getRowCell
:: (Row -> Row)
-> Cell
-> Maybe Cell
getRowCell f { column, row } =
({ column, row: _ }) <$> getElemSat (f row)

nextColumnCell :: Cell -> Cell
nextColumnCell { column, row } = { column: inc column, row }
({ column, row: _ }) <$> getInBoundedRange (f row)

prevColumnCell :: Cell -> Cell
prevColumnCell { column, row } = { column: dec column, row }

nextRowCell :: Cell -> Cell
nextRowCell { column, row } = { column, row: inc row }
nextColumnCell :: Cell -> Cell
nextColumnCell { column, row } = { column: inc column, row }

prevRowCell :: Cell -> Cell
prevRowCell { column, row } = { column, row: dec row }

nextRowCell :: Cell -> Cell
nextRowCell { column, row } = { column, row: inc row }

getColumnHeader :: Header -> Maybe Column
getColumnHeader (ColumnHeader header) = Just header
getColumnHeader _ = Nothing
Expand All @@ -83,15 +84,6 @@ getRowHeader :: Header -> Maybe Row
getRowHeader (RowHeader header) = Just header
getRowHeader _ = Nothing

firstRow :: Row
firstRow = Row 1

maxRow :: Row
maxRow = Row 1_000

maxRowBounds :: NonEmptyArray Row
maxRowBounds = firstRow .. maxRow

swapTableMapColumn
:: forall v. Column -> Column -> HashMap Cell v -> HashMap Cell v
swapTableMapColumn origin target tableDict =
Expand All @@ -115,6 +107,12 @@ swapTableMapRow origin target tableDict =
(\cell -> cell.row == origin || cell.row == target)
(HashMap.keys tableDict)

allColumns :: NonEmptyArray Column
allColumns = allValues

allRows :: NonEmptyArray Row
allRows = allValues

newtype Column = Column Int

newtype Row = Row Int
Expand Down Expand Up @@ -158,11 +156,13 @@ instance Hashable Column where
hash = unwrap

instance Bounded Column where
bottom = wrap upperStartCode
top = wrap upperEndCode
bottom = zero
top = wrap (upperEndCode - upperStartCode)

instance Range Column where
range (Column c1) (Column c2) = Column <$> c1 .. c2
instance BoundedEnum Column where
cardinality = newtypeCardinality
fromEnum = newtypeFromEnum
toEnum = newtypeToEnum

derive newtype instance Eq Row
derive newtype instance Ord Row
Expand All @@ -179,10 +179,12 @@ instance Hashable Row where

instance Bounded Row where
bottom = one
top = wrap 1000000
top = wrap 10_000

instance Range Row where
range (Row r1) (Row r2) = Row <$> r1 .. r2
instance BoundedEnum Row where
cardinality = newtypeCardinality
fromEnum = newtypeFromEnum
toEnum = newtypeToEnum

derive instance Eq CellValue

Expand Down
40 changes: 21 additions & 19 deletions src/Components/Table/HandlerHelpers.purs
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,6 @@ copyCells
copyCells ev = withPrevent ev do
cellContents <- gets \st -> serializeSelectionValues st.multiSelection
st.selectedCell
st.columns
st.tableData
modify_ _ { selectionState = CopySelection }
liftAff $ Promise.toAffE $ writeText cellContents =<< getClipboard
Expand All @@ -82,7 +81,7 @@ pasteCells ev = withPrevent ev do
clipContents <- liftAff $ Promise.toAffE $ readText =<< getClipboard
let
newValues =
deserializeSelectionValues st.selectedCell st.columns clipContents
deserializeSelectionValues st.selectedCell clipContents
modify_ _
{ tableData = HashMap.union
newValues
Expand All @@ -95,7 +94,7 @@ deleteCells = do
st <- get
let
cellsToDelete =
join $ getTargetCells st.multiSelection st.selectedCell st.columns
join $ getTargetCells st.multiSelection st.selectedCell
modify_ _
{ tableData = foldl (flip HashMap.delete) st.tableData cellsToDelete }
refreshCells $ Set.fromFoldable cellsToDelete
Expand All @@ -112,62 +111,65 @@ selectCell
:: forall m. MonadEffect m => MonadState AppState m => CellMove -> m Unit
selectCell move = do
originCell <- gets _.selectedCell
{ selectedCell, columns, rows } <- modify \st -> st
{ selectedCell, rows } <- modify \st -> st
{ activeInput = false
, multiSelection = NoSelection
, selectedCell = getCellFromMove move st.selectedCell
}
visibleCols <- getVisibleCols
visibleRows <- getVisibleRows
goToCell visibleCols visibleRows columns rows originCell selectedCell
goToCell visibleCols visibleRows rows originCell selectedCell

goToCell
:: forall m
. MonadEffect m
=> MonadState AppState m
=> Array Element
-> Array Element
-> NonEmptyArray Column
-> NonEmptyArray Row
-> Cell
-> Cell
-> m Unit
goToCell visibleCols visibleRows allColumns allRows origin target = do
cols <- parseElements parseColumn visibleCols
sequence_ $ adjustRows (length visibleRows - 1) target.row <$> maximum allRows
<*> minimum allRows
liftEffect $ goToCellHelper cols allColumns origin target visibleCols
goToCell visibleCols visibleRows rows origin target = do
cols <- parseElements parseColumns visibleCols
adjustRows (length visibleRows - 1) target.row
(maximum1 rows)
(minimum1 rows)
liftEffect $ goToCellHelper cols origin target visibleCols
where
parseColumn = hush <<< runParser columnParser
parseColumns = hush <<< runParser columnParser

goToCellHelper
:: Array Column
-> NonEmptyArray Column
-> Cell
-> Cell
-> Array Element
-> Effect Unit
goToCellHelper cols allColumns origin { column, row } visibleCols
goToCellHelper cols origin { column, row } visibleCols

| last' cols == Just column && last allColumns /= origin.column = do
| last' cols == Just column && top /= origin.column = do
width <- traverse scrollWidth $ head' visibleCols
scrollByX (coalesce width + 1.0) =<< window

| head' cols == Just column && head allColumns /= origin.column = do
| head' cols == Just column && bottom /= origin.column = do
width <- traverse scrollWidth $ last' visibleCols
scrollByX (-(coalesce width + 1.0)) =<< window

| otherwise = focusCell { column, row }

adjustRows
:: forall m. MonadState AppState m => Int -> Row -> Row -> Row -> m Unit
adjustRows rowRange (Row currentRow) (Row maxRow) (Row minRow)
adjustRows rowRange currentRow maxRow minRow

| inc currentRow > maxRow = modify_ _
{ rows = Row <$> (currentRow - inc rowRange) .. (inc currentRow) }
{ rows = clampBounded (currentRow - wrap (inc rowRange))
.. clampBounded (inc currentRow)
}

| currentRow < minRow = modify_ _
{ rows = Row <$> currentRow .. (currentRow + rowRange) }
{ rows = clampBounded currentRow
.. clampBounded (currentRow + wrap rowRange)
}

| otherwise = pure unit

Expand Down
3 changes: 1 addition & 2 deletions src/Components/Table/Models.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module App.Components.Table.Models where
import FatPrelude
import Prim hiding (Row)

import App.Components.Table.Cell (Cell, CellValue, Column, Header, Row)
import App.Components.Table.Cell (Cell, CellValue, Header, Row)
import App.Components.Table.Formula (Formula, FormulaId, FormulaState)
import App.Components.Table.Selection (MultiSelection, SelectionState)
import App.SyntaxTree.Common (Module, QVar, QVarOp)
Expand All @@ -25,7 +25,6 @@ type AppState =
, tableFormulas :: HashMap Cell FormulaId
, tableDependencies :: HashMap Cell (NonEmptySet FormulaId)
, formulaCache :: HashMap FormulaId Formula
, columns :: NonEmptyArray Column
, rows :: NonEmptyArray Row
, multiSelection :: MultiSelection
, selectionState :: SelectionState
Expand Down
9 changes: 4 additions & 5 deletions src/Components/Table/Renderer.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import Prim hiding (Row)

import App.CSS.ClassNames (aboveSelection, atLeftSelection, atRightSelection, belowSelection, columnHeader, copySelection, cornerHeader, formulaBox, formulaBoxContainer, formulaCellInput, formulaContainer, formulaSignature, inSelection, mainContainer, rowHeader, selectedCellInput, selectedHeader, selectedSheetCell, sheetCell)
import App.CSS.Ids (cellId, formulaBoxId, formulaCellInputId, formulaSignatureId, selectedCellInputId)
import App.Components.Table.Cell (Cell, CellValue, Column, Header(..), Row, cellParser, parseCellValue, showCell)
import App.Components.Table.Cell (Cell, CellValue, Column, Header(..), Row, allColumns, cellParser, parseCellValue, showCell)
import App.Components.Table.Formula (formulaStateToClass)
import App.Components.Table.Models (Action(..), AppState, EventTransition(..))
import App.Components.Table.Selection (SelectionState(..), isCellAboveSelection, isCellAtLeftSelection, isCellAtRightSelection, isCellBelowSelection, isCellInSelection, isColumnSelected, isRowSelected)
Expand Down Expand Up @@ -87,13 +87,13 @@ renderFormulaDisplay { selectedCell, formulaCache, tableFormulas } =
tableFormulas

renderHeader :: forall i. AppState -> HTML i Action
renderHeader st@{ columns } =
renderHeader st =
thead_
[ tr_
$ toArray
$ cons
renderHeaderCorner
(renderColumnHeader st <$> columns)
(renderColumnHeader st <$> allColumns)
]
where
renderHeaderCorner =
Expand All @@ -108,7 +108,6 @@ renderBody :: forall i. AppState -> HTML i Action
renderBody
st@
{ rows
, columns
, tableData
} =
tbody_ $ toArray do
Expand All @@ -118,7 +117,7 @@ renderBody
(renderRow row)
where
renderRow row = do
column <- columns
column <- allColumns
let
cell = { column, row }
cellValue = HashMap.lookup cell tableData
Expand Down
Loading

0 comments on commit 76969dd

Please sign in to comment.