brick-0.63: A declarative terminal user interface library
Safe HaskellNone
LanguageHaskell2010

Brick.Widgets.List

Description

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

Note that lenses are provided for direct manipulation purposes, but lenses are *not* safe and should be used with care. (For example, listElementsL permits direct manipulation of the list container without performing bounds checking on the selected index.) If you need a safe API, consider one of the various functions for list manipulation. For example, instead of listElementsL, consider listReplace.

Synopsis

Documentation

data GenericList n t e Source #

List state. Lists have a container t of element type e that is the data stored by the list. Internally, 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

The List type synonym fixes t to Vector for compatibility with previous versions of this library.

For a container type to be usable with GenericList, it must have instances of Traversable and Splittable. The following functions impose further constraints:

Instances

Instances details
Functor t => Functor (GenericList n t) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

fmap :: (a -> b) -> GenericList n t a -> GenericList n t b #

(<$) :: a -> GenericList n t b -> GenericList n t a #

Foldable t => Foldable (GenericList n t) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

fold :: Monoid m => GenericList n t m -> m #

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

foldMap' :: Monoid m => (a -> m) -> GenericList n t a -> m #

foldr :: (a -> b -> b) -> b -> GenericList n t a -> b #

foldr' :: (a -> b -> b) -> b -> GenericList n t a -> b #

foldl :: (b -> a -> b) -> b -> GenericList n t a -> b #

foldl' :: (b -> a -> b) -> b -> GenericList n t a -> b #

foldr1 :: (a -> a -> a) -> GenericList n t a -> a #

foldl1 :: (a -> a -> a) -> GenericList n t a -> a #

toList :: GenericList n t a -> [a] #

null :: GenericList n t a -> Bool #

length :: GenericList n t a -> Int #

elem :: Eq a => a -> GenericList n t a -> Bool #

maximum :: Ord a => GenericList n t a -> a #

minimum :: Ord a => GenericList n t a -> a #

sum :: Num a => GenericList n t a -> a #

product :: Num a => GenericList n t a -> a #

Traversable t => Traversable (GenericList n t) Source # 
Instance details

Defined in Brick.Widgets.List

Methods

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

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

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

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

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

Defined in Brick.Widgets.List

Methods

showsPrec :: Int -> GenericList n t e -> ShowS #

show :: GenericList n t e -> String #

showList :: [GenericList n t e] -> ShowS #

Generic (GenericList n t e) Source # 
Instance details

Defined in Brick.Widgets.List

Associated Types

type Rep (GenericList n t e) :: Type -> Type #

Methods

from :: GenericList n t e -> Rep (GenericList n t e) x #

to :: Rep (GenericList n t e) x -> GenericList n t e #

Named (GenericList n t e) n Source # 
Instance details

Defined in Brick.Widgets.List

Methods

getName :: GenericList n t e -> n Source #

type Rep (GenericList n t e) Source # 
Instance details

Defined in Brick.Widgets.List

