brick-0.41.4: A declarative terminal user interface library

Safe HaskellNone
LanguageHaskell2010

Brick.Widgets.List

Contents

Description

This module provides a scrollable list type and functions for manipulating and rendering it.

Synopsis

Documentation

data List n e Source #

List state. Lists have an element type e that is the data stored by the list. Lists handle the following events by default:

  • Up/down arrow keys: move cursor of selected item
  • Page up / page down keys: move cursor of selected item by one page at a time (based on the number of items shown)
  • Home/end keys: move cursor of selected item to beginning or end of list
Instances
Functor (List n) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

fmap :: (a -> b) -> List n a -> List n b #

(<$) :: a -> List n b -> List n a #

Foldable (List n) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

fold :: Monoid m => List n m -> m #

foldMap :: Monoid m => (a -> m) -> List n a -> m #

foldr :: (a -> b -> b) -> b -> List n a -> b #

foldr' :: (a -> b -> b) -> b -> List n a -> b #

foldl :: (b -> a -> b) -> b -> List n a -> b #

foldl' :: (b -> a -> b) -> b -> List n a -> b #

foldr1 :: (a -> a -> a) -> List n a -> a #

foldl1 :: (a -> a -> a) -> List n a -> a #

toList :: List n a -> [a] #

null :: List n a -> Bool #

length :: List n a -> Int #

elem :: Eq a => a -> List n a -> Bool #

maximum :: Ord a => List n a -> a #

minimum :: Ord a => List n a -> a #

sum :: Num a => List n a -> a #

product :: Num a => List n a -> a #

Traversable (List n) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

traverse :: Applicative f => (a -> f b) -> List n a -> f (List n b) #

sequenceA :: Applicative f => List n (f a) -> f (List n a) #

mapM :: Monad m => (a -> m b) -> List n a -> m (List n b) #

sequence :: Monad m => List n (m a) -> m (List n a) #

(Show e, Show n) => Show (List n e) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

showsPrec :: Int -> List n e -> ShowS #

show :: List n e -> String #

showList :: [List n e] -> ShowS #

Generic (List n e) Source # 
Instance details

Defined in Brick.Widgets.List

Associated Types

type Rep (List n e) :: Type -> Type #

Methods

from :: List n e -> Rep (List n e) x #

to :: Rep (List n e) x -> List n e #

Named (List n e) n Source # 
Instance details

Defined in Brick.Widgets.List

Methods

getName :: List n e -> n Source #

type Rep (List n e) Source # 
Instance details

Defined in Brick.Widgets.List

