brick-tabular-list-2.2.0.10: Tabular list widgets for brick.
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • DisambiguateRecordFields
  • NamedFieldPuns
  • DeriveGeneric
  • LambdaCase
  • DuplicateRecordFields
  • OverloadedLabels
  • TypeApplications

Brick.Widgets.TabularList.Grid

Description

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 types

data GridRowCtxt Source #

Grid row context

Constructors

GRowC 

Fields

Instances

Instances details
Generic GridRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep GridRowCtxt :: Type -> Type #

Show GridRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Eq GridRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridRowCtxt = D1 ('MetaData "GridRowCtxt" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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

Constructors

GColC 

Fields

Instances

Instances details
Generic GridColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep GridColCtxt :: Type -> Type #

Show GridColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Eq GridColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridColCtxt = D1 ('MetaData "GridColCtxt" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'False) (C1 ('MetaCons "GColC" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index) :*: S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Selected)))

data GridCtxt Source #

Context for grid cells

Constructors

GrdCtxt 

Instances

Instances details
Generic GridCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep GridCtxt :: Type -> Type #

Methods

from :: GridCtxt -> Rep GridCtxt x #

to :: Rep GridCtxt x -> GridCtxt #

Show GridCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Eq GridCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridCtxt = D1 ('MetaData "GridCtxt" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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

Instances

Instances details
Generic (GridColHdr n) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridColHdr n) :: Type -> Type #

Methods

from :: GridColHdr n -> Rep (GridColHdr n) x #

to :: Rep (GridColHdr n) x -> GridColHdr n #

type Rep (GridColHdr n) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep (GridColHdr n) = D1 ('MetaData "GridColHdr" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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

Instances

Instances details
Generic (GridRenderers n e) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridRenderers n e) :: Type -> Type #

Methods

from :: GridRenderers n e -> Rep (GridRenderers n e) x #

to :: Rep (GridRenderers n e) x -> GridRenderers n e #

type Rep (GridRenderers n e) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep (GridRenderers n e) = D1 ('MetaData "GridRenderers" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'False) (C1 ('MetaCons "GridRenderers" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> WidthDeficit -> GridCtxt -> e -> Widget n)) :*: S1 ('MetaSel ('Just "rowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (RowHdr n e)))) :*: (S1 ('MetaSel ('Just "colHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (GridColHdr n))) :*: S1 ('MetaSel ('Just "colHdrRowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ColHdrRowHdr n))))))

data GridTabularList n e Source #

Constructors

GridTabularList 

Fields

Instances

Instances details
Generic (GridTabularList n e) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridTabularList n e) :: Type -> Type #

Methods

from :: GridTabularList n e -> Rep (GridTabularList n e) x #

to :: Rep (GridTabularList n e) x -> GridTabularList n e #

type Rep (GridTabularList n e) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep (GridTabularList n e) = D1 ('MetaData "GridTabularList" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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

gridTabularList Source #

Arguments

:: 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 #

Arguments

:: (Ord n, Show n) 
=> GridRenderers n e 
-> ListFocused 
-> GridTabularList n e

The list

-> Widget n 

Render grid tabular list

Column navigation

gridMoveLeft Source #

Arguments

:: GridTabularList n e

The list

-> GridTabularList n e 

Move to the left by one column.

gridMoveRight Source #

Arguments

:: GridTabularList n e

The list

-> GridTabularList n e 

Move to the right by one column.

gridMoveTo Source #

Arguments

:: Index 
-> GridTabularList n e

The list

-> GridTabularList n e 

Move to the given column index

gridMoveToBeginning Source #

Arguments

:: GridTabularList n e

The list

-> GridTabularList n e 

Move to the first column.

gridMoveToEnd Source #

Arguments

:: GridTabularList n e

The list

-> GridTabularList n e 

Move to the last column.

gridMovePageUp Source #

Arguments

:: 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.

gridMovePageDown Source #

Arguments

:: 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

handleGridListEvent Source #

Arguments

:: 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 #

Arguments

:: 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.

Shared types