{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-unused-record-wildcards #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE InstanceSigs #-}
module GHCup.Brick.Widgets.SectionList where
import Brick
( BrickEvent(VtyEvent, MouseDown),
EventM,
Size(..),
Widget(..),
ViewportType (Vertical),
(<=>))
import qualified Brick
import Brick.Widgets.Border ( hBorder)
import qualified Brick.Widgets.List as L
import Brick.Focus (FocusRing)
import qualified Brick.Focus as F
import Data.Function ( (&))
import Data.Maybe ( fromMaybe )
import Data.Vector ( Vector )
import qualified GHCup.Brick.Common as Common
import Prelude hiding ( appendFile )
import qualified Graphics.Vty as Vty
import qualified Data.Vector as V
import Optics.TH (makeLensesFor)
import Optics.State (use)
import Optics.State.Operators ( (%=), (<%=))
import Optics.Operators ((.~), (^.))
import Optics.Lens (Lens', lens)
data GenericSectionList n t e
= GenericSectionList
{ forall n (t :: * -> *) e. GenericSectionList n t e -> FocusRing n
sectionListFocusRing :: FocusRing n
, forall n (t :: * -> *) e.
GenericSectionList n t e -> Vector (GenericList n t e)
sectionListElements :: !(Vector (L.GenericList n t e))
, forall n (t :: * -> *) e. GenericSectionList n t e -> n
sectionListName :: n
}
makeLensesFor [("sectionListFocusRing", "sectionListFocusRingL"), ("sectionListElements", "sectionListElementsL"), ("sectionListName", "sectionListNameL")] ''GenericSectionList
type SectionList n e = GenericSectionList n V.Vector e
class ListItemSectionNameIndex n where
getListItemSectionNameIndex :: n -> Maybe (n, Int)
sectionList :: Foldable t
=> n
-> [(n, t e)]
-> Int
-> GenericSectionList n t e
sectionList :: forall (t :: * -> *) n e.
Foldable t =>
n -> [(n, t e)] -> Int -> GenericSectionList n t e
sectionList n
name [(n, t e)]
elements Int
height
= GenericSectionList
{ sectionListFocusRing :: FocusRing n
sectionListFocusRing = [n] -> FocusRing n
forall n. [n] -> FocusRing n
F.focusRing [n
section_name | (n
section_name, t e
_) <- [(n, t e)]
elements]
, sectionListElements :: Vector (GenericList n t e)
sectionListElements = [GenericList n t e] -> Vector (GenericList n t e)
forall a. [a] -> Vector a
V.fromList [n -> t e -> Int -> GenericList n t e
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
L.list n
section_name t e
els Int
height | (n
section_name, t e
els) <- [(n, t e)]
elements]
, sectionListName :: n
sectionListName = n
name
}
sectionL :: Eq n => n -> Lens' (GenericSectionList n t e) (L.GenericList n t e)
sectionL :: forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
section_name = (GenericSectionList n t e -> GenericList n t e)
-> (GenericSectionList n t e
-> GenericList n t e -> GenericSectionList n t e)
-> Lens
(GenericSectionList n t e)
(GenericSectionList n t e)
(GenericList n t e)
(GenericList n t e)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GenericSectionList n t e -> GenericList n t e
forall {t :: * -> *} {e}.
GenericSectionList n t e -> GenericList n t e
g GenericSectionList n t e
-> GenericList n t e -> GenericSectionList n t e
forall {t :: * -> *} {e}.
GenericSectionList n t e
-> GenericList n t e -> GenericSectionList n t e
s
where is_section_name :: GenericList n t e -> Bool
is_section_name = (n -> n -> Bool
forall a. Eq a => a -> a -> Bool
== n
section_name) (n -> Bool)
-> (GenericList n t e -> n) -> GenericList n t e -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList n t e -> n
forall n (t :: * -> *) e. GenericList n t e -> n
L.listName
g :: GenericSectionList n t e -> GenericList n t e
g GenericSectionList n t e
section_list =
let elms :: Vector (GenericList n t e)
elms = GenericSectionList n t e
section_list GenericSectionList n t e
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (Vector (GenericList n t e))
-> Vector (GenericList n t e)
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx (GenericSectionList n t e) (Vector (GenericList n t e))
forall n (t :: * -> *) e (t :: * -> *) e.
Lens
(GenericSectionList n t e)
(GenericSectionList n t e)
(Vector (GenericList n t e))
(Vector (GenericList n t e))
sectionListElementsL
zeroth :: GenericList n t e
zeroth = Vector (GenericList n t e)
elms Vector (GenericList n t e) -> Int -> GenericList n t e
forall a. Vector a -> Int -> a
V.! Int
0
in GenericList n t e -> Maybe (GenericList n t e) -> GenericList n t e
forall a. a -> Maybe a -> a
fromMaybe GenericList n t e
zeroth ((GenericList n t e -> Bool)
-> Vector (GenericList n t e) -> Maybe (GenericList n t e)
forall a. (a -> Bool) -> Vector a -> Maybe a
V.find GenericList n t e -> Bool
forall {t :: * -> *} {e}. GenericList n t e -> Bool
is_section_name Vector (GenericList n t e)
elms)
s :: GenericSectionList n t e
-> GenericList n t e -> GenericSectionList n t e
s gl :: GenericSectionList n t e
gl@(GenericSectionList FocusRing n
_ Vector (GenericList n t e)
elms n
_) GenericList n t e
list =
case (GenericList n t e -> Bool)
-> Vector (GenericList n t e) -> Maybe Int
forall a. (a -> Bool) -> Vector a -> Maybe Int
V.findIndex GenericList n t e -> Bool
forall {t :: * -> *} {e}. GenericList n t e -> Bool
is_section_name Vector (GenericList n t e)
elms of
Maybe Int
Nothing -> GenericSectionList n t e
gl
Just Int
i -> let new_elms :: Vector (GenericList n t e)
new_elms = Vector (GenericList n t e)
-> Vector (Int, GenericList n t e) -> Vector (GenericList n t e)
forall a. Vector a -> Vector (Int, a) -> Vector a
V.update Vector (GenericList n t e)
elms ([(Int, GenericList n t e)] -> Vector (Int, GenericList n t e)
forall a. [a] -> Vector a
V.fromList [(Int
i, GenericList n t e
list)])
in GenericSectionList n t e
gl GenericSectionList n t e
-> (GenericSectionList n t e -> GenericSectionList n t e)
-> GenericSectionList n t e
forall a b. a -> (a -> b) -> b
& Lens
(GenericSectionList n t e)
(GenericSectionList n t e)
(Vector (GenericList n t e))
(Vector (GenericList n t e))
forall n (t :: * -> *) e (t :: * -> *) e.
Lens
(GenericSectionList n t e)
(GenericSectionList n t e)
(Vector (GenericList n t e))
(Vector (GenericList n t e))
sectionListElementsL Lens
(GenericSectionList n t e)
(GenericSectionList n t e)
(Vector (GenericList n t e))
(Vector (GenericList n t e))
-> Vector (GenericList n t e)
-> GenericSectionList n t e
-> GenericSectionList n t e
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Vector (GenericList n t e)
new_elms
moveDown :: (L.Splittable t, Ord n, Foldable t) => EventM n (GenericSectionList n t e) ()
moveDown :: forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveDown = do
FocusRing n
ring <- Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
-> EventM n (GenericSectionList n t e) (FocusRing n)
forall k s (m :: * -> *) (is :: IxList) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL
case FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent FocusRing n
ring of
Maybe n
Nothing -> () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just n
l -> do
GenericList n t e
current_list <- Optic' A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> EventM n (GenericSectionList n t e) (GenericList n t e)
forall k s (m :: * -> *) (is :: IxList) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use (n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
l)
let current_idx :: Maybe Int
current_idx = GenericList n t e -> Maybe Int
forall n (t :: * -> *) e. GenericList n t e -> Maybe Int
L.listSelected GenericList n t e
current_list
list_length :: Int
list_length = GenericList n t e
current_list GenericList n t e -> (GenericList n t e -> Int) -> Int
forall a b. a -> (a -> b) -> b
& GenericList n t e -> Int
forall a. GenericList n t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length
if Maybe Int
current_idx Maybe Int -> Maybe Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Maybe Int
forall a. a -> Maybe a
Just (Int
list_length Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
then do
FocusRing n
new_focus <- Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
-> (FocusRing n -> FocusRing n)
-> EventM
n (GenericSectionList n t e) (ViewResult A_Lens (FocusRing n))
forall k b s (m :: * -> *) (is :: IxList) a.
(PermeableOptic k b, MonadState s m) =>
Optic k is s s a b -> (a -> b) -> m (ViewResult k b)
<%= FocusRing n -> FocusRing n
forall n. FocusRing n -> FocusRing n
F.focusNext
case FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent FocusRing n
new_focus of
Maybe n
Nothing -> () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just n
new_l -> Optic' A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: IxList}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom (n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
new_l) ((GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
Brick.modify GenericList n t e -> GenericList n t e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
L.listMoveToBeginning)
else Optic' A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: IxList}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom (n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
l) (EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ())
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall a b. (a -> b) -> a -> b
$ (GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
Brick.modify GenericList n t e -> GenericList n t e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
L.listMoveDown
moveUp :: (L.Splittable t, Ord n, Foldable t) => EventM n (GenericSectionList n t e) ()
moveUp :: forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveUp = do
FocusRing n
ring <- Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
-> EventM n (GenericSectionList n t e) (FocusRing n)
forall k s (m :: * -> *) (is :: IxList) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL
case FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent FocusRing n
ring of
Maybe n
Nothing -> () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just n
l -> do
GenericList n t e
current_list <- Optic' A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> EventM n (GenericSectionList n t e) (GenericList n t e)
forall k s (m :: * -> *) (is :: IxList) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use (n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
l)
let current_idx :: Maybe Int
current_idx = GenericList n t e -> Maybe Int
forall n (t :: * -> *) e. GenericList n t e -> Maybe Int
L.listSelected GenericList n t e
current_list
if Maybe Int
current_idx Maybe Int -> Maybe Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
then do
FocusRing n
new_focus <- Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
-> (FocusRing n -> FocusRing n)
-> EventM
n (GenericSectionList n t e) (ViewResult A_Lens (FocusRing n))
forall k b s (m :: * -> *) (is :: IxList) a.
(PermeableOptic k b, MonadState s m) =>
Optic k is s s a b -> (a -> b) -> m (ViewResult k b)
<%= FocusRing n -> FocusRing n
forall n. FocusRing n -> FocusRing n
F.focusPrev
case FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent FocusRing n
new_focus of
Maybe n
Nothing -> () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just n
new_l -> Optic' A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: IxList}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom (n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
new_l) ((GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
Brick.modify GenericList n t e -> GenericList n t e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
L.listMoveToEnd)
else Optic' A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: IxList}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom (n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
l) (EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ())
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall a b. (a -> b) -> a -> b
$ (GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
Brick.modify GenericList n t e -> GenericList n t e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
L.listMoveUp
sectionListSelectItem :: (L.Splittable t, Eq n, ListItemSectionNameIndex n, Foldable t) => n -> EventM n (GenericSectionList n t e) ()
sectionListSelectItem :: forall (t :: * -> *) n e.
(Splittable t, Eq n, ListItemSectionNameIndex n, Foldable t) =>
n -> EventM n (GenericSectionList n t e) ()
sectionListSelectItem n
selectedItem = case n -> Maybe (n, Int)
forall n. ListItemSectionNameIndex n => n -> Maybe (n, Int)
getListItemSectionNameIndex n
selectedItem of
Maybe (n, Int)
Nothing -> () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just (n
secName, Int
ix) -> do
Lens' (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL Lens' (GenericSectionList n t e) (FocusRing n)
-> (FocusRing n -> FocusRing n)
-> EventM n (GenericSectionList n t e) ()
forall k s (m :: * -> *) (is :: IxList) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> (a -> b) -> m ()
%= n -> FocusRing n -> FocusRing n
forall n. Eq n => n -> FocusRing n -> FocusRing n
F.focusSetCurrent n
secName
Optic
A_Lens
NoIx
(GenericSectionList n t e)
(GenericSectionList n t e)
(GenericList n t e)
(GenericList n t e)
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: IxList}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom (n
-> Optic
A_Lens
NoIx
(GenericSectionList n t e)
(GenericSectionList n t e)
(GenericList n t e)
(GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
secName) ((GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
Brick.modify ((GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ())
-> (GenericList n t e -> GenericList n t e)
-> EventM n (GenericList n t e) ()
forall a b. (a -> b) -> a -> b
$ Int -> GenericList n t e -> GenericList n t e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
L.listMoveTo Int
ix)
handleGenericListEvent :: (Foldable t, L.Splittable t, Ord n, ListItemSectionNameIndex n)
=> BrickEvent n a
-> EventM n (GenericSectionList n t e) ()
handleGenericListEvent :: forall (t :: * -> *) n a e.
(Foldable t, Splittable t, Ord n, ListItemSectionNameIndex n) =>
BrickEvent n a -> EventM n (GenericSectionList n t e) ()
handleGenericListEvent (VtyEvent (Vty.EvResize Int
_ Int
_)) = () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
handleGenericListEvent (VtyEvent (Vty.EvKey (Vty.KChar Char
'\t') [])) = Lens' (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL Lens' (GenericSectionList n t e) (FocusRing n)
-> (FocusRing n -> FocusRing n)
-> EventM n (GenericSectionList n t e) ()
forall k s (m :: * -> *) (is :: IxList) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> (a -> b) -> m ()
%= FocusRing n -> FocusRing n
forall n. FocusRing n -> FocusRing n
F.focusNext
handleGenericListEvent (VtyEvent (Vty.EvKey Key
Vty.KBackTab [])) = Lens' (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL Lens' (GenericSectionList n t e) (FocusRing n)
-> (FocusRing n -> FocusRing n)
-> EventM n (GenericSectionList n t e) ()
forall k s (m :: * -> *) (is :: IxList) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> (a -> b) -> m ()
%= FocusRing n -> FocusRing n
forall n. FocusRing n -> FocusRing n
F.focusPrev
handleGenericListEvent (MouseDown n
n Button
Vty.BLeft [Modifier]
_ Location
_) = n -> EventM n (GenericSectionList n t e) ()
forall (t :: * -> *) n e.
(Splittable t, Eq n, ListItemSectionNameIndex n, Foldable t) =>
n -> EventM n (GenericSectionList n t e) ()
sectionListSelectItem n
n
handleGenericListEvent (MouseDown n
_ Button
Vty.BScrollDown [Modifier]
_ Location
_) = EventM n (GenericSectionList n t e) ()
forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveDown
handleGenericListEvent (MouseDown n
_ Button
Vty.BScrollUp [Modifier]
_ Location
_) = EventM n (GenericSectionList n t e) ()
forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveUp
handleGenericListEvent (VtyEvent (Vty.EvKey Key
Vty.KDown [])) = EventM n (GenericSectionList n t e) ()
forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveDown
handleGenericListEvent (VtyEvent (Vty.EvKey Key
Vty.KUp [])) = EventM n (GenericSectionList n t e) ()
forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveUp
handleGenericListEvent (VtyEvent Event
ev) = do
FocusRing n
ring <- Lens' (GenericSectionList n t e) (FocusRing n)
-> EventM n (GenericSectionList n t e) (FocusRing n)
forall k s (m :: * -> *) (is :: IxList) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use Lens' (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL
case FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent FocusRing n
ring of
Maybe n
Nothing -> () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just n
l -> Optic
A_Lens
NoIx
(GenericSectionList n t e)
(GenericSectionList n t e)
(GenericList n t e)
(GenericList n t e)
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: IxList}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom (n
-> Optic
A_Lens
NoIx
(GenericSectionList n t e)
(GenericSectionList n t e)
(GenericList n t e)
(GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
l) (EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ())
-> EventM n (GenericList n t e) ()
-> EventM n (GenericSectionList n t e) ()
forall a b. (a -> b) -> a -> b
$ Event -> EventM n (GenericList n t e) ()
forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n) =>
Event -> EventM n (GenericList n t e) ()
L.handleListEvent Event
ev
handleGenericListEvent BrickEvent n a
_ = () -> EventM n (GenericSectionList n t e) ()
forall a. a -> EventM n (GenericSectionList n t e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
renderSectionList :: forall n t e . (Traversable t, Ord n, Show n, Eq n, L.Splittable t, Semigroup (t e))
=> (Int -> Bool -> e -> Widget n)
-> Bool
-> GenericSectionList n t e
-> Widget n
renderSectionList :: forall n (t :: * -> *) e.
(Traversable t, Ord n, Show n, Eq n, Splittable t,
Semigroup (t e)) =>
(Int -> Bool -> e -> Widget n)
-> Bool -> GenericSectionList n t e -> Widget n
renderSectionList Int -> Bool -> e -> Widget n
renderElem Bool
sectionFocus ge :: GenericSectionList n t e
ge@(GenericSectionList FocusRing n
focus Vector (GenericList n t e)
elms n
slName) =
Size -> Size -> RenderM n (Result n) -> Widget n
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Brick.Widget Size
Brick.Greedy Size
Brick.Greedy (RenderM n (Result n) -> Widget n)
-> RenderM n (Result n) -> Widget n
forall a b. (a -> b) -> a -> b
$ Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
Brick.render (Widget n -> RenderM n (Result n))
-> Widget n -> RenderM n (Result n)
forall a b. (a -> b) -> a -> b
$ n -> ViewportType -> Widget n -> Widget n
forall n.
(Ord n, Show n) =>
n -> ViewportType -> Widget n -> Widget n
Brick.viewport n
slName ViewportType
Brick.Vertical (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
(Widget n -> Int -> GenericList n t e -> Widget n)
-> Widget n -> Vector (GenericList n t e) -> Widget n
forall a b. (a -> Int -> b -> a) -> a -> Vector b -> a
V.ifoldl' (\(!Widget n
accWidget) !Int
i GenericList n t e
list ->
let hasFocusList :: Bool
hasFocusList = GenericList n t e -> Bool
sectionIsFocused GenericList n t e
list
makeVisible :: Widget n -> Widget n
makeVisible = if Bool
hasFocusList then Location -> DisplayRegion -> Widget n -> Widget n
forall n. Location -> DisplayRegion -> Widget n -> Widget n
Brick.visibleRegion (DisplayRegion -> Location
Brick.Location (Int
c, Int
r)) (Int
1, Int
1) else Widget n -> Widget n
forall a. a -> a
id
appendBorder :: Widget n -> Widget n
appendBorder = if Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Widget n -> Widget n
forall a. a -> a
id else (Widget n
forall n. Widget n
hBorder Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<=>)
newWidget :: Widget n
newWidget = Widget n -> Widget n
forall {n}. Widget n -> Widget n
appendBorder (Widget n -> Widget n
forall {n}. Widget n -> Widget n
makeVisible (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Bool -> GenericList n t e -> Widget n
renderInnerList Bool
hasFocusList GenericList n t e
list)
in Widget n
accWidget Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<=> Widget n
newWidget
)
Widget n
forall n. Widget n
Brick.emptyWidget
Vector (GenericList n t e)
elms
where
sectionIsFocused :: L.GenericList n t e -> Bool
sectionIsFocused :: GenericList n t e -> Bool
sectionIsFocused GenericList n t e
l = Bool
sectionFocus Bool -> Bool -> Bool
&& (n -> Maybe n
forall a. a -> Maybe a
Just (GenericList n t e -> n
forall n (t :: * -> *) e. GenericList n t e -> n
L.listName GenericList n t e
l) Maybe n -> Maybe n -> Bool
forall a. Eq a => a -> a -> Bool
== FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent FocusRing n
focus)
renderInnerList :: Bool -> L.GenericList n t e -> Widget n
renderInnerList :: Bool -> GenericList n t e -> Widget n
renderInnerList Bool
hasFocus GenericList n t e
l = Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
Brick.vLimit (GenericList n t e -> Int
forall a. GenericList n t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length GenericList n t e
l) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ (Int -> Bool -> e -> Widget n)
-> Bool -> GenericList n t e -> Widget n
forall (t :: * -> *) n e.
(Traversable t, Splittable t, Ord n, Show n) =>
(Int -> Bool -> e -> Widget n)
-> Bool -> GenericList n t e -> Widget n
L.renderListWithIndex (\Int
i Bool
b -> Int -> Bool -> e -> Widget n
renderElem Int
i (Bool
b Bool -> Bool -> Bool
&& Bool
hasFocus)) Bool
hasFocus GenericList n t e
l
(Int
c, Int
r) :: (Int, Int) = case GenericSectionList n t e -> Maybe (Int, e)
forall n (t :: * -> *) e.
(Eq n, Splittable t, Traversable t, Semigroup (t e)) =>
GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement GenericSectionList n t e
ge of
Maybe (Int, e)
Nothing -> (Int
0, Int
0)
Just (Int
selElIx, e
_) -> (Int
0, Int
selElIx)
sectionListSelectedElement :: (Eq n, L.Splittable t, Traversable t, Semigroup (t e)) => GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement :: forall n (t :: * -> *) e.
(Eq n, Splittable t, Traversable t, Semigroup (t e)) =>
GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement GenericSectionList n t e
generic_section_list = do
n
current_focus <- GenericSectionList n t e
generic_section_list GenericSectionList n t e
-> Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
-> FocusRing n
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx (GenericSectionList n t e) (FocusRing n)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL FocusRing n -> (FocusRing n -> Maybe n) -> Maybe n
forall a b. a -> (a -> b) -> b
& FocusRing n -> Maybe n
forall n. FocusRing n -> Maybe n
F.focusGetCurrent
let current_section :: GenericList n t e
current_section = GenericSectionList n t e
generic_section_list GenericSectionList n t e
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
-> GenericList n t e
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. n
-> Optic'
A_Lens NoIx (GenericSectionList n t e) (GenericList n t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL n
current_focus
GenericList n t e -> Maybe (Int, e)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement GenericList n t e
current_section