{-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NoFieldSelectors #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE ExistentialQuantification #-} -- | Types shared by tabular list widgets. -- -- You don't have to import this module because modules for tabular list widgets re-export this module. module Brick.Widgets.TabularList.Types ( -- * Tabular dimensions RowHdrWidth(..) , ColWidth(..) , ColHdrHeight(..) , ListItemHeight(..) -- * Shared rendering context , Index(..) , AvailWidth(..) , WidthDeficit(..) , ListFocused(..) , Selected(..) -- * Row header , RowHdrCtxt(..) , RowHdr(..) , ColHdrRowHdr(..) ) where -- base import GHC.Generics (Generic) -- brick import Brick.Types import Brick.Widgets.Center import Brick.Widgets.Core -- | Index of a tabular list component among the same kind of components newtype Index = Ix Int deriving (Enum, Eq, Generic, Show) -- | Width for row header newtype RowHdrWidth = RowHdrW Int deriving (Eq, Generic, Show) -- | Width of a column header or a row column newtype ColWidth = ColW Int deriving (Eq, Generic, Show) -- | Height for column headers and column header row header newtype ColHdrHeight = ColHdrH Int deriving (Eq, Generic, Show) -- | 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. newtype ListItemHeight = LstItmH Int deriving (Eq, Generic, Show) -- | Available width newtype AvailWidth = AvlW Int deriving (Eq, Generic, Show) -- | > 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 -- @ newtype WidthDeficit = WdthD Int deriving (Eq, Generic, Show) -- | Whether the list is focused in an application newtype ListFocused = LstFcs Bool deriving (Eq, Generic, Show) -- | Whether a tabular list component is selected newtype Selected = Sel Bool deriving (Eq, Generic, Show) -- | Row header context newtype RowHdrCtxt = RowHdrCtxt { selected :: Selected } deriving (Eq, Generic, Show) -- | Row header -- -- * [Type Variables]("Brick.Widgets.TabularList#g:TypeVariables") -- * [Rendering]("Brick.Widgets.TabularList#g:Rendering") -- -- Type Variables -- -- * r - the type of row header data RowHdr n e = forall r. RowHdr { draw :: ListFocused -> WidthDeficit -> RowHdrCtxt -> r -> Widget n -- | Calculate row header width from visible row headers and the width available for a list row. , width :: AvailWidth -> [r] -> RowHdrWidth -- | Get a row header from a list row and row index. , toRH :: e -> Index -> r } -- | 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. newtype ColHdrRowHdr n = ColHdrRowHdr (ListFocused -> WidthDeficit -> Widget n) deriving Generic