type Rep (List n e) = D1 (MetaData "List" "Brick.Widgets.List" "brick-0.41.4-JSX4ztgkehu8x18aIQ01xr" False) (C1 (MetaCons "List" PrefixI True) ((S1 (MetaSel (Just "listElements") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector e)) :*: S1 (MetaSel (Just "listSelected") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 (MetaSel (Just "listName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n) :*: S1 (MetaSel (Just "listItemHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))

Constructing a list

list Source #

Arguments

:: n

The list name (must be unique)

-> Vector e

The initial list contents

-> Int

The list item height in rows (all list item widgets must be this high)

-> List n e 

Construct a list in terms of an element type e.

Rendering a list

renderList Source #

Arguments

:: (Ord n, Show n) 
=> (Bool -> e -> Widget n)

Rendering function, True for the selected element

-> Bool

Whether the list has focus

-> List n e

The List to be rendered

-> Widget n

rendered widget

Turn a list state value into a widget given an item drawing function.

renderListWithIndex Source #

Arguments

:: (Ord n, Show n) 
=> (Int -> Bool -> e -> Widget n)

Rendering function, taking index, and True for the selected element

-> Bool

Whether the list has focus

-> List n e

The List to be rendered

-> Widget n

rendered widget

Like renderList, except the render function is also provided with the index of each element.

Handling events

handleListEvent :: Ord n => Event -> List n e -> EventM n (List n e) Source #

handleListEventVi Source #

Arguments

:: Ord n 
=> (Event -> List n e -> EventM n (List n e))

Fallback event handler to use if none of the vi keys match.

-> Event 
-> List n e 
-> EventM n (List n e) 

Enable list movement with the vi keys with a fallback if none match. Use (handleListEventVi handleListEvent) in place of handleListEvent to add the vi keys bindings to the standard ones. Movements handled include:

  • Up (k)
  • Down (j)
  • Page Up (Ctrl-b)
  • Page Down (Ctrl-f)
  • Half Page Up (Ctrl-u)
  • Half Page Down (Ctrl-d)
  • Top (g)
  • Bottom (G)

Lenses

listElementsL :: forall n e e. Lens (List n e) (List n e) (Vector e) (Vector e) Source #

listSelectedL :: forall n e. Lens' (List n e) (Maybe Int) Source #

listNameL :: forall n e n. Lens (List n e) (List n e) n n Source #

listItemHeightL :: forall n e. Lens' (List n e) Int Source #

Accessors

listElements :: List n e -> Vector e Source #

The list's vector of elements.

listName :: List n e -> n Source #

The list's name.

listSelectedElement :: List n e -> Maybe (Int, e) Source #

Return a list's selected element, if any.

listSelected :: List n e -> Maybe Int Source #

The list's selected element index, if any.

listItemHeight :: List n e -> Int Source #

The height of the list items.

Manipulating a list

listMoveBy :: Int -> List n e -> List n e Source #

Move the list selected index. If the index is `Just x`, adjust by the specified amount; if it is Nothing (i.e. there is no selection) and the direction is positive, set to `Just 0` (first element), otherwise set to `Just (length - 1)` (last element). Subject to validation.

listMoveTo :: Int -> List n e -> List n e Source #

Set the selected index for a list to the specified index, subject to validation.

listMoveToElement :: Eq e => e -> List n e -> List n e Source #

Set the selected index for a list to the index of the specified element if it is in the list, or leave the list unmodified otherwise.

listMoveUp :: List n e -> List n e Source #

Move the list selected index up by one. (Moves the cursor up, subtracts one from the index.)

listMoveDown :: List n e -> List n e Source #

Move the list selected index down by one. (Moves the cursor down, adds one to the index.)

listMoveByPages :: (Ord n, RealFrac m) => m -> List n e -> EventM n (List n e) Source #

Move the list selected index by some (fractional) number of pages.

listMovePageUp :: Ord n => List n e -> EventM n (List n e) Source #

Move the list selected index up by one page.

listMovePageDown :: Ord n => List n e -> EventM n (List n e) Source #

Move the list selected index down by one page.

listInsert Source #

Arguments

:: Int

The position at which to insert (0 <= i <= size)

-> e

The element to insert

-> List n e 
-> List n e 

Insert an item into a list at the specified position.

listRemove Source #

Arguments

:: Int

The position at which to remove an element (0 <= i < size)

-> List n e 
-> List n e 

Remove an element from a list at the specified position.

listReplace :: Vector e -> Maybe Int -> List n e -> List n e Source #

Replace the contents of a list with a new set of elements and update the new selected index. If the list is empty, empty selection is used instead. Otherwise, if the specified selected index (via Just) is not in the list bounds, zero is used instead.

listClear :: List n e -> List n e Source #

Remove all elements from the list and clear the selection.

listReverse :: List n e -> List n e Source #

Reverse the list. The element selected before the reversal will again be the selected one.

listModify :: (e -> e) -> List n e -> List n e Source #

Apply a function to the selected element. If no element is selected the list is not modified.

Attributes

listAttr :: AttrName Source #

The top-level attribute used for the entire list.

listSelectedAttr :: AttrName Source #

The attribute used only for the currently-selected list item when the list does not have focus. Extends listAttr.

listSelectedFocusedAttr :: AttrName Source #

The attribute used only for the currently-selected list item when the list has focus. Extends listSelectedAttr.