brick-tabular-list-2.2.0.10: Tabular list widgets for brick.
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • DeriveGeneric
  • ExistentialQuantification
  • GeneralizedNewtypeDeriving
  • ExplicitForAll

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

Tabular dimensions

newtype RowHdrWidth Source #

Width for row header

Constructors

RowHdrW Int 

Instances

Instances details
Generic RowHdrWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep RowHdrWidth :: Type -> Type #

Show RowHdrWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq RowHdrWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep RowHdrWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep RowHdrWidth = D1 ('MetaData "RowHdrWidth" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "RowHdrW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype ColWidth Source #

Width of a column header or a row column

Constructors

ColW Int 

Instances

Instances details
Generic ColWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep ColWidth :: Type -> Type #

Methods

from :: ColWidth -> Rep ColWidth x #

to :: Rep ColWidth x -> ColWidth #

Show ColWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq ColWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ColWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ColWidth = D1 ('MetaData "ColWidth" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "ColW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype ColHdrHeight Source #

Height for column headers and column header row header

Constructors

ColHdrH Int 

Instances

Instances details
Generic ColHdrHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep ColHdrHeight :: Type -> Type #

Show ColHdrHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq ColHdrHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ColHdrHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ColHdrHeight = D1 ('MetaData "ColHdrHeight" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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.

Constructors

LstItmH Int 

Instances

Instances details
Generic ListItemHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep ListItemHeight :: Type -> Type #

Show ListItemHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq ListItemHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ListItemHeight Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ListItemHeight = D1 ('MetaData "ListItemHeight" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "LstItmH" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Shared rendering context

newtype Index Source #

Index of a tabular list component among the same kind of components

Constructors

Ix Int 

Instances

Instances details
Enum Index Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Generic Index Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep Index :: Type -> Type #

Methods

from :: Index -> Rep Index x #

to :: Rep Index x -> Index #

Show Index Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Eq Index Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Methods

(==) :: Index -> Index -> Bool #

(/=) :: Index -> Index -> Bool #

type Rep Index Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep Index = D1 ('MetaData "Index" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "Ix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype AvailWidth Source #

Available width

Constructors

AvlW Int 

Instances

Instances details
Generic AvailWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep AvailWidth :: Type -> Type #

Show AvailWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq AvailWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep AvailWidth Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep AvailWidth = D1 ('MetaData "AvailWidth" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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

Constructors

WdthD Int 

Instances

Instances details
Generic WidthDeficit Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep WidthDeficit :: Type -> Type #

Show WidthDeficit Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq WidthDeficit Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep WidthDeficit Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep WidthDeficit = D1 ('MetaData "WidthDeficit" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" '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

Constructors

LstFcs Bool 

Instances

Instances details
Generic ListFocused Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep ListFocused :: Type -> Type #

Show ListFocused Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq ListFocused Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ListFocused Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep ListFocused = D1 ('MetaData "ListFocused" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "LstFcs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype Selected Source #

Whether a tabular list component is selected

Constructors

Sel Bool 

Instances

Instances details
Generic Selected Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep Selected :: Type -> Type #

Methods

from :: Selected -> Rep Selected x #

to :: Rep Selected x -> Selected #

Show Selected Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq Selected Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep Selected Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep Selected = D1 ('MetaData "Selected" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "Sel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Row header

newtype RowHdrCtxt Source #

Row header context

Constructors

RowHdrCtxt 

Fields

Instances

Instances details
Generic RowHdrCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Associated Types

type Rep RowHdrCtxt :: Type -> Type #

Show RowHdrCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

Eq RowHdrCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep RowHdrCtxt Source # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep RowHdrCtxt = D1 ('MetaData "RowHdrCtxt" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "RowHdrCtxt" 'PrefixI 'True) (S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Selected)))

data RowHdr n e Source #

Row header

Type Variables

  • r - the type of row header

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.

Instances

Instances details
Generic (ColHdrRowHdr n) Source # 
Instance details

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 # 
Instance details

Defined in Brick.Widgets.TabularList.Types

type Rep (ColHdrRowHdr n) = D1 ('MetaData "ColHdrRowHdr" "Brick.Widgets.TabularList.Types" "brick-tabular-list-2.2.0.10-1F10XiequAjJHoOSDwgTaa" 'True) (C1 ('MetaCons "ColHdrRowHdr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListFocused -> WidthDeficit -> Widget n))))