type Rep (GenericList n t e) = D1 ('MetaData "GenericList" "Brick.Widgets.List" "brick-0.63-AXjxfylufgr2HzZo0AavwP" 'False) (C1 ('MetaCons "List" 'PrefixI 'True) ((S1 ('MetaSel ('Just "listElements") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (t 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))))

type List n e = GenericList n Vector e Source #

An alias for GenericList specialized to use a Vector as its container type.

Constructing a list

list Source #

Arguments

:: Foldable t 
=> n

The list name (must be unique)

-> t e

The initial list contents

-> Int

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

-> GenericList n t e 

Construct a list in terms of container t with element type e.

Rendering a list

renderList Source #

Arguments

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

Rendering function, True for the selected element

-> Bool

Whether the list has focus

-> GenericList n t e

The List to be rendered

-> Widget n

rendered widget

Render a list using the specified item drawing function.

Evaluates the underlying container up to, and a bit beyond, the selected element. The exact amount depends on available height for drawing and listItemHeight. At most, it will evaluate up to element (i + h + 1) where i is the selected index and h is the available height.

Note that this function renders the list with the listAttr as the default attribute and then uses listSelectedAttr as the default attribute for the selected item if the list is not focused or listSelectedFocusedAttr otherwise. This is provided as a convenience so that the item rendering function doesn't have to be concerned with attributes, but if those attributes are undesirable for your purposes, forceAttr can always be used by the item rendering function to ensure that another attribute is used instead.

renderListWithIndex Source #

Arguments

:: (Traversable t, Splittable t, 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

-> GenericList n t 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.

Has the same evaluation characteristics as renderList.

Handling events

handleListEvent :: (Foldable t, Splittable t, Ord n) => Event -> GenericList n t e -> EventM n (GenericList n t e) Source #

Handle events for list cursor movement. Events handled are:

  • Up (up arrow key)
  • Down (down arrow key)
  • Page Up (PgUp)
  • Page Down (PgDown)
  • Go to first element (Home)
  • Go to last element (End)

handleListEventVi Source #

Arguments

:: (Foldable t, Splittable t, Ord n) 
=> (Event -> GenericList n t e -> EventM n (GenericList n t e))

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

-> Event 
-> GenericList n t e 
-> EventM n (GenericList n t e) 

Enable list movement with the vi keys with a fallback handler 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)
  • Go to first element (g)
  • Go to last element (G)

Lenses

listElementsL :: forall n t e t e. Lens (GenericList n t e) (GenericList n t e) (t e) (t e) Source #

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

listNameL :: forall n t e n. Lens (GenericList n t e) (GenericList n t e) n n Source #

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

Accessors

listElements :: GenericList n t e -> t e Source #

The list's sequence of elements.

listName :: GenericList n t e -> n Source #

The list's name.

listSelectedElement :: (Splittable t, Foldable t) => GenericList n t e -> Maybe (Int, e) Source #

Return a list's selected element, if any.

Only evaluates as much of the container as needed.

Complexity: same as splitAt for the container type.

listSelectedElement for List: O(1)
listSelectedElement for Seq: O(log(min(i, n - i)))

listSelected :: GenericList n t e -> Maybe Int Source #

The list's selected element index, if any.

listItemHeight :: GenericList n t e -> Int Source #

The height of an individual item in the list.

Manipulating a list

listMoveBy :: (Foldable t, Splittable t) => Int -> GenericList n t e -> GenericList n t e Source #

Move the list selected index.

If the current selection is Just x, the selection is adjusted by the specified amount. The value is clamped to the extents of the list (i.e. the selection does not "wrap").

If the current selection 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).

Complexity: same as splitAt for the container type.

listMoveBy for List: O(1)
listMoveBy for Seq: O(log(min(i,n-i)))

listMoveTo :: (Foldable t, Splittable t) => Int -> GenericList n t e -> GenericList n t e Source #

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

If pos >= 0, indexes from the start of the list (which gets evaluated up to the target index)

If pos < 0, indexes from the end of the list (which evalutes length of the list).

Complexity: same as splitAt for the container type.

listMoveTo for List: O(1)
listMoveTo for Seq: O(log(min(i,n-i)))

listMoveToElement :: (Eq e, Foldable t, Splittable t) => e -> GenericList n t e -> GenericList n t e Source #

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

O(n). Only evaluates as much of the container as needed.

listFindBy :: (Foldable t, Splittable t) => (e -> Bool) -> GenericList n t e -> GenericList n t e Source #

Starting from the currently-selected position, attempt to find and select the next element matching the predicate. If there are no matches for the remainder of the list or if the list has no selection at all, the search starts at the beginning. If no matching element is found anywhere in the list, leave the list unmodified.

O(n). Only evaluates as much of the container as needed.

listMoveUp :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e Source #

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

listMoveDown :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e Source #

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

listMoveByPages :: (Foldable t, Splittable t, Ord n, RealFrac m) => m -> GenericList n t e -> EventM n (GenericList n t e) Source #

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

listMovePageUp :: (Foldable t, Splittable t, Ord n) => GenericList n t e -> EventM n (GenericList n t e) Source #

Move the list selected index up by one page.

listMovePageDown :: (Foldable t, Splittable t, Ord n) => GenericList n t e -> EventM n (GenericList n t e) Source #

Move the list selected index down by one page.

listMoveToBeginning :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e Source #

Move the list selection to the first element in the list.

listMoveToEnd :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e Source #

Move the list selection to the last element in the list.

listInsert Source #

Arguments

:: (Splittable t, Applicative t, Semigroup (t e)) 
=> Int

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

-> e

The element to insert

-> GenericList n t e 
-> GenericList n t e 

Insert an item into a list at the specified position.

Complexity: the worse of splitAt and <> for the container type.

listInsert for List: O(n)
listInsert for Seq: O(log(min(i, length n - i)))

listRemove Source #

Arguments

:: (Splittable t, Foldable t, Semigroup (t e)) 
=> Int

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

-> GenericList n t e 
-> GenericList n t e 

Remove an element from a list at the specified position.

Applies splitAt two times: first to split the structure at the given position, and again to remove the first element from the tail. Consider the asymptotics of splitAt for the container type when using this function.

Complexity: the worse of splitAt and <> for the container type.

listRemove for List: O(n)
listRemove for Seq: O(log(min(i, n - i)))

listReplace :: (Foldable t, Splittable t) => t e -> Maybe Int -> GenericList n t e -> GenericList n t 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.

Complexity: same as splitAt for the container type.

listClear :: Monoid (t e) => GenericList n t e -> GenericList n t e Source #

Remove all elements from the list and clear the selection.

O(1)

listReverse :: (Reversible t, Foldable t) => GenericList n t e -> GenericList n t e Source #

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

Complexity: same as reverse for the container type.

listReverse for List: O(n)
listReverse for Seq: O(n)

listModify :: Traversable t => (e -> e) -> GenericList n t e -> GenericList n t e Source #

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

Complexity: same as traverse for the container type (typically O(n)).

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.

Classes

class Splittable t where Source #

Ordered container types that can be split at a given index. An instance of this class is required for a container type to be usable with GenericList.

Minimal complete definition

splitAt

Methods

splitAt :: Int -> t a -> (t a, t a) Source #

Split at the given index. Equivalent to (take n xs, drop n xs) and therefore total.

slice Source #

Arguments

:: Int

start index

-> Int

length

-> t a 
-> t a 

Slice the structure. Equivalent to (take n . drop i) xs and therefore total.

The default implementation applies splitAt two times: first to drop elements leading up to the slice, and again to drop elements after the slice.

Instances

Instances details
Splittable Seq Source #

O(log(min(i,n-i))) splitAt.

Instance details

Defined in Brick.Widgets.List

Methods

splitAt :: Int -> Seq a -> (Seq a, Seq a) Source #

slice :: Int -> Int -> Seq a -> Seq a Source #

Splittable Vector Source #

O(1) splitAt.

Instance details

Defined in Brick.Widgets.List

Methods

splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #

slice :: Int -> Int -> Vector a -> Vector a Source #

class Reversible t where Source #

Ordered container types where the order of elements can be reversed. Only required if you want to use listReverse.

Methods

reverse :: t a -> t a Source #

Instances

Instances details
Reversible Seq Source #

O(n) reverse

Instance details

Defined in Brick.Widgets.List

Methods

reverse :: Seq a -> Seq a Source #

Reversible Vector Source #

O(n) reverse

Instance details

Defined in Brick.Widgets.List

Methods

reverse :: Vector a -> Vector a Source #