Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data GenericList n t e
- type List n e = GenericList n Vector e
- list :: Foldable t => n -> t e -> Int -> GenericList n t e
- renderList :: (Traversable t, Splittable t, Ord n, Show n) => (Bool -> e -> Widget n) -> Bool -> GenericList n t e -> Widget n
- renderListWithIndex :: (Traversable t, Splittable t, Ord n, Show n) => (Int -> Bool -> e -> Widget n) -> Bool -> GenericList n t e -> Widget n
- handleListEvent :: (Foldable t, Splittable t, Ord n) => Event -> GenericList n t e -> EventM n (GenericList n t e)
- handleListEventVi :: (Foldable t, Splittable t, Ord n) => (Event -> GenericList n t e -> EventM n (GenericList n t e)) -> Event -> GenericList n t e -> EventM n (GenericList n t e)
- listElementsL :: forall n t e t e. Lens (GenericList n t e) (GenericList n t e) (t e) (t e)
- listSelectedL :: forall n t e. Lens' (GenericList n t e) (Maybe Int)
- listNameL :: forall n t e n. Lens (GenericList n t e) (GenericList n t e) n n
- listItemHeightL :: forall n t e. Lens' (GenericList n t e) Int
- listElements :: GenericList n t e -> t e
- listName :: GenericList n t e -> n
- listSelectedElement :: (Splittable t, Foldable t) => GenericList n t e -> Maybe (Int, e)
- listSelected :: GenericList n t e -> Maybe Int
- listItemHeight :: GenericList n t e -> Int
- listMoveBy :: (Foldable t, Splittable t) => Int -> GenericList n t e -> GenericList n t e
- listMoveTo :: (Foldable t, Splittable t) => Int -> GenericList n t e -> GenericList n t e
- listMoveToElement :: (Eq e, Foldable t, Splittable t) => e -> GenericList n t e -> GenericList n t e
- listFindBy :: (Foldable t, Splittable t) => (e -> Bool) -> GenericList n t e -> GenericList n t e
- listMoveUp :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e
- listMoveDown :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e
- listMoveByPages :: (Foldable t, Splittable t, Ord n, RealFrac m) => m -> GenericList n t e -> EventM n (GenericList n t e)
- listMovePageUp :: (Foldable t, Splittable t, Ord n) => GenericList n t e -> EventM n (GenericList n t e)
- listMovePageDown :: (Foldable t, Splittable t, Ord n) => GenericList n t e -> EventM n (GenericList n t e)
- listMoveToBeginning :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e
- listMoveToEnd :: (Foldable t, Splittable t) => GenericList n t e -> GenericList n t e
- listInsert :: (Splittable t, Applicative t, Semigroup (t e)) => Int -> e -> GenericList n t e -> GenericList n t e
- listRemove :: (Splittable t, Foldable t, Semigroup (t e)) => Int -> GenericList n t e -> GenericList n t e
- listReplace :: (Foldable t, Splittable t) => t e -> Maybe Int -> GenericList n t e -> GenericList n t e
- listClear :: Monoid (t e) => GenericList n t e -> GenericList n t e
- listReverse :: (Reversible t, Foldable t) => GenericList n t e -> GenericList n t e
- listModify :: Traversable t => (e -> e) -> GenericList n t e -> GenericList n t e
- listAttr :: AttrName
- listSelectedAttr :: AttrName
- listSelectedFocusedAttr :: AttrName
- class Splittable t where
- class Reversible t where
- reverse :: t a -> t a
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
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
:: 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
:: (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.
:: (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)
:: (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 #
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 forList
: O(1) listMoveBy forSeq
: 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 forList
: O(1) listMoveTo forSeq
: 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.
:: (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 |
:: (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 forList
: O(n) listRemove forSeq
: 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 #
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
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
.
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 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
Splittable Seq Source # | O(log(min(i,n-i))) |
Splittable Vector Source # | O(1) |
class Reversible t where Source #
Ordered container types where the order of elements can be
reversed. Only required if you want to use listReverse
.