brick-tabular-list-0.1.0.2: Tabular list widgets for brick.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brick.Widgets.TabularList.Grid

Description

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 types

data GridContents n row cell rowH colH Source #

Functions for getting contents of grid tabular list elements. See List Type Variables.

Constructors

GridContents 

Fields

Instances

Instances details
Generic (GridContents n row cell rowH colH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridContents n row cell rowH colH) :: Type -> Type #

Methods

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 # 
Instance details

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

Constructors

GridContext 

Fields

Instances

Instances details
Generic GridContext Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep GridContext :: Type -> Type #

Show GridContext Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep GridContext Source # 
Instance details

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

Constructors

GridRenderers 

Fields

Instances

Instances details
Generic (GridRenderers n row cell rowH colH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridRenderers n row cell rowH colH) :: Type -> Type #

Methods

from :: GridRenderers n row cell rowH colH -> Rep (GridRenderers n row cell rowH colH) x #

to :: Rep (GridRenderers n row cell rowH colH) x -> GridRenderers n row cell rowH colH #

type Rep (GridRenderers n row cell rowH colH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep (GridRenderers n row cell rowH colH) = D1 ('MetaData "GridRenderers" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "GridRenderers" 'PrefixI 'True) (S1 ('MetaSel ('Just "drawCell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> WidthDeficit -> GridContext -> row -> Maybe cell -> Widget n)) :*: (S1 ('MetaSel ('Just "drawRowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ListFocused -> WidthDeficit -> Position -> row -> Maybe rowH -> Widget n))) :*: S1 ('MetaSel ('Just "drawColHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ListFocused -> WidthDeficit -> Position -> Maybe colH -> Widget n))))))

data GridSizes rowH Source #

Sizes for elements of grid tabular list. See List Type Variables.

Constructors

GridSizes 

Fields

Instances

Instances details
Generic (GridSizes rowH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridSizes rowH) :: Type -> Type #

Methods

from :: GridSizes rowH -> Rep (GridSizes rowH) x #

to :: Rep (GridSizes rowH) x -> GridSizes rowH #

type Rep (GridSizes rowH) Source # 
Instance details

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 #

Constructors

GridTabularList 

Fields

Instances

Instances details
Generic (GridTabularList n row cell rowH colH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

Associated Types

type Rep (GridTabularList n row cell rowH colH) :: Type -> Type #

Methods

from :: GridTabularList n row cell rowH colH -> Rep (GridTabularList n row cell rowH colH) x #

to :: Rep (GridTabularList n row cell rowH colH) x -> GridTabularList n row cell rowH colH #

type Rep (GridTabularList n row cell rowH colH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Grid

type Rep (GridTabularList n row cell rowH colH) = D1 ('MetaData "GridTabularList" "Brick.Widgets.TabularList.Grid" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "GridTabularList" 'PrefixI 'True) ((S1 ('MetaSel ('Just "list") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenericList n Seq row)) :*: S1 ('MetaSel ('Just "sizes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GridSizes rowH))) :*: (S1 ('MetaSel ('Just "contents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GridContents n row cell rowH colH)) :*: S1 ('MetaSel ('Just "currentColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColumnIndex))))

List construction

gridTabularList Source #

Arguments

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

Arguments

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

gridMoveLeft Source #

Arguments

:: GridTabularList n row cell rowH colH

The list

-> GridTabularList n row cell rowH colH 

Move to the left by one column.

gridMoveRight Source #

Arguments

:: GridTabularList n row cell rowH colH

The list

-> GridTabularList n row cell rowH colH 

Move to the right by one column.

gridMoveTo Source #

Arguments

:: ColumnIndex 
-> GridTabularList n row cell rowH colH

The list

-> GridTabularList n row cell rowH colH 

Move to the given column index

gridMoveToBeginning Source #

Arguments

:: GridTabularList n row cell rowH colH

The list

-> GridTabularList n row cell rowH colH 

Move to the first column.

gridMoveToEnd Source #

Arguments

:: GridTabularList n row cell rowH colH

The list

-> GridTabularList n row cell rowH colH 

Move to the last column.

gridMovePageUp Source #

Arguments

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

gridMovePageDown Source #

Arguments

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

handleGridListEvent Source #

Arguments

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

Arguments

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

Shared types