Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Extensions |
|
Grid tabular list is a uniform grid that supports cell-by-cell navigation.
Because this list is designed to show arbitrary numbers 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 GridRowCtxt = GRowC {}
- data GridColCtxt = GColC {}
- data GridCtxt = GrdCtxt {
- row :: GridRowCtxt
- col :: GridColCtxt
- data GridColHdr n = GridColHdr {
- draw :: ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
- height :: ColHdrHeight
- data GridRenderers n e = GridRenderers {
- cell :: ListFocused -> WidthDeficit -> GridCtxt -> e -> Widget n
- rowHdr :: Maybe (RowHdr n e)
- colHdr :: Maybe (GridColHdr n)
- colHdrRowHdr :: Maybe (ColHdrRowHdr n)
- data GridTabularList n e = GridTabularList {
- list :: GenericList n Seq e
- widths :: Seq ColWidth
- currentColumn :: Index
- gridTabularList :: n -> Seq e -> ListItemHeight -> Seq ColWidth -> GridTabularList n e
- renderGridTabularList :: (Ord n, Show n) => GridRenderers n e -> ListFocused -> GridTabularList n e -> Widget n
- gridMoveLeft :: GridTabularList n e -> GridTabularList n e
- gridMoveRight :: GridTabularList n e -> GridTabularList n e
- gridMoveTo :: Index -> GridTabularList n e -> GridTabularList n e
- gridMoveToBeginning :: GridTabularList n e -> GridTabularList n e
- gridMoveToEnd :: GridTabularList n e -> GridTabularList n e
- gridMovePageUp :: Ord n => GridRenderers n e -> EventM n (GridTabularList n e) ()
- gridMovePageDown :: Ord n => GridRenderers n e -> EventM n (GridTabularList n e) ()
- handleGridListEvent :: Ord n => GridRenderers n e -> Event -> EventM n (GridTabularList n e) ()
- handleGridListEventVi :: Ord n => GridRenderers n e -> Event -> EventM n (GridTabularList n e) ()
- module Brick.Widgets.TabularList.Types
Data types
data GridRowCtxt Source #
Grid row context
Instances
Generic GridRowCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridRowCtxt :: Type -> Type # from :: GridRowCtxt -> Rep GridRowCtxt x # to :: Rep GridRowCtxt x -> GridRowCtxt # | |
Show GridRowCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid showsPrec :: Int -> GridRowCtxt -> ShowS # show :: GridRowCtxt -> String # showList :: [GridRowCtxt] -> ShowS # | |
Eq GridRowCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid (==) :: GridRowCtxt -> GridRowCtxt -> Bool # (/=) :: GridRowCtxt -> GridRowCtxt -> Bool # | |
type Rep GridRowCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridRowCtxt = D1 ('MetaData "GridRowCtxt" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.6-AiZXcnb49SU5Sm94CE44Dq" 'False) (C1 ('MetaCons "GRowC" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index) :*: S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Selected))) |
data GridColCtxt Source #
Grid column context
Instances
Generic GridColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridColCtxt :: Type -> Type # from :: GridColCtxt -> Rep GridColCtxt x # to :: Rep GridColCtxt x -> GridColCtxt # | |
Show GridColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid showsPrec :: Int -> GridColCtxt -> ShowS # show :: GridColCtxt -> String # showList :: [GridColCtxt] -> ShowS # | |
Eq GridColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid (==) :: GridColCtxt -> GridColCtxt -> Bool # (/=) :: GridColCtxt -> GridColCtxt -> Bool # | |
type Rep GridColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridColCtxt = D1 ('MetaData "GridColCtxt" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.6-AiZXcnb49SU5Sm94CE44Dq" 'False) (C1 ('MetaCons "GColC" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index) :*: S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Selected))) |
Context for grid cells
GrdCtxt | |
|
Instances
Generic GridCtxt Source # | |
Show GridCtxt Source # | |
Eq GridCtxt Source # | |
type Rep GridCtxt Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep GridCtxt = D1 ('MetaData "GridCtxt" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.6-AiZXcnb49SU5Sm94CE44Dq" 'False) (C1 ('MetaCons "GrdCtxt" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GridRowCtxt) :*: S1 ('MetaSel ('Just "col") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GridColCtxt))) |
data GridColHdr n Source #
Grid column header
GridColHdr | |
|
Instances
Generic (GridColHdr n) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridColHdr n) :: Type -> Type # from :: GridColHdr n -> Rep (GridColHdr n) x # to :: Rep (GridColHdr n) x -> GridColHdr n # | |
type Rep (GridColHdr n) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridColHdr n) = D1 ('MetaData "GridColHdr" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.6-AiZXcnb49SU5Sm94CE44Dq" 'False) (C1 ('MetaCons "GridColHdr" 'PrefixI 'True) (S1 ('MetaSel ('Just "draw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> WidthDeficit -> GridColCtxt -> Widget n)) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColHdrHeight))) |
data GridRenderers n e Source #
Rendering functions for components of grid tabular list
GridRenderers | |
|
Instances
data GridTabularList n e Source #
GridTabularList | |
|
Instances
Generic (GridTabularList n e) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridTabularList n e) :: Type -> Type # from :: GridTabularList n e -> Rep (GridTabularList n e) x # to :: Rep (GridTabularList n e) x -> GridTabularList n e # | |
type Rep (GridTabularList n e) Source # | |
Defined in Brick.Widgets.TabularList.Grid type Rep (GridTabularList n e) = D1 ('MetaData "GridTabularList" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.6-AiZXcnb49SU5Sm94CE44Dq" 'False) (C1 ('MetaCons "GridTabularList" 'PrefixI 'True) (S1 ('MetaSel ('Just "list") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenericList n Seq e)) :*: (S1 ('MetaSel ('Just "widths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq ColWidth)) :*: S1 ('MetaSel ('Just "currentColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index)))) |
List construction
:: n | The list name (must be unique) |
-> Seq e | The initial list elements |
-> ListItemHeight | |
-> Seq ColWidth | |
-> GridTabularList n e |
Create a grid tabular list
Rendering
renderGridTabularList Source #
:: (Ord n, Show n) | |
=> GridRenderers n e | |
-> ListFocused | |
-> GridTabularList n e | The list |
-> Widget n |
Render grid tabular list
Column navigation
:: GridTabularList n e | The list |
-> GridTabularList n e |
Move to the left by one column.
:: GridTabularList n e | The list |
-> GridTabularList n e |
Move to the right by one column.
:: Index | |
-> GridTabularList n e | The list |
-> GridTabularList n e |
Move to the given column index
:: GridTabularList n e | The list |
-> GridTabularList n e |
Move to the first column.
:: Ord n | |
=> GridRenderers n e | Renderers |
-> EventM n (GridTabularList n e) () |
Move to the previous page of columns.
GridRenderers
are needed because if row header doesn't exist, width calculation is affected.
:: Ord n | |
=> GridRenderers n e | Renderers |
-> EventM n (GridTabularList n e) () |
Move to the next page of columns.
GridRenderers
are needed because if row header doesn't exist, width calculation is affected.
Event handlers
:: Ord n | |
=> GridRenderers n e | Renderers |
-> Event | |
-> EventM n (GridTabularList n e) () |
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 doesn't exist, width calculation is affected.
handleGridListEventVi Source #
:: Ord n | |
=> GridRenderers n e | Renderers |
-> Event | |
-> EventM n (GridTabularList n e) () |
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 doesn't exist, width calculation is affected.