1{-# LANGUAGE TupleSections #-}
2{-# LANGUAGE OverloadedStrings #-}
3{-# LANGUAGE TemplateHaskell #-}
4{-# LANGUAGE DeriveFunctor #-}
5{-# LANGUAGE DeriveFoldable#-}
6{-# LANGUAGE DeriveTraversable #-}
7{-# LANGUAGE MultiParamTypeClasses #-}
8{-# LANGUAGE FlexibleInstances #-}
9{-# LANGUAGE DeriveGeneric #-}
10-- | This module provides a scrollable list type and functions for
11-- manipulating and rendering it.
12--
13-- Note that lenses are provided for direct manipulation purposes, but
14-- lenses are *not* safe and should be used with care. (For example,
15-- 'listElementsL' permits direct manipulation of the list container
16-- without performing bounds checking on the selected index.) If you
17-- need a safe API, consider one of the various functions for list
18-- manipulation. For example, instead of 'listElementsL', consider
19-- 'listReplace'.
20module Brick.Widgets.List
21  ( GenericList
22  , List
23
24  -- * Constructing a list
25  , list
26
27  -- * Rendering a list
28  , renderList
29  , renderListWithIndex
30
31  -- * Handling events
32  , handleListEvent
33  , handleListEventVi
34
35  -- * Lenses
36  , listElementsL
37  , listSelectedL
38  , listNameL
39  , listItemHeightL
40
41  -- * Accessors
42  , listElements
43  , listName
44  , listSelectedElement
45  , listSelected
46  , listItemHeight
47
48  -- * Manipulating a list
49  , listMoveBy
50  , listMoveTo
51  , listMoveToElement
52  , listFindBy
53  , listMoveUp
54  , listMoveDown
55  , listMoveByPages
56  , listMovePageUp
57  , listMovePageDown
58  , listMoveToBeginning
59  , listMoveToEnd
60  , listInsert
61  , listRemove
62  , listReplace
63  , listClear
64  , listReverse
65  , listModify
66
67  -- * Attributes
68  , listAttr
69  , listSelectedAttr
70  , listSelectedFocusedAttr
71
72  -- * Classes
73  , Splittable(..)
74  , Reversible(..)
75  )
76where
77
78import Prelude hiding (reverse, splitAt)
79
80import Control.Applicative ((<|>))
81#if !MIN_VERSION_base(4,8,0)
82import Control.Applicative ((<$>), (<*>), pure)
83import Data.Foldable (Foldable, find, toList)
84import Data.Traversable (Traversable)
85#else
86import Data.Foldable (find, toList)
87#endif
88import Control.Monad.Trans.State (evalState, get, put)
89
90import Lens.Micro ((^.), (^?), (&), (.~), (%~), _2, _head, set)
91import Data.Functor (($>))
92import Data.List.NonEmpty (NonEmpty((:|)))
93import Data.Maybe (fromMaybe)
94#if !(MIN_VERSION_base(4,11,0))
95import Data.Semigroup (Semigroup, (<>))
96#endif
97import Data.Semigroup (sconcat)
98import qualified Data.Sequence as Seq
99import Graphics.Vty (Event(..), Key(..), Modifier(..))
100import qualified Data.Vector as V
101import GHC.Generics (Generic)
102
103import Brick.Types
104import Brick.Main (lookupViewport)
105import Brick.Widgets.Core
106import Brick.Util (clamp)
107import Brick.AttrMap
108
109-- | List state. Lists have a container @t@ of element type @e@ that is
110-- the data stored by the list. Internally, Lists handle the following
111-- events by default:
112--
113-- * Up/down arrow keys: move cursor of selected item
114-- * Page up / page down keys: move cursor of selected item by one page
115--   at a time (based on the number of items shown)
116-- * Home/end keys: move cursor of selected item to beginning or end of
117--   list
118--
119-- The 'List' type synonym fixes @t@ to 'V.Vector' for compatibility
120-- with previous versions of this library.
121--
122-- For a container type to be usable with 'GenericList', it must have
123-- instances of 'Traversable' and 'Splittable'. The following functions
124-- impose further constraints:
125--
126-- * 'listInsert': 'Applicative' and 'Semigroup'
127-- * 'listRemove': 'Semigroup'
128-- * 'listClear': 'Monoid'
129-- * 'listReverse': 'Reversible'
130--
131data GenericList n t e =
132    List { listElements :: !(t e)
133         -- ^ The list's sequence of elements.
134         , listSelected :: !(Maybe Int)
135         -- ^ The list's selected element index, if any.
136         , listName :: n
137         -- ^ The list's name.
138         , listItemHeight :: Int
139         -- ^ The height of an individual item in the list.
140         } deriving (Functor, Foldable, Traversable, Show, Generic)
141
142suffixLenses ''GenericList
143
144-- | An alias for 'GenericList' specialized to use a 'Vector' as its
145-- container type.
146type List n e = GenericList n V.Vector e
147
148instance Named (GenericList n t e) n where
149    getName = listName
150
151-- | Ordered container types that can be split at a given index. An
152-- instance of this class is required for a container type to be usable
153-- with 'GenericList'.
154class Splittable t where
155    {-# MINIMAL splitAt #-}
156
157    -- | Split at the given index. Equivalent to @(take n xs, drop n xs)@
158    -- and therefore total.
159    splitAt :: Int -> t a -> (t a, t a)
160
161    -- | Slice the structure. Equivalent to @(take n . drop i) xs@ and
162    -- therefore total.
163    --
164    -- The default implementation applies 'splitAt' two times: first to
165    -- drop elements leading up to the slice, and again to drop elements
166    -- after the slice.
167    slice :: Int {- ^ start index -} -> Int {- ^ length -} -> t a -> t a
168    slice i n = fst . splitAt n . snd . splitAt i
169
170-- | /O(1)/ 'splitAt'.
171instance Splittable V.Vector where
172    splitAt = V.splitAt
173
174-- | /O(log(min(i,n-i)))/ 'splitAt'.
175instance Splittable Seq.Seq where
176    splitAt = Seq.splitAt
177
178-- | Ordered container types where the order of elements can be
179-- reversed. Only required if you want to use 'listReverse'.
180class Reversible t where
181    {-# MINIMAL reverse #-}
182    reverse :: t a -> t a
183
184-- | /O(n)/ 'reverse'
185instance Reversible V.Vector where
186  reverse = V.reverse
187
188-- | /O(n)/ 'reverse'
189instance Reversible Seq.Seq where
190  reverse = Seq.reverse
191
192-- | Handle events for list cursor movement.  Events handled are:
193--
194-- * Up (up arrow key)
195-- * Down (down arrow key)
196-- * Page Up (PgUp)
197-- * Page Down (PgDown)
198-- * Go to first element (Home)
199-- * Go to last element (End)
200handleListEvent :: (Foldable t, Splittable t, Ord n)
201                => Event
202                -> GenericList n t e
203                -> EventM n (GenericList n t e)
204handleListEvent e theList =
205    case e of
206        EvKey KUp [] -> return $ listMoveUp theList
207        EvKey KDown [] -> return $ listMoveDown theList
208        EvKey KHome [] -> return $ listMoveToBeginning theList
209        EvKey KEnd [] -> return $ listMoveToEnd theList
210        EvKey KPageDown [] -> listMovePageDown theList
211        EvKey KPageUp [] -> listMovePageUp theList
212        _ -> return theList
213
214-- | Enable list movement with the vi keys with a fallback handler if
215-- none match. Use 'handleListEventVi' 'handleListEvent' in place of
216-- 'handleListEvent' to add the vi keys bindings to the standard ones.
217-- Movements handled include:
218--
219-- * Up (k)
220-- * Down (j)
221-- * Page Up (Ctrl-b)
222-- * Page Down (Ctrl-f)
223-- * Half Page Up (Ctrl-u)
224-- * Half Page Down (Ctrl-d)
225-- * Go to first element (g)
226-- * Go to last element (G)
227handleListEventVi :: (Foldable t, Splittable t, Ord n)
228                  => (Event -> GenericList n t e -> EventM n (GenericList n t e))
229                  -- ^ Fallback event handler to use if none of the vi keys
230                  -- match.
231                  -> Event
232                  -> GenericList n t e
233                  -> EventM n (GenericList n t e)
234handleListEventVi fallback e theList =
235    case e of
236        EvKey (KChar 'k') [] -> return $ listMoveUp theList
237        EvKey (KChar 'j') [] -> return $ listMoveDown theList
238        EvKey (KChar 'g') [] -> return $ listMoveToBeginning theList
239        EvKey (KChar 'G') [] -> return $ listMoveToEnd theList
240        EvKey (KChar 'f') [MCtrl] -> listMovePageDown theList
241        EvKey (KChar 'b') [MCtrl] -> listMovePageUp theList
242        EvKey (KChar 'd') [MCtrl] -> listMoveByPages (0.5::Double) theList
243        EvKey (KChar 'u') [MCtrl] -> listMoveByPages (-0.5::Double) theList
244        _ -> fallback e theList
245
246-- | Move the list selection to the first element in the list.
247listMoveToBeginning :: (Foldable t, Splittable t)
248                    => GenericList n t e
249                    -> GenericList n t e
250listMoveToBeginning = listMoveTo 0
251
252-- | Move the list selection to the last element in the list.
253listMoveToEnd :: (Foldable t, Splittable t)
254              => GenericList n t e
255              -> GenericList n t e
256listMoveToEnd l = listMoveTo (length $ listElements l) l
257
258-- | The top-level attribute used for the entire list.
259listAttr :: AttrName
260listAttr = "list"
261
262-- | The attribute used only for the currently-selected list item when
263-- the list does not have focus. Extends 'listAttr'.
264listSelectedAttr :: AttrName
265listSelectedAttr = listAttr <> "selected"
266
267-- | The attribute used only for the currently-selected list item when
268-- the list has focus. Extends 'listSelectedAttr'.
269listSelectedFocusedAttr :: AttrName
270listSelectedFocusedAttr = listSelectedAttr <> "focused"
271
272-- | Construct a list in terms of container 't' with element type 'e'.
273list :: (Foldable t)
274     => n
275     -- ^ The list name (must be unique)
276     -> t e
277     -- ^ The initial list contents
278     -> Int
279     -- ^ The list item height in rows (all list item widgets must be
280     -- this high).
281     -> GenericList n t e
282list name es h =
283    let selIndex = if null es then Nothing else Just 0
284        safeHeight = max 1 h
285    in List es selIndex name safeHeight
286
287-- | Render a list using the specified item drawing function.
288--
289-- Evaluates the underlying container up to, and a bit beyond, the
290-- selected element. The exact amount depends on available height
291-- for drawing and 'listItemHeight'. At most, it will evaluate up to
292-- element @(i + h + 1)@ where @i@ is the selected index and @h@ is the
293-- available height.
294--
295-- Note that this function renders the list with the 'listAttr' as
296-- the default attribute and then uses 'listSelectedAttr' as the
297-- default attribute for the selected item if the list is not focused
298-- or 'listSelectedFocusedAttr' otherwise. This is provided as a
299-- convenience so that the item rendering function doesn't have to be
300-- concerned with attributes, but if those attributes are undesirable
301-- for your purposes, 'forceAttr' can always be used by the item
302-- rendering function to ensure that another attribute is used instead.
303renderList :: (Traversable t, Splittable t, Ord n, Show n)
304           => (Bool -> e -> Widget n)
305           -- ^ Rendering function, True for the selected element
306           -> Bool
307           -- ^ Whether the list has focus
308           -> GenericList n t e
309           -- ^ The List to be rendered
310           -> Widget n
311           -- ^ rendered widget
312renderList drawElem = renderListWithIndex $ const drawElem
313
314-- | Like 'renderList', except the render function is also provided with
315-- the index of each element.
316--
317-- Has the same evaluation characteristics as 'renderList'.
318renderListWithIndex :: (Traversable t, Splittable t, Ord n, Show n)
319                    => (Int -> Bool -> e -> Widget n)
320                    -- ^ Rendering function, taking index, and True for
321                    -- the selected element
322                    -> Bool
323                    -- ^ Whether the list has focus
324                    -> GenericList n t e
325                    -- ^ The List to be rendered
326                    -> Widget n
327                    -- ^ rendered widget
328renderListWithIndex drawElem foc l =
329    withDefAttr listAttr $
330    drawListElements foc l drawElem
331
332imap :: (Traversable t) => (Int -> a -> b) -> t a -> t b
333imap f xs =
334    let act = traverse (\a -> get >>= \i -> put (i + 1) $> f i a) xs
335    in evalState act 0
336
337-- | Draws the list elements.
338--
339-- Evaluates the underlying container up to, and a bit beyond, the
340-- selected element. The exact amount depends on available height
341-- for drawing and 'listItemHeight'. At most, it will evaluate up to
342-- element @(i + h + 1)@ where @i@ is the selected index and @h@ is the
343-- available height.
344drawListElements :: (Traversable t, Splittable t, Ord n, Show n)
345                 => Bool
346                 -> GenericList n t e
347                 -> (Int -> Bool -> e -> Widget n)
348                 -> Widget n
349drawListElements foc l drawElem =
350    Widget Greedy Greedy $ do
351        c <- getContext
352
353        -- Take (numPerHeight * 2) elements, or whatever is left
354        let es = slice start (numPerHeight * 2) (l^.listElementsL)
355
356            idx = fromMaybe 0 (l^.listSelectedL)
357
358            start = max 0 $ idx - numPerHeight + 1
359
360            -- The number of items to show is the available height
361            -- divided by the item height...
362            initialNumPerHeight = (c^.availHeightL) `div` (l^.listItemHeightL)
363            -- ... but if the available height leaves a remainder of
364            -- an item height then we need to ensure that we render an
365            -- extra item to show a partial item at the top or bottom to
366            -- give the expected result when an item is more than one
367            -- row high. (Example: 5 rows available with item height
368            -- of 3 yields two items: one fully rendered, the other
369            -- rendered with only its top 2 or bottom 2 rows visible,
370            -- depending on how the viewport state changes.)
371            numPerHeight = initialNumPerHeight +
372                           if initialNumPerHeight * (l^.listItemHeightL) == c^.availHeightL
373                           then 0
374                           else 1
375
376            off = start * (l^.listItemHeightL)
377
378            drawnElements = flip imap es $ \i e ->
379                let j = i + start
380                    isSelected = Just j == l^.listSelectedL
381                    elemWidget = drawElem j isSelected e
382                    selItemAttr = if foc
383                                  then withDefAttr listSelectedFocusedAttr
384                                  else withDefAttr listSelectedAttr
385                    makeVisible = if isSelected
386                                  then visible . selItemAttr
387                                  else id
388                in makeVisible elemWidget
389
390        render $ viewport (l^.listNameL) Vertical $
391                 translateBy (Location (0, off)) $
392                 vBox $ toList drawnElements
393
394-- | Insert an item into a list at the specified position.
395--
396-- Complexity: the worse of 'splitAt' and `<>` for the container type.
397--
398-- @
399-- listInsert for 'List': O(n)
400-- listInsert for 'Seq.Seq': O(log(min(i, length n - i)))
401-- @
402listInsert :: (Splittable t, Applicative t, Semigroup (t e))
403           => Int
404           -- ^ The position at which to insert (0 <= i <= size)
405           -> e
406           -- ^ The element to insert
407           -> GenericList n t e
408           -> GenericList n t e
409listInsert pos e l =
410    let es = l^.listElementsL
411        newSel = case l^.listSelectedL of
412            Nothing -> 0
413            Just s -> if pos <= s
414                      then s + 1
415                      else s
416        (front, back) = splitAt pos es
417    in l & listSelectedL .~ Just newSel
418         & listElementsL .~ sconcat (front :| [pure e, back])
419
420-- | Remove an element from a list at the specified position.
421--
422-- Applies 'splitAt' two times: first to split the structure at the
423-- given position, and again to remove the first element from the tail.
424-- Consider the asymptotics of `splitAt` for the container type when
425-- using this function.
426--
427-- Complexity: the worse of 'splitAt' and `<>` for the container type.
428--
429-- @
430-- listRemove for 'List': O(n)
431-- listRemove for 'Seq.Seq': O(log(min(i, n - i)))
432-- @
433listRemove :: (Splittable t, Foldable t, Semigroup (t e))
434           => Int
435           -- ^ The position at which to remove an element (0 <= i <
436           -- size)
437           -> GenericList n t e
438           -> GenericList n t e
439listRemove pos l | null l = l
440                 | pos /= splitClamp l pos = l
441                 | otherwise =
442    let newSel = case l^.listSelectedL of
443            Nothing -> 0
444            Just s | pos == 0 -> 0
445                   | pos == s -> pos - 1
446                   | pos  < s -> s - 1
447                   | otherwise -> s
448        (front, rest) = splitAt pos es
449        (_, back) = splitAt 1 rest
450        es' = front <> back
451        es = l^.listElementsL
452    in l & listSelectedL .~ (if null es' then Nothing else Just newSel)
453         & listElementsL .~ es'
454
455-- | Replace the contents of a list with a new set of elements and
456-- update the new selected index. If the list is empty, empty selection
457-- is used instead. Otherwise, if the specified selected index (via
458-- 'Just') is not in the list bounds, zero is used instead.
459--
460-- Complexity: same as 'splitAt' for the container type.
461listReplace :: (Foldable t, Splittable t)
462            => t e
463            -> Maybe Int
464            -> GenericList n t e
465            -> GenericList n t e
466listReplace es idx l =
467    let l' = l & listElementsL .~ es
468        newSel = if null es then Nothing else inBoundsOrZero <$> idx
469        inBoundsOrZero i
470            | i == splitClamp l' i = i
471            | otherwise = 0
472    in l' & listSelectedL .~ newSel
473
474-- | Move the list selected index up by one. (Moves the cursor up,
475-- subtracts one from the index.)
476listMoveUp :: (Foldable t, Splittable t)
477           => GenericList n t e
478           -> GenericList n t e
479listMoveUp = listMoveBy (-1)
480
481-- | Move the list selected index up by one page.
482listMovePageUp :: (Foldable t, Splittable t, Ord n)
483               => GenericList n t e
484               -> EventM n (GenericList n t e)
485listMovePageUp = listMoveByPages (-1::Double)
486
487-- | Move the list selected index down by one. (Moves the cursor down,
488-- adds one to the index.)
489listMoveDown :: (Foldable t, Splittable t)
490             => GenericList n t e
491             -> GenericList n t e
492listMoveDown = listMoveBy 1
493
494-- | Move the list selected index down by one page.
495listMovePageDown :: (Foldable t, Splittable t, Ord n)
496                 => GenericList n t e
497                 -> EventM n (GenericList n t e)
498listMovePageDown = listMoveByPages (1::Double)
499
500-- | Move the list selected index by some (fractional) number of pages.
501listMoveByPages :: (Foldable t, Splittable t, Ord n, RealFrac m)
502                => m
503                -> GenericList n t e
504                -> EventM n (GenericList n t e)
505listMoveByPages pages theList = do
506    v <- lookupViewport (theList^.listNameL)
507    case v of
508        Nothing -> return theList
509        Just vp -> do
510            let nElems = round $ pages * fromIntegral (vp^.vpSize._2) /
511                                 fromIntegral (theList^.listItemHeightL)
512            return $ listMoveBy nElems theList
513
514-- | Move the list selected index.
515--
516-- If the current selection is @Just x@, the selection is adjusted by
517-- the specified amount. The value is clamped to the extents of the list
518-- (i.e. the selection does not "wrap").
519--
520-- If the current selection is @Nothing@ (i.e. there is no selection)
521-- and the direction is positive, set to @Just 0@ (first element),
522-- otherwise set to @Just (length - 1)@ (last element).
523--
524-- Complexity: same as 'splitAt' for the container type.
525--
526-- @
527-- listMoveBy for 'List': O(1)
528-- listMoveBy for 'Seq.Seq': O(log(min(i,n-i)))
529-- @
530listMoveBy :: (Foldable t, Splittable t)
531           => Int
532           -> GenericList n t e
533           -> GenericList n t e
534listMoveBy amt l =
535    let target = case l ^. listSelectedL of
536            Nothing
537                | amt > 0 -> 0
538                | otherwise -> length l - 1
539            Just i -> max 0 (amt + i)  -- don't be negative
540    in listMoveTo target l
541
542-- | Set the selected index for a list to the specified index, subject
543-- to validation.
544--
545-- If @pos >= 0@, indexes from the start of the list (which gets
546-- evaluated up to the target index)
547--
548-- If @pos < 0@, indexes from the end of the list (which evalutes
549-- 'length' of the list).
550--
551-- Complexity: same as 'splitAt' for the container type.
552--
553-- @
554-- listMoveTo for 'List': O(1)
555-- listMoveTo for 'Seq.Seq': O(log(min(i,n-i)))
556-- @
557listMoveTo :: (Foldable t, Splittable t)
558           => Int
559           -> GenericList n t e
560           -> GenericList n t e
561listMoveTo pos l =
562    let len = length l
563        i = if pos < 0 then len - pos else pos
564        newSel = splitClamp l i
565    in l & listSelectedL .~ if null l then Nothing else Just newSel
566
567-- | Split-based clamp that avoids evaluating 'length' of the structure
568-- (unless the structure is already fully evaluated).
569splitClamp :: (Foldable t, Splittable t) => GenericList n t e -> Int -> Int
570splitClamp l i =
571    let (_, t) = splitAt i (l ^. listElementsL)  -- split at i
572    in
573        -- If the tail is empty, then the requested index is not in the
574        -- list. And because we have already seen the end of the list,
575        -- using 'length' will not force unwanted computation.
576        --
577        -- Otherwise if tail is not empty, then we already know that i
578        -- is in the list, so we don't need to know the length
579        clamp 0 (if null t then length l - 1 else i) i
580
581-- | Set the selected index for a list to the index of the first
582-- occurrence of the specified element if it is in the list, or leave
583-- the list unmodified otherwise.
584--
585-- /O(n)/.  Only evaluates as much of the container as needed.
586listMoveToElement :: (Eq e, Foldable t, Splittable t)
587                  => e
588                  -> GenericList n t e
589                  -> GenericList n t e
590listMoveToElement e = listFindBy (== e) . set listSelectedL Nothing
591
592-- | Starting from the currently-selected position, attempt to find
593-- and select the next element matching the predicate. If there are no
594-- matches for the remainder of the list or if the list has no selection
595-- at all, the search starts at the beginning. If no matching element is
596-- found anywhere in the list, leave the list unmodified.
597--
598-- /O(n)/.  Only evaluates as much of the container as needed.
599listFindBy :: (Foldable t, Splittable t)
600           => (e -> Bool)
601           -> GenericList n t e
602           -> GenericList n t e
603listFindBy test l =
604    let start = maybe 0 (+1) (l ^. listSelectedL)
605        (h, t) = splitAt start (l ^. listElementsL)
606        tailResult = find (test . snd) . zip [start..] . toList $ t
607        headResult = find (test . snd) . zip [0..] . toList $ h
608        result = tailResult <|> headResult
609    in maybe id (set listSelectedL . Just . fst) result l
610
611-- | Return a list's selected element, if any.
612--
613-- Only evaluates as much of the container as needed.
614--
615-- Complexity: same as 'splitAt' for the container type.
616--
617-- @
618-- listSelectedElement for 'List': O(1)
619-- listSelectedElement for 'Seq.Seq': O(log(min(i, n - i)))
620-- @
621listSelectedElement :: (Splittable t, Foldable t)
622                    => GenericList n t e
623                    -> Maybe (Int, e)
624listSelectedElement l = do
625    sel <- l^.listSelectedL
626    let (_, xs) = splitAt sel (l ^. listElementsL)
627    (sel,) <$> toList xs ^? _head
628
629-- | Remove all elements from the list and clear the selection.
630--
631-- /O(1)/
632listClear :: (Monoid (t e)) => GenericList n t e -> GenericList n t e
633listClear l = l & listElementsL .~ mempty & listSelectedL .~ Nothing
634
635-- | Reverse the list. The element selected before the reversal will
636-- again be the selected one.
637--
638-- Complexity: same as 'reverse' for the container type.
639--
640-- @
641-- listReverse for 'List': O(n)
642-- listReverse for 'Seq.Seq': O(n)
643-- @
644listReverse :: (Reversible t, Foldable t)
645            => GenericList n t e
646            -> GenericList n t e
647listReverse l =
648    l & listElementsL %~ reverse
649      & listSelectedL %~ fmap (length l - 1 -)
650
651-- | Apply a function to the selected element. If no element is selected
652-- the list is not modified.
653--
654-- Complexity: same as 'traverse' for the container type (typically
655-- /O(n)/).
656listModify :: (Traversable t)
657           => (e -> e)
658           -> GenericList n t e
659           -> GenericList n t e
660listModify f l =
661    case l ^. listSelectedL of
662        Nothing -> l
663        Just j -> l & listElementsL %~ imap (\i e -> if i == j then f e else e)
664