Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Extensions |
|
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 MixedRowCtxt = MRowC {}
- newtype MixedColCtxt = MColC {}
- data MixedCtxt = MxdCtxt {
- row :: MixedRowCtxt
- col :: MixedColCtxt
- data MixedColHdr n w = MixedColHdr {
- draw :: ListFocused -> MixedColCtxt -> Widget n
- widths :: w -> [ColWidth]
- height :: ColHdrHeight
- data MixedRenderers n e w = MixedRenderers {
- cell :: ListFocused -> MixedCtxt -> e -> Widget n
- rowHdr :: Maybe (RowHdr n e)
- colHdr :: Maybe (MixedColHdr n w)
- colHdrRowHdr :: Maybe (ColHdrRowHdr n)
- newtype WidthsPerRowKind e w = WsPerRK (AvailWidth -> [e] -> w)
- newtype WidthsPerRow e w = WsPerR (w -> e -> [ColWidth])
- data MixedTabularList n e w = MixedTabularList {
- list :: GenericList n Seq e
- widthsPerRowKind :: WidthsPerRowKind e w
- widthsPerRow :: WidthsPerRow e w
- mixedTabularList :: n -> Seq e -> ListItemHeight -> WidthsPerRowKind e w -> WidthsPerRow e w -> MixedTabularList n e w
- renderMixedTabularList :: (Show n, Ord n) => MixedRenderers n e w -> ListFocused -> MixedTabularList n e w -> Widget n
- handleMixedListEvent :: Ord n => Event -> EventM n (MixedTabularList n e w) ()
- handleMixedListEventVi :: Ord n => Event -> EventM n (MixedTabularList n e w) ()
- module Brick.Widgets.TabularList.Types
Data types
data MixedRowCtxt Source #
Mixed row context
Instances
newtype MixedColCtxt Source #
Mixed column context
Instances
Generic MixedColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep MixedColCtxt :: Type -> Type # from :: MixedColCtxt -> Rep MixedColCtxt x # to :: Rep MixedColCtxt x -> MixedColCtxt # | |
Show MixedColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Mixed showsPrec :: Int -> MixedColCtxt -> ShowS # show :: MixedColCtxt -> String # showList :: [MixedColCtxt] -> ShowS # | |
Eq MixedColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Mixed (==) :: MixedColCtxt -> MixedColCtxt -> Bool # (/=) :: MixedColCtxt -> MixedColCtxt -> Bool # | |
type Rep MixedColCtxt Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep MixedColCtxt = D1 ('MetaData "MixedColCtxt" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.1-2pfa2xpwleVH0maazyIiI3" 'True) (C1 ('MetaCons "MColC" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index))) |
Context for mixed columns
MxdCtxt | |
|
Instances
Generic MixedCtxt Source # | |
Show MixedCtxt Source # | |
Eq MixedCtxt Source # | |
type Rep MixedCtxt Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep MixedCtxt = D1 ('MetaData "MixedCtxt" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.1-2pfa2xpwleVH0maazyIiI3" '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
MixedColHdr | |
|
Instances
Generic (MixedColHdr n w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (MixedColHdr n w) :: Type -> Type # from :: MixedColHdr n w -> Rep (MixedColHdr n w) x # to :: Rep (MixedColHdr n w) x -> MixedColHdr n w # | |
type Rep (MixedColHdr n w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (MixedColHdr n w) = D1 ('MetaData "MixedColHdr" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.1-2pfa2xpwleVH0maazyIiI3" '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
MixedRenderers | |
|
Instances
newtype WidthsPerRowKind e w Source #
Calculate widths per row kind from visible list rows and the width available after row header.
WsPerRK (AvailWidth -> [e] -> w) |
Instances
Generic (WidthsPerRowKind e w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (WidthsPerRowKind e w) :: Type -> Type # from :: WidthsPerRowKind e w -> Rep (WidthsPerRowKind e w) x # to :: Rep (WidthsPerRowKind e w) x -> WidthsPerRowKind e w # | |
type Rep (WidthsPerRowKind e w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (WidthsPerRowKind e w) = D1 ('MetaData "WidthsPerRowKind" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.1-2pfa2xpwleVH0maazyIiI3" '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.
Instances
Generic (WidthsPerRow e w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (WidthsPerRow e w) :: Type -> Type # from :: WidthsPerRow e w -> Rep (WidthsPerRow e w) x # to :: Rep (WidthsPerRow e w) x -> WidthsPerRow e w # | |
type Rep (WidthsPerRow e w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (WidthsPerRow e w) = D1 ('MetaData "WidthsPerRow" "Brick.Widgets.TabularList.Mixed" "brick-tabular-list-2.2.0.1-2pfa2xpwleVH0maazyIiI3" 'True) (C1 ('MetaCons "WsPerR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> e -> [ColWidth])))) |
data MixedTabularList n e w Source #
MixedTabularList | |
|
Instances
Generic (MixedTabularList n e w) Source # | |
Defined in Brick.Widgets.TabularList.Mixed type Rep (MixedTabularList n e w) :: Type -> Type # 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 # | |
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.1-2pfa2xpwleVH0maazyIiI3" '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
:: 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 #
:: (Show n, Ord n) | |
=> MixedRenderers n e w | Renderers |
-> ListFocused | |
-> MixedTabularList n e w | The list |
-> Widget n |
Render mixed tabular list.
Event handlers
:: 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 #
:: Ord n | |
=> Event | Event |
-> EventM n (MixedTabularList n e w) () |
Handle events for mixed tabular list with vim keys. This just calls handleListEventVi
.