{-# LANGUAGE KindSignatures #-}
-- | Functions that brick event handlers can use to move up or down while skipping a certain kind of elements.
--
-- ![ ](demo-01.png) ![ ](demo-02.png)
--
-- For example, in the above demo program, you can move in the list while skipping separators.
module Brick.Widgets.List.Skip (
-- * Types
  Dir(..)
, Amount(..)
, Move(..)
-- * Functions
, listSkip
, listSearchFromCurrent
, listShow
-- * Classes
, Searchable(..)
) where

-- base
import Prelude hiding (take, drop)
-- third party packages
import Lens.Micro
import qualified Data.Vector as V
import Data.Vector hiding (take, drop, modify)
import qualified Data.Sequence as S
import Data.Sequence hiding (take, drop)
-- brick
import qualified Brick.Widgets.List as L
import Brick.Types hiding (Direction(..))
import Brick.Main

-- | Should the search include the current location?
data IncludeCurrent = IncludeCurrent | ExcludeCurrent deriving (Int -> IncludeCurrent -> ShowS
[IncludeCurrent] -> ShowS
IncludeCurrent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IncludeCurrent] -> ShowS
$cshowList :: [IncludeCurrent] -> ShowS
show :: IncludeCurrent -> String
$cshow :: IncludeCurrent -> String
showsPrec :: Int -> IncludeCurrent -> ShowS
$cshowsPrec :: Int -> IncludeCurrent -> ShowS
Show, IncludeCurrent -> IncludeCurrent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IncludeCurrent -> IncludeCurrent -> Bool
$c/= :: IncludeCurrent -> IncludeCurrent -> Bool
== :: IncludeCurrent -> IncludeCurrent -> Bool
$c== :: IncludeCurrent -> IncludeCurrent -> Bool
Eq)

-- | The direction to move in
data Dir =
  -- | Backward, or Up
  Bwd |
  -- | Forward, or Down
  Fwd
  deriving (Int -> Dir -> ShowS
[Dir] -> ShowS
Dir -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dir] -> ShowS
$cshowList :: [Dir] -> ShowS
show :: Dir -> String
$cshow :: Dir -> String
showsPrec :: Int -> Dir -> ShowS
$cshowsPrec :: Int -> Dir -> ShowS
Show, Dir -> Dir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dir -> Dir -> Bool
$c/= :: Dir -> Dir -> Bool
== :: Dir -> Dir -> Bool
$c== :: Dir -> Dir -> Bool
Eq)

-- | The amount to move by
data Amount =
  -- | Move to the next element that fails the test.
  One |
  -- | Move forward or backward as much as possible, and start searching in the opposite direction.
  Most |
  -- | Move by one page. From there, start searching. If the search fails, start searching in the opposite direction.
  Page |
  -- | Move by half page. From there, start searching. If the search fails, start searching in the opposite direction.
  HalfPage
  deriving (Int -> Amount -> ShowS
[Amount] -> ShowS
Amount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Amount] -> ShowS
$cshowList :: [Amount] -> ShowS
show :: Amount -> String
$cshow :: Amount -> String
showsPrec :: Int -> Amount -> ShowS
$cshowsPrec :: Int -> Amount -> ShowS
Show, Amount -> Amount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Amount -> Amount -> Bool
$c/= :: Amount -> Amount -> Bool
== :: Amount -> Amount -> Bool
$c== :: Amount -> Amount -> Bool
Eq)

-- | Description of a movement
data Move =
  Move Amount Dir |
  NoMove
  deriving (Int -> Move -> ShowS
[Move] -> ShowS
Move -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Move] -> ShowS
$cshowList :: [Move] -> ShowS
show :: Move -> String
$cshow :: Move -> String
showsPrec :: Int -> Move -> ShowS
$cshowsPrec :: Int -> Move -> ShowS
Show, Move -> Move -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Move -> Move -> Bool
$c/= :: Move -> Move -> Bool
== :: Move -> Move -> Bool
$c== :: Move -> Move -> Bool
Eq)

