brick-tabular-list-1.0.0.1: Tabular list widgets for brick.
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • DisambiguateRecordFields
  • RecordPuns
  • 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 MixedContext Source #

Context for mixed columns

Constructors

MixedContext 

Fields

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-1.0.0.1-En9LBR6wT7ZEawsXqx3s8t" 'False) (C1 ('MetaCons "MixedColHdr" 'PrefixI 'True) (S1 ('MetaSel ('Just "draw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> Index -> Widget n)) :*: (S1 ('MetaSel ('Just "widths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> [Width])) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Height))))

data MixedRenderers n e w r Source #

Rendering functions for components of mixed tabular list

Instances

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

Defined in Brick.Widgets.TabularList.Mixed

Associated Types

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

Methods

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

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

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

Defined in Brick.Widgets.TabularList.Mixed

type Rep (MixedRenderers n e w r) = D1 ('MetaData "MixedRenderers" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-1.0.0.1-En9LBR6wT7ZEawsXqx3s8t" 'False) (C1 ('MetaCons "MixedRenderers" 'PrefixI 'True) ((S1 ('MetaSel ('Just "drawCell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> MixedContext -> e -> Widget n)) :*: S1 ('MetaSel ('Just "rowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (RowHdr n e r)))) :*: (S1 ('MetaSel ('Just "colHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (MixedColHdr n w))) :*: S1 ('MetaSel ('Just "drawColHdrRowHdr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DrawColHdrRowHdr n)))))

type CalcWidthsPerRowKind e w = AvailWidth -> [e] -> w Source #

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

type WidthsPerRow e w = w -> e -> [Width] 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.

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-1.0.0.1-En9LBR6wT7ZEawsXqx3s8t" 'False) (C1 ('MetaCons "MixedTabularList" 'PrefixI 'True) (S1 ('MetaSel ('Just "list") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenericList n Seq e)) :*: (S1 ('MetaSel ('Just "calcWidthsPerRowKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CalcWidthsPerRowKind 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 
-> CalcWidthsPerRowKind 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 r

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