Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Grid tabular list is a uniform grid that supports cell-by-cell navigation.
Read Shared Traits of Tabular List Widgets before reading further.
Because this list is designed to show an arbitrary number of columns, horizontal scrolling is supported through cell-by-cell navigation.
Grid tabular list tries to show the current column in the center. If it can't show the current column in the center, it shows the first column in the left corner or the last column in the right corner.
It should be fast enough to handle a large spreadsheet. It is also suitable for an interface to a database table.
Synopsis
- data GridContents n row cell rowH colH = GridContents {}
- data GridContext = GridContext {}
- data GridRenderers n row cell rowH colH = GridRenderers {
- drawCell :: ListFocused -> WidthDeficit -> GridContext -> row -> Maybe cell -> Widget n
- drawRowHdr :: Maybe (ListFocused -> WidthDeficit -> Position -> row -> Maybe rowH -> Widget n)
- drawColHdr :: Maybe (ListFocused -> WidthDeficit -> Position -> Maybe colH -> Widget n)
- data GridSizes rowH = GridSizes {}
- data GridTabularList n row cell rowH colH = GridTabularList {
- list :: GenericList n Seq row
- sizes :: GridSizes rowH
- contents :: GridContents n row cell rowH colH
- currentColumn :: ColumnIndex
- gridTabularList :: n -> Seq row -> ListItemHeight -> GridSizes rowH -> GridContents n row cell rowH colH -> GridTabularList n row cell rowH colH
- renderGridTabularList :: (Ord n, Show n) => GridRenderers n row cell rowH colH -> ListFocused -> GridTabularList n row cell rowH colH -> Widget n
- gridMoveLeft :: GridTabularList n row cell rowH colH -> GridTabularList n row cell rowH colH
- gridMoveRight :: GridTabularList n row cell rowH colH -> GridTabularList n row cell rowH colH
- gridMoveTo :: ColumnIndex -> GridTabularList n row cell rowH colH -> GridTabularList n row cell rowH colH
- gridMoveToBeginning :: GridTabularList n row cell rowH colH -> GridTabularList n row cell rowH colH
- gridMoveToEnd :: GridTabularList n row cell rowH colH -> GridTabularList n row cell rowH colH
- gridMovePageUp :: Ord n => GridRenderers n row cell rowH colH -> EventM n (GridTabularList n row cell rowH colH) ()
- gridMovePageDown :: Ord n => GridRenderers n row cell rowH colH -> EventM n (GridTabularList n row cell rowH colH) ()
- handleGridListEvent :: Ord n => GridRenderers n row cell rowH colH -> Event -> EventM n (GridTabularList n row cell rowH colH) ()
- handleGridListEventVi :: Ord n => GridRenderers n row cell rowH colH -> Event -> EventM n (GridTabularList n row cell rowH colH) ()
- module Brick.Widgets.TabularList.Types
Data types
data GridContents n row cell rowH colH Source #
Functions for getting contents of grid tabular list elements. See List Type Variables.
Instances
Generic (GridContents n row cell rowH colH) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridContents n row cell rowH colH) :: Type -> Type # from :: GridContents n row cell rowH colH -> Rep (GridContents n row cell rowH colH) x # to :: Rep (GridContents n row cell rowH colH) x -> GridContents n row cell rowH colH # | |
type Rep (GridContents n row cell rowH colH) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridContents n row cell rowH colH) = D1 ('MetaData "GridContents" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "GridContents" 'PrefixI 'True) (S1 ('MetaSel ('Just "cell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (row -> ColumnIndex -> Maybe cell)) :*: (S1 ('MetaSel ('Just "rowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (row -> RowIndex -> Maybe rowH))) :*: S1 ('MetaSel ('Just "colHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ColumnIndex -> Maybe colH)))))) |
data GridContext Source #
Context information for grid cells
Instances
Generic GridContext Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridContext :: Type -> Type # from :: GridContext -> Rep GridContext x # to :: Rep GridContext x -> GridContext # | |
Show GridContext Source # | |
Defined in Brick.Widgets.TabularList.Grid showsPrec :: Int -> GridContext -> ShowS # show :: GridContext -> String # showList :: [GridContext] -> ShowS # | |
type Rep GridContext Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridContext = D1 ('MetaData "GridContext" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "GridContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position) :*: S1 ('MetaSel ('Just "col") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position))) |
data GridRenderers n row cell rowH colH Source #
Rendering functions for elements of grid tabular list. See
GridRenderers | |
|
Instances
Sizes for elements of grid tabular list. See List Type Variables.
Instances
Generic (GridSizes rowH) Source # | |
type Rep (GridSizes rowH) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridSizes rowH) = D1 ('MetaData "GridSizes" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "GridSizes" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Width)) :*: (S1 ('MetaSel ('Just "rowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (RowHeaderWidth rowH))) :*: S1 ('MetaSel ('Just "colHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Height))))) |
data GridTabularList n row cell rowH colH Source #
See List Type Variables.
GridTabularList | |
|
Instances
List construction
:: n | The list name (must be unique) |
-> Seq row | The initial list rows |
-> ListItemHeight | |
-> GridSizes rowH | |
-> GridContents n row cell rowH colH | |
-> GridTabularList n row cell rowH colH |
Create a grid tabular list
Rendering
renderGridTabularList Source #
:: (Ord n, Show n) | |
=> GridRenderers n row cell rowH colH | Renderers |
-> ListFocused | |
-> GridTabularList n row cell rowH colH | The list |
-> Widget n |
Render grid tabular list
Column navigation
:: GridTabularList n row cell rowH colH | The list |
-> GridTabularList n row cell rowH colH |
Move to the left by one column.
:: GridTabularList n row cell rowH colH | The list |
-> GridTabularList n row cell rowH colH |
Move to the right by one column.
:: ColumnIndex | |
-> GridTabularList n row cell rowH colH | The list |
-> GridTabularList n row cell rowH colH |
Move to the given column index
:: GridTabularList n row cell rowH colH | The list |
-> GridTabularList n row cell rowH colH |
Move to the first column.
:: GridTabularList n row cell rowH colH | The list |
-> GridTabularList n row cell rowH colH |
Move to the last column.
:: Ord n | |
=> GridRenderers n row cell rowH colH | Renderers |
-> EventM n (GridTabularList n row cell rowH colH) () |
Move to the previous page of columns.
GridRenderers
are needed because if row header renderer doesn't exist, width calculation is affected.
:: Ord n | |
=> GridRenderers n row cell rowH colH | Renderers |
-> EventM n (GridTabularList n row cell rowH colH) () |
Move to the next page of columns.
GridRenderers
are needed because if row header renderer doesn't exist, width calculation is affected.
Event handlers
:: Ord n | |
=> GridRenderers n row cell rowH colH | Renderers |
-> Event | |
-> EventM n (GridTabularList n row cell rowH colH) () |
Handle events for grid tabular list with navigation keys.
It adds the following keyboard shortcuts to handleListEvent
.
- Move to the left by one column (Left arrow key)
- Move to the right by one column (Right arrow key)
- Go to the first column (Ctrl+Home)
- Go to the last column (Ctrl+End)
- Move to the previous page of columns (Ctrl+PageUp)
- Move to the next page of columns (Ctrl+PageDown)
GridRenderers
are needed because if row header renderer doesn't exist, width calculation is affected.
handleGridListEventVi Source #
:: Ord n | |
=> GridRenderers n row cell rowH colH | Renderers |
-> Event | |
-> EventM n (GridTabularList n row cell rowH colH) () |
Handle events for grid tabular list with vim keys.
It adds the following keyboard shortcuts to handleListEventVi
.
- Move to the left by one column (h)
- Move to the right by one column (l)
- Go to the first column (H)
- Go to the last column (L)
- Move to the previous page of columns (Alt+h)
- Move to the next page of columns (Alt+l)
GridRenderers
are needed because if row header renderer doesn't exist, width calculation is affected.