-- | Move by a specified amount. Skip elements that pass the test.
--
-- After moving, this function calls 'listShow' with the direction of 'Move'.
listSkip :: (Foldable t, L.Splittable t, Searchable t, Ord n)
  => (e -> Bool) -- ^ The test
  -> Move
  -> EventM n (L.GenericList n t e) ()
listSkip :: forall (t :: * -> *) n e.
(Foldable t, Splittable t, Searchable t, Ord n) =>
(e -> Bool) -> Move -> EventM n (GenericList n t e) ()
listSkip e -> Bool
t Move
m = case Move
m of
  Move Amount
a Dir
Bwd -> do
    case Amount
a of
      Amount
One -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipBackward e -> Bool
t
      Amount
Most -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) e n.
(Searchable t, Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipToBeginning e -> Bool
t
      Amount
Page -> forall (t :: * -> *) n pages e.
(Searchable t, Foldable t, Splittable t, Ord n, RealFrac pages) =>
(e -> Bool) -> pages -> EventM n (GenericList n t e) ()
listSkipByPages e -> Bool
t (-Double
1.0)
      Amount
HalfPage -> forall (t :: * -> *) n pages e.
(Searchable t, Foldable t, Splittable t, Ord n, RealFrac pages) =>
(e -> Bool) -> pages -> EventM n (GenericList n t e) ()
listSkipByPages e -> Bool
t (-Double
0.5)
    forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> Dir -> EventM n (GenericList n t e) ()
listShow e -> Bool
t Dir
Bwd
  Move Amount
a Dir
Fwd -> do
    case Amount
a of
      Amount
One -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipForward e -> Bool
t
      Amount
Most -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) e n.
(Searchable t, Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipToEnd e -> Bool
t
      Amount
Page -> forall (t :: * -> *) n pages e.
(Searchable t, Foldable t, Splittable t, Ord n, RealFrac pages) =>
(e -> Bool) -> pages -> EventM n (GenericList n t e) ()
listSkipByPages e -> Bool
t Double
1.0
      Amount
HalfPage -> forall (t :: * -> *) n pages e.
(Searchable t, Foldable t, Splittable t, Ord n, RealFrac pages) =>
(e -> Bool) -> pages -> EventM n (GenericList n t e) ()
listSkipByPages e -> Bool
t Double
0.5
    forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> Dir -> EventM n (GenericList n t e) ()
listShow e -> Bool
t Dir
Fwd
  Move
NoMove -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | From the current element, search for an element that fails the test, and go to it.
listSearchFromCurrent :: Searchable t
  => (e -> Bool) -- ^ The test
  -> Dir
  -> EventM n (L.GenericList n t e) ()
listSearchFromCurrent :: forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> Dir -> EventM n (GenericList n t e) ()
listSearchFromCurrent e -> Bool
t Dir
d = let
  searchList :: IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
searchList = case Dir
d of
    Dir
Bwd -> forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward
    Dir
Fwd -> forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward
  in forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \GenericList n t e
l -> case forall {e} {n}.
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
searchList IncludeCurrent
IncludeCurrent e -> Bool
t GenericList n t e
l of
    Maybe Int
Nothing -> GenericList n t e
l
    Just Int
ix -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
ix

-- | If searching for an element that fails the test in the specified direction fails, show as many elements as possible
-- in the direction.
--
-- The current element is not included in the search.
listShow :: Searchable t
  => (e -> Bool) -- ^ The test
  -> Dir
  -> EventM n (L.GenericList n t e) ()
listShow :: forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> Dir -> EventM n (GenericList n t e) ()
listShow e -> Bool
t Dir
d = do
  GenericList n t e
l <- forall s (m :: * -> *). MonadState s m => m s
get
  let (IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipList, ViewportScroll n -> EventM n s ()
vScroll) = case Dir
d of
        -- `\s -> vScrollToXXX s` is eta expansion.
        -- eta expansion is required for GHC 9.0.2 because of simplified subsumption developed by Simon Peyton Jones.
        -- https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0287-simplify-subsumption.rst
        -- simplified subsumption is disabled by default in later GHC versions.
        -- Simon Petyon Jones hasn't found a way to avoid deep subsumption and eta expansion.
        Dir
Bwd -> (forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward, \ViewportScroll n
s -> forall n. ViewportScroll n -> forall s. EventM n s ()
vScrollToBeginning ViewportScroll n
s)
        Dir
Fwd -> (forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward, \ViewportScroll n
s -> forall n. ViewportScroll n -> forall s. EventM n s ()
vScrollToEnd ViewportScroll n
s)
  case forall {e} {n}.
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipList IncludeCurrent
ExcludeCurrent e -> Bool
t GenericList n t e
l of
    Maybe Int
Nothing -> forall {n} {s}. ViewportScroll n -> EventM n s ()
vScroll forall a b. (a -> b) -> a -> b
$ forall n. n -> ViewportScroll n
viewportScroll forall a b. (a -> b) -> a -> b
$ GenericList n t e
l forall s a. s -> Getting a s a -> a
^. forall n1 (t :: * -> *) e n2.
Lens (GenericList n1 t e) (GenericList n2 t e) n1 n2
L.listNameL
    Just Int
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Search forward for the first element index that fails the test
skipListForward :: Searchable t
  => IncludeCurrent
  -> (e -> Bool) -- ^ The test
  -> L.GenericList n t e
  -> Maybe Int -- ^ The first element index that fails the test
skipListForward :: forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward IncludeCurrent
incCur e -> Bool
test GenericList n t e
l = let
  skipForward :: a -> t e -> Maybe a
skipForward a
idx t e
es = case forall (t :: * -> *) a. Searchable t => t a -> Maybe (a, t a)
viewHead t e
es of
    Maybe (e, t e)
Nothing -> forall a. Maybe a
Nothing
    Just (e
e, t e
es') -> if e -> Bool
test e
e
      then a -> t e -> Maybe a
skipForward (a
idxforall a. Num a => a -> a -> a
+a
1) t e
es'
      else forall a. a -> Maybe a
Just a
idx
  -- Start with the current list element index. If the current element is excluded, then add 1 to the current index.
  start :: Int
start = case GenericList n t e
l forall s a. s -> Getting a s a -> a
^. forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL of
    Maybe Int
Nothing -> Int
0
    Just Int
i -> Int
i forall a. Num a => a -> a -> a
+ case IncludeCurrent
incCur of
      IncludeCurrent
IncludeCurrent -> Int
0
      IncludeCurrent
ExcludeCurrent -> Int
1
  es :: t e
es = forall (t :: * -> *) a. Searchable t => Int -> t a -> t a
drop Int
start forall a b. (a -> b) -> a -> b
$ GenericList n t e
l forall s a. s -> Getting a s a -> a
^. forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
L.listElementsL
  in forall {t :: * -> *} {a}.
(Searchable t, Num a) =>
a -> t e -> Maybe a
skipForward Int
start t e
es

-- | Search backward for the first element index that fails the test
skipListBackward :: Searchable t
  => IncludeCurrent
  -> (e -> Bool) -- ^ The test
  -> L.GenericList n t e
  -> Maybe Int -- ^ The first element index that fails the test
skipListBackward :: forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward IncludeCurrent
incCur e -> Bool
test GenericList n t e
l = let
  skipBackward :: a -> t e -> Maybe a
skipBackward a
idx t e
es = case forall (t :: * -> *) a. Searchable t => t a -> Maybe (t a, a)
viewLast t e
es of
    Maybe (t e, e)
Nothing -> forall a. Maybe a
Nothing
    Just (t e
es', e
e) -> if e -> Bool
test e
e
      then a -> t e -> Maybe a
skipBackward (a
idxforall a. Num a => a -> a -> a
-a
1) t e
es'
      else forall a. a -> Maybe a
Just a
idx
  -- Start with the current list element index + 1 so that the current index is included. If the current element is
  -- excluded, don't add 1 to the current index.
  start :: Int
start = case GenericList n t e
l forall s a. s -> Getting a s a -> a
^. forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL of
    Maybe Int
Nothing -> Int
0
    Just Int
i -> Int
i forall a. Num a => a -> a -> a
+ case IncludeCurrent
incCur of
      IncludeCurrent
IncludeCurrent -> Int
1
      IncludeCurrent
ExcludeCurrent -> Int
0
  es :: t e
es = forall (t :: * -> *) a. Searchable t => Int -> t a -> t a
take Int
start forall a b. (a -> b) -> a -> b
$ GenericList n t e
l forall s a. s -> Getting a s a -> a
^. forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
L.listElementsL
  in forall {t :: * -> *} {a}.
(Searchable t, Num a) =>
a -> t e -> Maybe a
skipBackward (Int
startforall a. Num a => a -> a -> a
-Int
1) t e
es

-- | Search backward for the first element that fails the test.
--
-- The current element is not included in the search.
--
-- If backward search fails, no change is made.
listSkipBackward :: Searchable t
  => (e -> Bool) -- ^ The test
  -> L.GenericList n t e
  -> L.GenericList n t e
listSkipBackward :: forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipBackward e -> Bool
test GenericList n t e
l = case forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward IncludeCurrent
ExcludeCurrent e -> Bool
test GenericList n t e
l of
  Maybe Int
Nothing -> GenericList n t e
l
  Just Int
idx -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
idx

-- | Search forward for the first element that fails the test.
--
-- The current element is not included in the search.
--
-- If forward search fails, no change is made.
listSkipForward :: Searchable t
  => (e -> Bool) -- ^ The test
  -> L.GenericList n t e
  -> L.GenericList n t e
listSkipForward :: forall (t :: * -> *) e n.
Searchable t =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipForward e -> Bool
test GenericList n t e
l = case forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward IncludeCurrent
ExcludeCurrent e -> Bool
test GenericList n t e
l of
  Maybe Int
Nothing -> GenericList n t e
l
  Just Int
idx -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
idx

-- | Move by a (fractional) number of pages in the list. If the number of pages to move by is 0, no change is made.
-- Otherwise, call 'L.listMoveByPages' with the number of pages to move by.
--
-- The element chosen by 'L.listMoveByPages' is included in the search.
--
-- After calling 'L.listMoveByPages', if the number of pages to move by was positive, search forward for the first
-- element that fails the test. If forward search fails, then search backward for the first such element. If backward
-- search fails too, cancel movements made by this function.
--
-- After calling 'L.listMoveByPages', if the number of pages to move by was negative, search backward for the first
-- element that fails the test. If backward search fails, then search forward for the first such element. If forward
-- search fails too, cancel movements made by this function.
listSkipByPages :: (Searchable t, Foldable t, L.Splittable t, Ord n, RealFrac pages)
  => (e -> Bool) -- ^ The test
  -> pages -- ^ Pages to move by
  -> EventM n (L.GenericList n t e) ()
listSkipByPages :: forall (t :: * -> *) n pages e.
(Searchable t, Foldable t, Splittable t, Ord n, RealFrac pages) =>
(e -> Bool) -> pages -> EventM n (GenericList n t e) ()
listSkipByPages e -> Bool
test pages
p = if pages
p forall a. Eq a => a -> a -> Bool
== pages
0
  then forall (m :: * -> *) a. Monad m => a -> m a
return ()
  else do
    GenericList n t e
origL <- forall s (m :: * -> *). MonadState s m => m s
get
    forall (t :: * -> *) n m e.
(Foldable t, Splittable t, Ord n, RealFrac m) =>
m -> EventM n (GenericList n t e) ()
L.listMoveByPages pages
p
    let (IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
searchList, IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
searchListOpposite) = if pages
p forall a. Ord a => a -> a -> Bool
< pages
0
           then (forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward, forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward)
           else (forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward, forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward)
    forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \GenericList n t e
l -> case forall {e} {n}.
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
searchList IncludeCurrent
IncludeCurrent e -> Bool
test GenericList n t e
l of
      Maybe Int
Nothing -> case forall {e} {n}.
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
searchListOpposite IncludeCurrent
ExcludeCurrent e -> Bool
test GenericList n t e
l of
        Maybe Int
Nothing -> GenericList n t e
origL
        Just Int
idx -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
idx
      Just Int
idx -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
idx

-- | From the first element, search forward for the first element that fails the test.
--
-- The first element is included in the search.
--
-- If forward search fails, no change is made.
listSkipToBeginning :: (Searchable t, Foldable t, L.Splittable t)
  => (e -> Bool) -- ^ The test
  -> L.GenericList n t e
  -> L.GenericList n t e
listSkipToBeginning :: forall (t :: * -> *) e n.
(Searchable t, Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipToBeginning e -> Bool
test GenericList n t e
l = case forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListForward IncludeCurrent
IncludeCurrent e -> Bool
test (forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
L.listMoveToBeginning GenericList n t e
l) of
  Maybe Int
Nothing -> GenericList n t e
l
  Just Int
idx -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
idx

-- | From the last element, search backward for the first element that fails the test.
--
-- The last element is included in the search.
--
-- If backward search fails, no change is made.
listSkipToEnd :: (Searchable t, Foldable t, L.Splittable t)
  => (e -> Bool) -- ^ The test
  -> L.GenericList n t e
  -> L.GenericList n t e
listSkipToEnd :: forall (t :: * -> *) e n.
(Searchable t, Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listSkipToEnd e -> Bool
test GenericList n t e
l = case forall (t :: * -> *) e n.
Searchable t =>
IncludeCurrent -> (e -> Bool) -> GenericList n t e -> Maybe Int
skipListBackward IncludeCurrent
IncludeCurrent e -> Bool
test (forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
L.listMoveToEnd GenericList n t e
l) of
  Maybe Int
Nothing -> GenericList n t e
l
  Just Int
idx -> GenericList n t e
l forall a b. a -> (a -> b) -> b
& forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Int
idx

-- | Functions for searching elements.
class Searchable (t :: * -> *) where
  -- | Get the head and the rest
  viewHead :: t a -> Maybe (a, t a)
  -- | Get the last element and the rest
  viewLast :: t a -> Maybe (t a, a)
  -- | Take a number of elements from the beginning
  take :: Int -> t a -> t a
  -- | Drop a number of elements from the beginning
  drop :: Int -> t a -> t a

-- | O(1) for all operations
instance Searchable Vector where
  viewHead :: forall a. Vector a -> Maybe (a, Vector a)
viewHead = forall a. Vector a -> Maybe (a, Vector a)
uncons
  viewLast :: forall a. Vector a -> Maybe (Vector a, a)
viewLast = forall a. Vector a -> Maybe (Vector a, a)
unsnoc
  take :: forall a. Int -> Vector a -> Vector a
take = forall a. Int -> Vector a -> Vector a
V.take
  drop :: forall a. Int -> Vector a -> Vector a
drop = forall a. Int -> Vector a -> Vector a
V.drop

-- | O(1) for viewHead and viewLast. O(log(min(i,n-i))) for take and drop.
instance Searchable Seq where
  viewHead :: forall a. Seq a -> Maybe (a, Seq a)
viewHead Seq a
s = case forall a. Seq a -> ViewL a
S.viewl Seq a
s of
    ViewL a
EmptyL -> forall a. Maybe a
Nothing
    a
a :< Seq a
s' -> forall a. a -> Maybe a
Just (a
a, Seq a
s')
  viewLast :: forall a. Seq a -> Maybe (Seq a, a)
viewLast Seq a
s = case forall a. Seq a -> ViewR a
S.viewr Seq a
s of
    ViewR a
EmptyR -> forall a. Maybe a
Nothing
    Seq a
s' :> a
a -> forall a. a -> Maybe a
Just (Seq a
s', a
a)
  take :: forall a. Int -> Seq a -> Seq a
take = forall a. Int -> Seq a -> Seq a
S.take
  drop :: forall a. Int -> Seq a -> Seq a
drop = forall a. Int -> Seq a -> Seq a
S.drop