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

Brick.Widgets.TabularList.Mixed

Description

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

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 MixedRowCtxt Source #

Mixed row context

Constructors

MRowC 

Fields

Instances

Instances details
Generic MixedRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep MixedRowCtxt :: Type -> Type #

Show MixedRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Eq MixedRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep MixedRowCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

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

newtype MixedColCtxt Source #

Mixed column context

Constructors

MColC 

Fields

Instances

Instances details
Generic MixedColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep MixedColCtxt :: Type -> Type #

Show MixedColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Eq MixedColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep MixedColCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep MixedColCtxt = D1 ('MetaData "MixedColCtxt" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "MColC" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index)))

data MixedCtxt Source #

Context for mixed columns

Constructors

MxdCtxt 

Instances

Instances details
Generic MixedCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep MixedCtxt :: Type -> Type #

Show MixedCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Eq MixedCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep MixedCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep MixedCtxt = D1 ('MetaData "MixedCtxt" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'False) (C1 ('MetaCons "MxdCtxt" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedRowCtxt) :*: S1 ('MetaSel ('Just "col") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedColCtxt)))

data MixedColHdr n w Source #

Mixed column header

Constructors

MixedColHdr 

Fields

Instances

Instances details
Generic (MixedColHdr n w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (MixedColHdr n w) :: Type -> Type #

Methods

from :: MixedColHdr n w -> Rep (MixedColHdr n w) x #

to :: Rep (MixedColHdr n w) x -> MixedColHdr n w #

type Rep (MixedColHdr n w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (MixedColHdr n w) = D1 ('MetaData "MixedColHdr" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'False) (C1 ('MetaCons "MixedColHdr" 'PrefixI 'True) (S1 ('MetaSel ('Just "draw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> MixedColCtxt -> Widget n)) :*: (S1 ('MetaSel ('Just "widths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> [ColWidth])) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColHdrHeight))))

data MixedRenderers n e w Source #

Rendering functions for components of mixed tabular list

Constructors

MixedRenderers 

Instances

Instances details
Generic (MixedRenderers n e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (MixedRenderers n e w) :: Type -> Type #

Methods

from :: MixedRenderers n e w -> Rep (MixedRenderers n e w) x #

to :: Rep (MixedRenderers n e w) x -> MixedRenderers n e w #

type Rep (MixedRenderers n e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

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

newtype WidthsPerRowKind e w Source #

Calculate widths per row kind from visible list rows and the width available after row header.

Constructors

WsPerRK (AvailWidth -> [e] -> w) 

Instances

Instances details
Generic (WidthsPerRowKind e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (WidthsPerRowKind e w) :: Type -> Type #

type Rep (WidthsPerRowKind e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (WidthsPerRowKind e w) = D1 ('MetaData "WidthsPerRowKind" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "WsPerRK" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AvailWidth -> [e] -> w))))

newtype WidthsPerRow e w Source #

It is a function to get widths for each row. Use pattern matching to detect the kind of each row. Usually, a row kind is a data constructor of row data type.

Constructors

WsPerR (w -> e -> [ColWidth]) 

Instances

Instances details
Generic (WidthsPerRow e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (WidthsPerRow e w) :: Type -> Type #

Methods

from :: WidthsPerRow e w -> Rep (WidthsPerRow e w) x #

to :: Rep (WidthsPerRow e w) x -> WidthsPerRow e w #

type Rep (WidthsPerRow e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (WidthsPerRow e w) = D1 ('MetaData "WidthsPerRow" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "WsPerR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> e -> [ColWidth]))))

data MixedTabularList n e w Source #

Constructors

MixedTabularList 

Fields

Instances

Instances details
Generic (MixedTabularList n e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

type Rep (MixedTabularList n e w) :: Type -> Type #

Methods

from :: MixedTabularList n e w -> Rep (MixedTabularList n e w) x #

to :: Rep (MixedTabularList n e w) x -> MixedTabularList n e w #

type Rep (MixedTabularList n e w) Source # 
Instance details

Defined in Brick.Widgets.TabularList.Mixed

type Rep (MixedTabularList n e w) = D1 ('MetaData "MixedTabularList" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'False) (C1 ('MetaCons "MixedTabularList" 'PrefixI 'True) (S1 ('MetaSel ('Just "list") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenericList n Seq e)) :*: (S1 ('MetaSel ('Just "widthsPerRowKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (WidthsPerRowKind e w)) :*: S1 ('MetaSel ('Just "widthsPerRow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (WidthsPerRow e w)))))

List construction

mixedTabularList Source #

Arguments

:: n

The name of the list. It must be unique.

-> Seq e

The initial list elements

-> ListItemHeight 
-> WidthsPerRowKind e w 
-> WidthsPerRow e w 
-> MixedTabularList n e w 

Create a mixed tabular list.

Rendering

renderMixedTabularList Source #

Arguments

:: (Show n, Ord n) 
=> MixedRenderers n e w

Renderers

-> ListFocused 
-> MixedTabularList n e w

The list

-> Widget n 

Render mixed tabular list.

Event handlers

handleMixedListEvent Source #

Arguments

:: Ord n 
=> Event

Event

-> EventM n (MixedTabularList n e w) () 

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

handleMixedListEventVi Source #

Arguments

:: Ord n 
=> Event

Event

-> EventM n (MixedTabularList n e w) () 

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

Shared types