module EVM.TTYCenteredList where
import Control.Lens
import Data.Maybe (fromMaybe)
import Brick.Types
import Brick.Widgets.Core
import Brick.Widgets.List
import qualified Data.Vector as V
renderList :: (Ord n, Show n)
=> (Bool -> e -> Widget n)
-> Bool
-> List n e
-> Widget n
renderList :: (Bool -> e -> Widget n) -> Bool -> List n e -> Widget n
renderList drawElem :: Bool -> e -> Widget n
drawElem foc :: Bool
foc l :: List n e
l =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
listAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
Bool -> List n e -> (Bool -> e -> Widget n) -> Widget n
forall n e.
(Ord n, Show n) =>
Bool -> List n e -> (Bool -> e -> Widget n) -> Widget n
drawListElements Bool
foc List n e
l Bool -> e -> Widget n
drawElem
drawListElements :: (Ord n, Show n) => Bool -> List n e -> (Bool -> e -> Widget n) -> Widget n
drawListElements :: Bool -> List n e -> (Bool -> e -> Widget n) -> Widget n
drawListElements foc :: Bool
foc l :: List n e
l drawElem :: Bool -> e -> Widget n
drawElem =
Size -> Size -> RenderM n (Result n) -> Widget n
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy Size
Greedy (RenderM n (Result n) -> Widget n)
-> RenderM n (Result n) -> Widget n
forall a b. (a -> b) -> a -> b
$ do
Context
c <- RenderM n Context
forall n. RenderM n Context
getContext
let es :: Vector e
es = Int -> Int -> Vector e -> Vector e
forall a. Int -> Int -> Vector a -> Vector a
V.slice Int
start Int
num (List n e
lList n e -> Getting (Vector e) (List n e) (Vector e) -> Vector e
forall s a. s -> Getting a s a -> a
^.Getting (Vector e) (List n e) (Vector e)
forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
listElementsL)
idx :: Int
idx = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe 0 (List n e
lList n e -> Getting (Maybe Int) (List n e) (Maybe Int) -> Maybe Int
forall s a. s -> Getting a s a -> a
^.Getting (Maybe Int) (List n e) (Maybe Int)
forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
listSelectedL)
start :: Int
start = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max 0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
initialNumPerHeight Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` 2)
num :: Int
num = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int
numPerHeight Int -> Int -> Int
forall a. Num a => a -> a -> a
* 2) (Vector e -> Int
forall a. Vector a -> Int
V.length (List n e
lList n e -> Getting (Vector e) (List n e) (Vector e) -> Vector e
forall s a. s -> Getting a s a -> a
^.Getting (Vector e) (List n e) (Vector e)
forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
listElementsL) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
start)
initialNumPerHeight :: Int
initialNumPerHeight = (Context
cContext -> Getting Int Context Int -> Int
forall s a. s -> Getting a s a -> a
^.Getting Int Context Int
Lens' Context Int
availHeightL) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` (List n e
lList n e -> Getting Int (List n e) Int -> Int
forall s a. s -> Getting a s a -> a
^.Getting Int (List n e) Int
forall n (t :: * -> *) e. Lens' (GenericList n t e) Int
listItemHeightL)
numPerHeight :: Int
numPerHeight = Int
initialNumPerHeight Int -> Int -> Int
forall a. Num a => a -> a -> a
+
if Int
initialNumPerHeight Int -> Int -> Int
forall a. Num a => a -> a -> a
* (List n e
lList n e -> Getting Int (List n e) Int -> Int
forall s a. s -> Getting a s a -> a
^.Getting Int (List n e) Int
forall n (t :: * -> *) e. Lens' (GenericList n t e) Int
listItemHeightL) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Context
cContext -> Getting Int Context Int -> Int
forall s a. s -> Getting a s a -> a
^.Getting Int Context Int
Lens' Context Int
availHeightL
then 0
else 1
drawnElements :: Vector (Widget n)
drawnElements = ((Int -> e -> Widget n) -> Vector e -> Vector (Widget n))
-> Vector e -> (Int -> e -> Widget n) -> Vector (Widget n)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> e -> Widget n) -> Vector e -> Vector (Widget n)
forall a b. (Int -> a -> b) -> Vector a -> Vector b
V.imap Vector e
es ((Int -> e -> Widget n) -> Vector (Widget n))
-> (Int -> e -> Widget n) -> Vector (Widget n)
forall a b. (a -> b) -> a -> b
$ \i :: Int
i e :: e
e ->
let isSelected :: Bool
isSelected = Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (if Int
start Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0 then Int
idx else Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
initialNumPerHeight 2)
elemWidget :: Widget n
elemWidget = Bool -> e -> Widget n
drawElem Bool
isSelected e
e
selItemAttr :: Widget n -> Widget n
selItemAttr = if Bool
foc
then AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
listSelectedFocusedAttr
else AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
listSelectedAttr
makeVisible :: Widget n -> Widget n
makeVisible = if Bool
isSelected
then Widget n -> Widget n
forall n. Widget n -> Widget n
visible (Widget n -> Widget n)
-> (Widget n -> Widget n) -> Widget n -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Widget n -> Widget n
selItemAttr
else Widget n -> Widget n
forall a. a -> a
id
in Widget n -> Widget n
makeVisible Widget n
elemWidget
Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
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
viewport (List n e
lList n e -> Getting n (List n e) n -> n
forall s a. s -> Getting a s a -> a
^.Getting n (List n e) n
forall n1 (t :: * -> *) e n2.
Lens (GenericList n1 t e) (GenericList n2 t e) n1 n2
listNameL) ViewportType
Vertical (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
[Widget n] -> Widget n
forall n. [Widget n] -> Widget n
vBox ([Widget n] -> Widget n) -> [Widget n] -> Widget n
forall a b. (a -> b) -> a -> b
$ Vector (Widget n) -> [Widget n]
forall a. Vector a -> [a]
V.toList Vector (Widget n)
drawnElements