Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Extensions |
|
Brick.Widgets.TabularList.Types
Description
Types shared by tabular list widgets.
You don't have to import this module because modules for tabular list widgets re-export this module.
Synopsis
- newtype RowHdrWidth = RowHdrW Int
- newtype ColWidth = ColW Int
- newtype ColHdrHeight = ColHdrH Int
- newtype ListItemHeight = LstItmH Int
- newtype Index = Ix Int
- newtype AvailWidth = AvlW Int
- newtype WidthDeficit = WdthD Int
- newtype ListFocused = LstFcs Bool
- newtype Selected = Sel Bool
- newtype RowHdrCtxt = RowHdrCtxt {}
- data RowHdr n e = forall r.RowHdr {
- draw :: ListFocused -> WidthDeficit -> RowHdrCtxt -> r -> Widget n
- width :: AvailWidth -> [r] -> RowHdrWidth
- toRH :: e -> Index -> r
- newtype ColHdrRowHdr n = ColHdrRowHdr (ListFocused -> WidthDeficit -> Widget n)
Tabular dimensions
newtype RowHdrWidth Source #
Width for row header
Instances
Generic RowHdrWidth Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep RowHdrWidth :: Type -> Type # | |
Show RowHdrWidth Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> RowHdrWidth -> ShowS # show :: RowHdrWidth -> String # showList :: [RowHdrWidth] -> ShowS # | |
Eq RowHdrWidth Source # | |
Defined in Brick.Widgets.TabularList.Types | |
type Rep RowHdrWidth Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep RowHdrWidth = D1 ('MetaData "RowHdrWidth" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "RowHdrW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Width of a column header or a row column
newtype ColHdrHeight Source #
Height for column headers and column header row header
Instances
Generic ColHdrHeight Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep ColHdrHeight :: Type -> Type # | |
Show ColHdrHeight Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> ColHdrHeight -> ShowS # show :: ColHdrHeight -> String # showList :: [ColHdrHeight] -> ShowS # | |
Eq ColHdrHeight Source # | |
Defined in Brick.Widgets.TabularList.Types | |
type Rep ColHdrHeight Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep ColHdrHeight = D1 ('MetaData "ColHdrHeight" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "ColHdrH" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
newtype ListItemHeight Source #
The fixed height for row headers and row columns.
If the height of row headers or row columns is not this height, then the list will look broken.
Instances
Generic ListItemHeight Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep ListItemHeight :: Type -> Type # Methods from :: ListItemHeight -> Rep ListItemHeight x # to :: Rep ListItemHeight x -> ListItemHeight # | |
Show ListItemHeight Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> ListItemHeight -> ShowS # show :: ListItemHeight -> String # showList :: [ListItemHeight] -> ShowS # | |
Eq ListItemHeight Source # | |
Defined in Brick.Widgets.TabularList.Types Methods (==) :: ListItemHeight -> ListItemHeight -> Bool # (/=) :: ListItemHeight -> ListItemHeight -> Bool # | |
type Rep ListItemHeight Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep ListItemHeight = D1 ('MetaData "ListItemHeight" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "LstItmH" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Shared rendering context
Index of a tabular list component among the same kind of components
newtype AvailWidth Source #
Available width
Instances
Generic AvailWidth Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep AvailWidth :: Type -> Type # | |
Show AvailWidth Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> AvailWidth -> ShowS # show :: AvailWidth -> String # showList :: [AvailWidth] -> ShowS # | |
Eq AvailWidth Source # | |
Defined in Brick.Widgets.TabularList.Types | |
type Rep AvailWidth Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep AvailWidth = D1 ('MetaData "AvailWidth" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "AvlW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
newtype WidthDeficit Source #
widthDeficit = max 0 $ desiredColumnWidth - availableWidth
It is positive when a column is shrunk to the available width.
If you use fixed paddings to introduce gaps between columns, you may want to remove fixed paddings when width deficit is positive because a column is not preceded or followed by other columns and its width is shrunk.
The following examples show how to remove gaps between columns when width deficit is positive.
padRight
(Pad
$ if widthDeficit > 0 then 0 else 1) $padLeft
Max
content
padLeft
(Pad
$ if widthDeficit > 0 then 0 else 1) $hCenter
content
Instances
Generic WidthDeficit Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep WidthDeficit :: Type -> Type # | |
Show WidthDeficit Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> WidthDeficit -> ShowS # show :: WidthDeficit -> String # showList :: [WidthDeficit] -> ShowS # | |
Eq WidthDeficit Source # | |
Defined in Brick.Widgets.TabularList.Types | |
type Rep WidthDeficit Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep WidthDeficit = D1 ('MetaData "WidthDeficit" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "WdthD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
newtype ListFocused Source #
Whether the list is focused in an application
Instances
Generic ListFocused Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep ListFocused :: Type -> Type # | |
Show ListFocused Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> ListFocused -> ShowS # show :: ListFocused -> String # showList :: [ListFocused] -> ShowS # | |
Eq ListFocused Source # | |
Defined in Brick.Widgets.TabularList.Types | |
type Rep ListFocused Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep ListFocused = D1 ('MetaData "ListFocused" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "LstFcs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) |
Whether a tabular list component is selected
Row header
newtype RowHdrCtxt Source #
Row header context
Constructors
RowHdrCtxt | |
Instances
Generic RowHdrCtxt Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep RowHdrCtxt :: Type -> Type # | |
Show RowHdrCtxt Source # | |
Defined in Brick.Widgets.TabularList.Types Methods showsPrec :: Int -> RowHdrCtxt -> ShowS # show :: RowHdrCtxt -> String # showList :: [RowHdrCtxt] -> ShowS # | |
Eq RowHdrCtxt Source # | |
Defined in Brick.Widgets.TabularList.Types | |
type Rep RowHdrCtxt Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep RowHdrCtxt = D1 ('MetaData "RowHdrCtxt" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "RowHdrCtxt" 'PrefixI 'True) (S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Selected))) |
Constructors
forall r. RowHdr | |
Fields
|
newtype ColHdrRowHdr n Source #
The renderer for column header row header.
If row headers and column headers exist and ColHdrRowHdr
doesn't exist, then column header row header is filled
with empty space. ColHdrRowHdr
merely allows you to customize column header row header.
Constructors
ColHdrRowHdr (ListFocused -> WidthDeficit -> Widget n) |
Instances
Generic (ColHdrRowHdr n) Source # | |
Defined in Brick.Widgets.TabularList.Types Associated Types type Rep (ColHdrRowHdr n) :: Type -> Type # Methods from :: ColHdrRowHdr n -> Rep (ColHdrRowHdr n) x # to :: Rep (ColHdrRowHdr n) x -> ColHdrRowHdr n # | |
type Rep (ColHdrRowHdr n) Source # | |
Defined in Brick.Widgets.TabularList.Types type Rep (ColHdrRowHdr n) = D1 ('MetaData "ColHdrRowHdr" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.16-AzxUe9vlOkY71SH49qQOhd" 'True) (C1 ('MetaCons "ColHdrRowHdr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> WidthDeficit -> Widget n)))) |