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

Brick.Widgets.TabularList.Mixed

Description

Mixed tabular list is a list with different kinds of rows.

Read Shared Traits of Tabular List Widgets before reading further.

Each row belongs to a row kind which is usually a data constructor of row data type. Because there can be more than one data constructor in row data type, this list is called mixed tabular list. Each row kind can have a different number of columns than another row kind.

Cell by cell navigation is not supported. You can navigate row by row.

Because this list is designed to show every column in the available space, horizontal scrolling is not supported.

Synopsis

Data types

data MixedContents row cell rowH colH Source #

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

Constructors

MixedContents 

Fields

Instances

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

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

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

Methods

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

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

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

Defined in Brick.Widgets.TabularList.Mixed

type Rep (MixedContents row cell rowH colH) = D1 ('MetaData "MixedContents" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "MixedContents" '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 MixedRenderers n row cell rowH colH Source #

Rendering functions for elements of mixed tabular list. See

Constructors

MixedRenderers 

Fields

Instances

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

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

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

Methods

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

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

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

Defined in Brick.Widgets.TabularList.Mixed

type Rep (MixedRenderers n row cell rowH colH) = D1 ('MetaData "MixedRenderers" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "MixedRenderers" 'PrefixI 'True) (S1 ('MetaSel ('Just "drawCell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> Position -> 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 -> ColumnIndex -> Maybe colH -> Widget n))))))

data ColSizes row Source #

Column sizes calculated after row header width is calculated. See List Type Variables.

Constructors

ColSizes 

Fields

  • rowKind :: row -> [Width]

    Widths for each row kind. Use pattern matching to detect the kind of each row. Usually, a row kind is a data constructor of row. The returned widths should be pre-calculated widths. If widths are calculated in this function, width calculation will be repeated at every row. If the function is given pre-calculated widths, width calculation is done only once.

  • colHdr :: Maybe ([Width], Height)

    Widths and height for column headers. Widths and height don't have to be pre-calculated because column headers are only drawn once. Because they are drawn once, any calculation done in this field is also done only once.

Instances

Instances details
Generic (ColSizes row) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (ColSizes row) :: Type -> Type #

Methods

from :: ColSizes row -> Rep (ColSizes row) x #

to :: Rep (ColSizes row) x -> ColSizes row #

type Rep (ColSizes row) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (ColSizes row) = D1 ('MetaData "ColSizes" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "ColSizes" 'PrefixI 'True) (S1 ('MetaSel ('Just "rowKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (row -> [Width])) :*: S1 ('MetaSel ('Just "colHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ([Width], Height)))))

data CalcColSizes row Source #

Function for calculating column sizes. See List Type Variables.

Constructors

AvailWidth (AvailWidth -> ColSizes row)

Calculate sizes with the width available after row header width is calculated.

VisibleRows ([row] -> AvailWidth -> ColSizes row)

Calculate sizes with visible rows and the width available after row header width is calculated.

Instances

Instances details
Generic (CalcColSizes row) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (CalcColSizes row) :: Type -> Type #

Methods

from :: CalcColSizes row -> Rep (CalcColSizes row) x #

to :: Rep (CalcColSizes row) x -> CalcColSizes row #

type Rep (CalcColSizes row) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (CalcColSizes row) = D1 ('MetaData "CalcColSizes" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "AvailWidth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AvailWidth -> ColSizes row))) :+: C1 ('MetaCons "VisibleRows" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ([row] -> AvailWidth -> ColSizes row))))

data MixedSizes row rowH Source #

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

Constructors

MixedSizes 

Fields

Instances

Instances details
Generic (MixedSizes row rowH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (MixedSizes row rowH) :: Type -> Type #

Methods

from :: MixedSizes row rowH -> Rep (MixedSizes row rowH) x #

to :: Rep (MixedSizes row rowH) x -> MixedSizes row rowH #

type Rep (MixedSizes row rowH) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (MixedSizes row rowH) = D1 ('MetaData "MixedSizes" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-0.1.0.2-xtK2tbLVHI135hCs28APH" 'False) (C1 ('MetaCons "MixedSizes" 'PrefixI 'True) (S1 ('MetaSel ('Just "rowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (RowHeaderWidth rowH))) :*: S1 ('MetaSel ('Just "colSizes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CalcColSizes row))))

data MixedTabularList n row cell rowH colH Source #

Constructors

MixedTabularList 

Fields

Instances

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

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

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

Methods

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

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

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

Defined in Brick.Widgets.TabularList.Mixed

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

List construction

mixedTabularList Source #

Arguments

:: n

The name of the list. It must be unique.

-> Seq row

The initial list rows

-> ListItemHeight 
-> MixedSizes row rowH 
-> MixedContents row cell rowH colH 
-> MixedTabularList n row cell rowH colH 

Create a mixed tabular list.

Rendering

renderMixedTabularList Source #

Arguments

:: (Show n, Ord n) 
=> MixedRenderers n row cell rowH colH

Renderers

-> ListFocused 
-> MixedTabularList n row cell rowH colH

The list

-> Widget n 

Render mixed tabular list

Event handlers

handleMixedListEvent :: Ord n => Event -> EventM n (MixedTabularList n row cell rowH colH) () Source #

Handle events for mixed tabular list with navigation keys. This just calls handleListEvent.

handleMixedListEventVi :: Ord n => Event -> EventM n (MixedTabularList n row cell rowH colH) () Source #

Handle events for mixed tabular list with vim keys. This just calls handleListEventVi.

Shared types