{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TypeApplications #-}
module Brick.Widgets.TabularList.Grid (
GridRowCtxt(..)
, GridColCtxt(..)
, GridCtxt(..)
, GridColHdr(..)
, GridRenderers(..)
, GridTabularList(..)
, gridTabularList
, renderGridTabularList
, gridMoveLeft
, gridMoveRight
, gridMoveTo
, gridMoveToBeginning
, gridMoveToEnd
, gridMovePageUp
, gridMovePageDown
, handleGridListEvent
, handleGridListEventVi
, module Brick.Widgets.TabularList.Types
) where
import Brick.Widgets.TabularList.Types
import Brick.Widgets.TabularList.Internal.Common
import Brick.Widgets.TabularList.Internal.Lens
import GHC.Generics (Generic)
import Data.Foldable (toList)
import Control.Monad (unless)
import Optics.Core ( (&), (%), (%~), (.~), (^.), coercedTo )
import qualified Data.Sequence as S
import Data.Sequence (Seq(..))
import Data.Generics.Labels
import qualified Brick.Widgets.List as L
import Brick.Types
import Brick.Widgets.Core
import Graphics.Vty (Event(..), Key(..), Modifier(..))
import Brick.Main (lookupViewport)
data GridRowCtxt = GRowC {
GridRowCtxt -> Index
index :: Index
, GridRowCtxt -> Selected
selected :: Selected
} deriving (GridRowCtxt -> GridRowCtxt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GridRowCtxt -> GridRowCtxt -> Bool
$c/= :: GridRowCtxt -> GridRowCtxt -> Bool
== :: GridRowCtxt -> GridRowCtxt -> Bool
$c== :: GridRowCtxt -> GridRowCtxt -> Bool
Eq, forall x. Rep GridRowCtxt x -> GridRowCtxt
forall x. GridRowCtxt -> Rep GridRowCtxt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GridRowCtxt x -> GridRowCtxt
$cfrom :: forall x. GridRowCtxt -> Rep GridRowCtxt x
Generic, Int -> GridRowCtxt -> ShowS
[GridRowCtxt] -> ShowS
GridRowCtxt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GridRowCtxt] -> ShowS
$cshowList :: [GridRowCtxt] -> ShowS
show :: GridRowCtxt -> String
$cshow :: GridRowCtxt -> String
showsPrec :: Int -> GridRowCtxt -> ShowS
$cshowsPrec :: Int -> GridRowCtxt -> ShowS
Show)
data GridColCtxt = GColC {
GridColCtxt -> Index
index :: Index
, GridColCtxt -> Selected
selected :: Selected
} deriving (GridColCtxt -> GridColCtxt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GridColCtxt -> GridColCtxt -> Bool
$c/= :: GridColCtxt -> GridColCtxt -> Bool
== :: GridColCtxt -> GridColCtxt -> Bool
$c== :: GridColCtxt -> GridColCtxt -> Bool
Eq, forall x. Rep GridColCtxt x -> GridColCtxt
forall x. GridColCtxt -> Rep GridColCtxt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GridColCtxt x -> GridColCtxt
$cfrom :: forall x. GridColCtxt -> Rep GridColCtxt x
Generic, Int -> GridColCtxt -> ShowS
[GridColCtxt] -> ShowS
GridColCtxt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GridColCtxt] -> ShowS
$cshowList :: [GridColCtxt] -> ShowS
show :: GridColCtxt -> String
$cshow :: GridColCtxt -> String
showsPrec :: Int -> GridColCtxt -> ShowS
$cshowsPrec :: Int -> GridColCtxt -> ShowS
Show)
data GridCtxt = GrdCtxt {
GridCtxt -> GridRowCtxt
row :: GridRowCtxt
, GridCtxt -> GridColCtxt
col :: GridColCtxt
} deriving (GridCtxt -> GridCtxt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GridCtxt -> GridCtxt -> Bool
$c/= :: GridCtxt -> GridCtxt -> Bool
== :: GridCtxt -> GridCtxt -> Bool
$c== :: GridCtxt -> GridCtxt -> Bool
Eq, forall x. Rep GridCtxt x -> GridCtxt
forall x. GridCtxt -> Rep GridCtxt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GridCtxt x -> GridCtxt
$cfrom :: forall x. GridCtxt -> Rep GridCtxt x
Generic, Int -> GridCtxt -> ShowS
[GridCtxt] -> ShowS
GridCtxt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GridCtxt] -> ShowS
$cshowList :: [GridCtxt] -> ShowS
show :: GridCtxt -> String
$cshow :: GridCtxt -> String
showsPrec :: Int -> GridCtxt -> ShowS
$cshowsPrec :: Int -> GridCtxt -> ShowS
Show)
data GridColHdr n = GridColHdr {
forall n.
GridColHdr n
-> ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
draw :: ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
, forall n. GridColHdr n -> ColHdrHeight
height :: ColHdrHeight
} deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (GridColHdr n) x -> GridColHdr n
forall n x. GridColHdr n -> Rep (GridColHdr n) x
$cto :: forall n x. Rep (GridColHdr n) x -> GridColHdr n
$cfrom :: forall n x. GridColHdr n -> Rep (GridColHdr n) x
Generic
data GridRenderers n e = GridRenderers {
forall n e.
GridRenderers n e
-> ListFocused -> WidthDeficit -> GridCtxt -> e -> Widget n
cell :: ListFocused -> WidthDeficit -> GridCtxt -> e -> Widget n
, forall n e. GridRenderers n e -> Maybe (RowHdr n e)
rowHdr :: Maybe (RowHdr n e)
, forall n e. GridRenderers n e -> Maybe (GridColHdr n)
colHdr :: Maybe (GridColHdr n)
, forall n e. GridRenderers n e -> Maybe (ColHdrRowHdr n)
colHdrRowHdr :: Maybe (ColHdrRowHdr n)
} deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n e x. Rep (GridRenderers n e) x -> GridRenderers n e
forall n e x. GridRenderers n e -> Rep (GridRenderers n e) x
$cto :: forall n e x. Rep (GridRenderers n e) x -> GridRenderers n e
$cfrom :: forall n e x. GridRenderers n e -> Rep (GridRenderers n e) x
Generic
data GridTabularList n e = GridTabularList {
forall n e. GridTabularList n e -> GenericList n Seq e
list :: L.GenericList n Seq e
, forall n e. GridTabularList n e -> Seq ColWidth
widths :: Seq ColWidth
, forall n e. GridTabularList n e -> Index
currentColumn :: Index
} deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n e x. Rep (GridTabularList n e) x -> GridTabularList n e
forall n e x. GridTabularList n e -> Rep (GridTabularList n e) x
$cto :: forall n e x. Rep (GridTabularList n e) x -> GridTabularList n e
$cfrom :: forall n e x. GridTabularList n e -> Rep (GridTabularList n e) x
Generic
gridTabularList
:: n
-> Seq e
-> ListItemHeight
-> Seq ColWidth
-> GridTabularList n e
gridTabularList :: forall n e.
n -> Seq e -> ListItemHeight -> Seq ColWidth -> GridTabularList n e
gridTabularList n
n Seq e
rows (LstItmH Int
h) Seq ColWidth
widths = GridTabularList {
$sel:list:GridTabularList :: GenericList n Seq e
list = forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
L.list n
n Seq e
rows Int
h
, $sel:widths:GridTabularList :: Seq ColWidth
widths = Seq ColWidth
widths
, $sel:currentColumn:GridTabularList :: Index
currentColumn = Int -> Index
Ix Int
0
}
newtype AccWidth = AccW Int deriving (AccWidth -> AccWidth -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccWidth -> AccWidth -> Bool
$c/= :: AccWidth -> AccWidth -> Bool
== :: AccWidth -> AccWidth -> Bool
$c== :: AccWidth -> AccWidth -> Bool
Eq, Int -> AccWidth -> ShowS
[AccWidth] -> ShowS
AccWidth -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccWidth] -> ShowS
$cshowList :: [AccWidth] -> ShowS
show :: AccWidth -> String
$cshow :: AccWidth -> String
showsPrec :: Int -> AccWidth -> ShowS
$cshowsPrec :: Int -> AccWidth -> ShowS
Show)
data VisibleGridColumns =
NoColumn |
CurrentColumn |
AnchoredLeft {
VisibleGridColumns -> Index
right :: Index
} |
MiddleColumns {
VisibleGridColumns -> Index
left :: Index,
right :: Index,
VisibleGridColumns -> Int
offset :: Int,
VisibleGridColumns -> AccWidth
tW :: AccWidth
} |
AnchoredRight {
left :: Index,
offset :: Int,
tW :: AccWidth
}
deriving (VisibleGridColumns -> VisibleGridColumns -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VisibleGridColumns -> VisibleGridColumns -> Bool
$c/= :: VisibleGridColumns -> VisibleGridColumns -> Bool
== :: VisibleGridColumns -> VisibleGridColumns -> Bool
$c== :: VisibleGridColumns -> VisibleGridColumns -> Bool
Eq, Int -> VisibleGridColumns -> ShowS
[VisibleGridColumns] -> ShowS
VisibleGridColumns -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VisibleGridColumns] -> ShowS
$cshowList :: [VisibleGridColumns] -> ShowS
show :: VisibleGridColumns -> String
$cshow :: VisibleGridColumns -> String
showsPrec :: Int -> VisibleGridColumns -> ShowS
$cshowsPrec :: Int -> VisibleGridColumns -> ShowS
Show)
visibleGridColumns :: GridTabularList n e -> AvailWidth -> VisibleGridColumns
visibleGridColumns :: forall n e. GridTabularList n e -> AvailWidth -> VisibleGridColumns
visibleGridColumns GridTabularList n e
l (AvlW Int
aW) = let
(Ix Int
curCol) = GridTabularList n e
l forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "currentColumn" a => a
#currentColumn
ws :: Seq ColWidth
ws = GridTabularList n e
l forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "widths" a => a
#widths
in case forall a. Int -> Seq a -> (Seq a, Seq a)
S.splitAt Int
curCol Seq ColWidth
ws of
(Seq ColWidth
_, Seq ColWidth
Empty) -> VisibleGridColumns
NoColumn
(Seq ColWidth
left, ColW Int
cW :<| Seq ColWidth
right) -> if Int
aW forall a. Ord a => a -> a -> Bool
<= Int
0
then VisibleGridColumns
NoColumn
else if Int
aW forall a. Ord a => a -> a -> Bool
<= Int
cW
then VisibleGridColumns
CurrentColumn
else let
lW :: Int
lW = (Int
aW forall a. Num a => a -> a -> a
- Int
cW) forall a. Integral a => a -> a -> a
`div` Int
2
rW :: Int
rW = Int
aW forall a. Num a => a -> a -> a
- Int
lW forall a. Num a => a -> a -> a
- Int
cW
leftForMiddle :: Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
leftForMiddle (Seq ColWidth
l :|> ColW Int
w) (Ix Int
idx) (AccW Int
accW) = if Int
accWforall a. Num a => a -> a -> a
+Int
w forall a. Ord a => a -> a -> Bool
< Int
lW
then Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
leftForMiddle Seq ColWidth
l (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
idxforall a. Num a => a -> a -> a
-Int
1) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
w)
else Index
-> AccWidth
-> Seq ColWidth
-> Index
-> AccWidth
-> VisibleGridColumns
rightForMiddle (Int -> Index
Ix Int
idx) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
w) Seq ColWidth
right (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
curCol forall a. Num a => a -> a -> a
+ Int
1) (Int -> AccWidth
AccW Int
0)
leftForMiddle Seq ColWidth
Empty Index
_ (AccW Int
accW) = Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
rightForLeft Seq ColWidth
right (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
curColforall a. Num a => a -> a -> a
+Int
1) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
cW)
rightForMiddle :: Index
-> AccWidth
-> Seq ColWidth
-> Index
-> AccWidth
-> VisibleGridColumns
rightForMiddle (Ix Int
li) (AccW Int
lAccW) (ColW Int
w :<| Seq ColWidth
r) (Ix Int
ri) (AccW Int
accW) = if Int
accWforall a. Num a => a -> a -> a
+Int
w forall a. Ord a => a -> a -> Bool
< Int
rW
then Index
-> AccWidth
-> Seq ColWidth
-> Index
-> AccWidth
-> VisibleGridColumns
rightForMiddle (Int -> Index
Ix Int
li) (Int -> AccWidth
AccW Int
lAccW) Seq ColWidth
r (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
riforall a. Num a => a -> a -> a
+Int
1) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
w)
else MiddleColumns { $sel:left:NoColumn :: Index
left = Int -> Index
Ix Int
li, $sel:right:NoColumn :: Index
right = Int -> Index
Ix Int
ri, $sel:offset:NoColumn :: Int
offset = Int
lAccWforall a. Num a => a -> a -> a
-Int
lW, $sel:tW:NoColumn :: AccWidth
tW = Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
lAccWforall a. Num a => a -> a -> a
+Int
cWforall a. Num a => a -> a -> a
+Int
accWforall a. Num a => a -> a -> a
+Int
w }
rightForMiddle Index
_ AccWidth
_ Seq ColWidth
Empty Index
_ (AccW Int
accW) = Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
leftForRight Seq ColWidth
left (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
curColforall a. Num a => a -> a -> a
-Int
1) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
cW)
rightForLeft :: Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
rightForLeft (ColW Int
w :<| Seq ColWidth
r) (Ix Int
idx) (AccW Int
accW) = if Int
accWforall a. Num a => a -> a -> a
+Int
w forall a. Ord a => a -> a -> Bool
< Int
aW
then Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
rightForLeft Seq ColWidth
r (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
idxforall a. Num a => a -> a -> a
+Int
1) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
w)
else Index -> VisibleGridColumns
AnchoredLeft forall a b. (a -> b) -> a -> b
$ Int -> Index
Ix Int
idx
rightForLeft Seq ColWidth
Empty (Ix Int
idx) AccWidth
_ = Index -> VisibleGridColumns
AnchoredLeft (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
idxforall a. Num a => a -> a -> a
-Int
1)
leftForRight :: Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
leftForRight (Seq ColWidth
l :|> ColW Int
w) (Ix Int
idx) (AccW Int
accW) = if Int
accWforall a. Num a => a -> a -> a
+Int
w forall a. Ord a => a -> a -> Bool
< Int
aW
then Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
leftForRight Seq ColWidth
l (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
idxforall a. Num a => a -> a -> a
-Int
1) (Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
w)
else AnchoredRight { $sel:left:NoColumn :: Index
left = Int -> Index
Ix Int
idx, $sel:offset:NoColumn :: Int
offset = Int
accWforall a. Num a => a -> a -> a
+Int
wforall a. Num a => a -> a -> a
-Int
aW, $sel:tW:NoColumn :: AccWidth
tW = Int -> AccWidth
AccW forall a b. (a -> b) -> a -> b
$ Int
accWforall a. Num a => a -> a -> a
+Int
w }
leftForRight Seq ColWidth
Empty Index
_ AccWidth
_ = Index -> VisibleGridColumns
AnchoredLeft forall a b. (a -> b) -> a -> b
$ Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length Seq ColWidth
ws forall a. Num a => a -> a -> a
- Int
1
in Seq ColWidth -> Index -> AccWidth -> VisibleGridColumns
leftForMiddle Seq ColWidth
left (Int -> Index
Ix forall a b. (a -> b) -> a -> b
$ Int
curColforall a. Num a => a -> a -> a
-Int
1) (Int -> AccWidth
AccW Int
0)
newtype Height = H Int deriving (Height -> Height -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Height -> Height -> Bool
$c/= :: Height -> Height -> Bool
== :: Height -> Height -> Bool
$c== :: Height -> Height -> Bool
Eq, Int -> Height -> ShowS
[Height] -> ShowS
Height -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Height] -> ShowS
$cshowList :: [Height] -> ShowS
show :: Height -> String
$cshow :: Height -> String
showsPrec :: Int -> Height -> ShowS
$cshowsPrec :: Int -> Height -> ShowS
Show)
renderGridColumns
:: GridTabularList n e
-> VisibleGridColumns
-> (WidthDeficit -> Index -> ColWidth -> Widget n)
-> Height
-> Widget n
renderGridColumns :: forall n e.
GridTabularList n e
-> VisibleGridColumns
-> (WidthDeficit -> Index -> ColWidth -> Widget n)
-> Height
-> Widget n
renderGridColumns GridTabularList n e
l VisibleGridColumns
vCs WidthDeficit -> Index -> ColWidth -> Widget n
dC (H Int
h) = forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy Size
Fixed forall a b. (a -> b) -> a -> b
$ do
Context n
c <- forall n. RenderM n (Context n)
getContext
let cWs :: Seq ColWidth
cWs = GridTabularList n e
l forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "widths" a => a
#widths
Ix Int
curCol = GridTabularList n e
l forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "currentColumn" a => a
#currentColumn
aW :: Int
aW = Context n
cforall {s} {a}. s -> Getting a s a -> a
^^.forall n. Lens' (Context n) Int
availWidthL
forall n. Widget n -> RenderM n (Result n)
render forall a b. (a -> b) -> a -> b
$ case VisibleGridColumns
vCs of
VisibleGridColumns
NoColumn -> forall n. Widget n
emptyWidget
VisibleGridColumns
CurrentColumn -> case forall a. Int -> Seq a -> Maybe a
S.lookup Int
curCol Seq ColWidth
cWs of
Maybe ColWidth
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Current column, " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Int
curCol forall a. Semigroup a => a -> a -> a
<> String
" is outside the boundary of column widths."
Just (ColW Int
cW) -> WidthDeficit -> Index -> ColWidth -> Widget n
dC (Int -> WidthDeficit
WdthD forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Int
cW forall a. Num a => a -> a -> a
- Int
aW) (Int -> Index
Ix Int
curCol) (Int -> ColWidth
ColW Int
aW)
AnchoredLeft {$sel:right:NoColumn :: VisibleGridColumns -> Index
right=Ix Int
r} -> forall n. [Widget n] -> Widget n
hBox forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (WidthDeficit -> Index -> ColWidth -> Widget n
dC forall a b. (a -> b) -> a -> b
$ Int -> WidthDeficit
WdthD Int
0) [Int -> Index
Ix Int
0..] forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. Int -> Seq a -> Seq a
S.take (Int
rforall a. Num a => a -> a -> a
+Int
1) Seq ColWidth
cWs
MiddleColumns {$sel:left:NoColumn :: VisibleGridColumns -> Index
left=Ix Int
l, $sel:right:NoColumn :: VisibleGridColumns -> Index
right=Ix Int
r, Int
offset :: Int
$sel:offset:NoColumn :: VisibleGridColumns -> Int
offset, $sel:tW:NoColumn :: VisibleGridColumns -> AccWidth
tW=AccW Int
tw} -> forall n. Int -> Widget n -> Widget n
cropLeftBy Int
offset forall a b. (a -> b) -> a -> b
$ forall n. (Int, Int) -> Widget n -> Widget n
sz (Int
tw, Int
h) forall a b. (a -> b) -> a -> b
$
forall n. [Widget n] -> Widget n
hBox forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (WidthDeficit -> Index -> ColWidth -> Widget n
dC forall a b. (a -> b) -> a -> b
$ Int -> WidthDeficit
WdthD Int
0) [Int -> Index
Ix Int
l..] forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. Int -> Seq a -> Seq a
S.take (Int
rforall a. Num a => a -> a -> a
-Int
lforall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ forall a. Int -> Seq a -> Seq a
S.drop Int
l Seq ColWidth
cWs
AnchoredRight {$sel:left:NoColumn :: VisibleGridColumns -> Index
left=Ix Int
l, Int
offset :: Int
$sel:offset:NoColumn :: VisibleGridColumns -> Int
offset, $sel:tW:NoColumn :: VisibleGridColumns -> AccWidth
tW=AccW Int
tw} -> forall n. Int -> Widget n -> Widget n
cropLeftBy Int
offset forall a b. (a -> b) -> a -> b
$ forall n. (Int, Int) -> Widget n -> Widget n
sz (Int
tw, Int
h) forall a b. (a -> b) -> a -> b
$
forall n. [Widget n] -> Widget n
hBox forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (WidthDeficit -> Index -> ColWidth -> Widget n
dC forall a b. (a -> b) -> a -> b
$ Int -> WidthDeficit
WdthD Int
0) [Int -> Index
Ix Int
l..] forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. Int -> Seq a -> Seq a
S.drop Int
l Seq ColWidth
cWs
renderGridTabularList :: (Ord n, Show n)
=> GridRenderers n e
-> ListFocused
-> GridTabularList n e
-> Widget n
renderGridTabularList :: forall n e.
(Ord n, Show n) =>
GridRenderers n e -> ListFocused -> GridTabularList n e -> Widget n
renderGridTabularList GridRenderers n e
r (LstFcs Bool
f) GridTabularList n e
l = forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy Size
Greedy forall a b. (a -> b) -> a -> b
$ do
Context n
c <- forall n. RenderM n (Context n)
getContext
let aW :: Int
aW = Context n
cforall {s} {a}. s -> Getting a s a -> a
^^.forall n. Lens' (Context n) Int
availWidthL
aH :: Int
aH = Context n
cforall {s} {a}. s -> Getting a s a -> a
^^.forall n. Lens' (Context n) Int
availHeightL
cell :: ListFocused -> WidthDeficit -> GridCtxt -> e -> Widget n
cell = GridRenderers n e
r forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "cell" a => a
#cell
GridTabularList {$sel:list:GridTabularList :: forall n e. GridTabularList n e -> GenericList n Seq e
list=GenericList n Seq e
l', $sel:currentColumn:GridTabularList :: forall n e. GridTabularList n e -> Index
currentColumn=Index
curCol} = GridTabularList n e
l
iH :: Int
iH = GenericList n Seq e
l' forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "listItemHeight" a => a
#listItemHeight
colHdrRow :: VisibleGridColumns -> RowHdrWidth -> WidthDeficit -> Widget n
colHdrRow VisibleGridColumns
vCs (RowHdrW Int
rhw) (WdthD Int
rhwd) = case GridRenderers n e
r forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "colHdr" a => a
#colHdr of
Maybe (GridColHdr n)
Nothing -> forall n. Widget n
emptyWidget
Just (GridColHdr {ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
draw :: ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
$sel:draw:GridColHdr :: forall n.
GridColHdr n
-> ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
draw, $sel:height:GridColHdr :: forall n. GridColHdr n -> ColHdrHeight
height=ColHdrH Int
chh}) -> let
col :: WidthDeficit -> Index -> ColWidth -> Widget n
col WidthDeficit
wd Index
c (ColW Int
w) = forall n. (Int, Int) -> Widget n -> Widget n
sz (Int
w, Int
chh) forall a b. (a -> b) -> a -> b
$ ListFocused -> WidthDeficit -> GridColCtxt -> Widget n
draw (Bool -> ListFocused
LstFcs Bool
f) WidthDeficit
wd forall a b. (a -> b) -> a -> b
$ Index -> Selected -> GridColCtxt
GColC Index
c forall a b. (a -> b) -> a -> b
$ Bool -> Selected
Sel (Index
c forall a. Eq a => a -> a -> Bool
== Index
curCol)
chrh :: Widget n
chrh = case GridRenderers n e
r forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "colHdrRowHdr" a => a
#colHdrRowHdr of
Maybe (ColHdrRowHdr n)
Nothing -> forall n. Char -> Widget n
fill Char
' '
Just (ColHdrRowHdr ListFocused -> WidthDeficit -> Widget n
chrh) -> ListFocused -> WidthDeficit -> Widget n
chrh (Bool -> ListFocused
LstFcs Bool
f) (Int -> WidthDeficit
WdthD Int
rhwd)
in forall n. (Int, Int) -> Widget n -> Widget n
sz (Int
rhw, Int
chh) Widget n
chrh forall n. Widget n -> Widget n -> Widget n
<+> forall n e.
GridTabularList n e
-> VisibleGridColumns
-> (WidthDeficit -> Index -> ColWidth -> Widget n)
-> Height
-> Widget n
renderGridColumns GridTabularList n e
l VisibleGridColumns
vCs WidthDeficit -> Index -> ColWidth -> Widget n
col (Int -> Height
H Int
chh)
row :: VisibleGridColumns -> Int -> Bool -> e -> Widget n
row VisibleGridColumns
vCs Int
i Bool
f e
r = let
col :: WidthDeficit -> Index -> ColWidth -> Widget n
col WidthDeficit
wd Index
c (ColW Int
w) = let gc :: GridCtxt
gc = GridRowCtxt -> GridColCtxt -> GridCtxt
GrdCtxt (Index -> Selected -> GridRowCtxt
GRowC (Int -> Index
Ix Int
i) (Bool -> Selected
Sel Bool
f)) forall a b. (a -> b) -> a -> b
$ Index -> Selected -> GridColCtxt
GColC Index
c forall a b. (a -> b) -> a -> b
$ Bool -> Selected
Sel (Index
c forall a. Eq a => a -> a -> Bool
== Index
curCol)
in forall n. (Int, Int) -> Widget n -> Widget n
sz (Int
w, Int
iH) forall a b. (a -> b) -> a -> b
$ ListFocused -> WidthDeficit -> GridCtxt -> e -> Widget n
cell (Bool -> ListFocused
LstFcs Bool
f) WidthDeficit
wd GridCtxt
gc e
r
in forall n e.
GridTabularList n e
-> VisibleGridColumns
-> (WidthDeficit -> Index -> ColWidth -> Widget n)
-> Height
-> Widget n
renderGridColumns GridTabularList n e
l VisibleGridColumns
vCs WidthDeficit -> Index -> ColWidth -> Widget n
col (Int -> Height
H Int
iH)
lst :: RenderM n (Result n)
lst = let vCs :: VisibleGridColumns
vCs = forall n e. GridTabularList n e -> AvailWidth -> VisibleGridColumns
visibleGridColumns GridTabularList n e
l (Int -> AvailWidth
AvlW Int
aW) in
forall n. Widget n -> RenderM n (Result n)
render forall a b. (a -> b) -> a -> b
$ VisibleGridColumns -> RowHdrWidth -> WidthDeficit -> Widget n
colHdrRow VisibleGridColumns
vCs (Int -> RowHdrWidth
RowHdrW Int
0) (Int -> WidthDeficit
WdthD Int
0) forall n. Widget n -> Widget n -> 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 (VisibleGridColumns -> Int -> Bool -> e -> Widget n
row VisibleGridColumns
vCs) Bool
f GenericList n Seq e
l'
hdrLst :: RowHdr n e -> RenderM n (Result n)
hdrLst (RowHdr {$sel:draw:RowHdr :: ()
draw=ListFocused -> WidthDeficit -> RowHdrCtxt -> r -> Widget n
drw, AvailWidth -> [r] -> RowHdrWidth
$sel:width:RowHdr :: ()
width :: AvailWidth -> [r] -> RowHdrWidth
width, $sel:toRH:RowHdr :: ()
toRH=e -> Index -> r
tR}) = let
RowHdrW Int
rhw' = AvailWidth -> [r] -> RowHdrWidth
width (Int -> AvailWidth
AvlW Int
aW) forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith e -> Index -> r
tR) forall a b. (a -> b) -> a -> b
$ forall n e. GenericList n Seq e -> AvailHeight -> ([e], [Index])
visibleRowIdx GenericList n Seq e
l' (Int -> AvailHeight
AvlH Int
aH)
rhw :: Int
rhw = forall a. Ord a => a -> a -> a
min Int
rhw' Int
aW
rhwd :: WidthDeficit
rhwd = Int -> WidthDeficit
WdthD forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Int
rhw' forall a. Num a => a -> a -> a
- Int
aW
vCs :: VisibleGridColumns
vCs = forall n e. GridTabularList n e -> AvailWidth -> VisibleGridColumns
visibleGridColumns GridTabularList n e
l forall a b. (a -> b) -> a -> b
$ Int -> AvailWidth
AvlW forall a b. (a -> b) -> a -> b
$ Int
aW forall a. Num a => a -> a -> a
- Int
rhw
hdrRow :: Int -> Bool -> e -> Widget n
hdrRow Int
i Bool
f e
r = forall n. (Int, Int) -> Widget n -> Widget n
sz (Int
rhw, Int
iH) (ListFocused -> WidthDeficit -> RowHdrCtxt -> r -> Widget n
drw (Bool -> ListFocused
LstFcs Bool
f) WidthDeficit
rhwd (Selected -> RowHdrCtxt
RowHdrCtxt forall a b. (a -> b) -> a -> b
$ Bool -> Selected
Sel Bool
f) forall a b. (a -> b) -> a -> b
$ e -> Index -> r
tR e
r (Int -> Index
Ix Int
i)) forall n. Widget n -> Widget n -> Widget n
<+> VisibleGridColumns -> Int -> Bool -> e -> Widget n
row VisibleGridColumns
vCs Int
i Bool
f e
r
in forall n. Widget n -> RenderM n (Result n)
render forall a b. (a -> b) -> a -> b
$ VisibleGridColumns -> RowHdrWidth -> WidthDeficit -> Widget n
colHdrRow VisibleGridColumns
vCs (Int -> RowHdrWidth
RowHdrW Int
rhw) WidthDeficit
rhwd forall n. Widget n -> Widget n -> 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 -> Bool -> e -> Widget n
hdrRow Bool
f GenericList n Seq e
l'
forall b a. b -> (a -> b) -> Maybe a -> b
maybe RenderM n (Result n)
lst RowHdr n e -> RenderM n (Result n)
hdrLst forall a b. (a -> b) -> a -> b
$ GridRenderers n e
r forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "rowHdr" a => a
#rowHdr
gridMoveLeft
:: GridTabularList n e
-> GridTabularList n e
gridMoveLeft :: forall n e. GridTabularList n e -> GridTabularList n e
gridMoveLeft GridTabularList n e
gl = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "list" a => a
#list forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "listSelected" a => a
#listSelected
then GridTabularList n e
gl
else GridTabularList n e
gl forall a b. a -> (a -> b) -> b
& forall a. IsLabel "currentColumn" a => a
#currentColumn forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a s. Coercible s a => Iso' s a
coercedTo @Int forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
%~ forall a. Ord a => a -> a -> a
max Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a -> a
subtract Int
1
gridMoveRight
:: GridTabularList n e
-> GridTabularList n e
gridMoveRight :: forall n e. GridTabularList n e -> GridTabularList n e
gridMoveRight GridTabularList n e
gl = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "list" a => a
#list forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "listSelected" a => a
#listSelected
then GridTabularList n e
gl
else GridTabularList n e
gl forall a b. a -> (a -> b) -> b
& forall a. IsLabel "currentColumn" a => a
#currentColumn forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a s. Coercible s a => Iso' s a
coercedTo @Int forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
%~ forall a. Ord a => a -> a -> a
min (forall (t :: * -> *) a. Foldable t => t a -> Int
length (GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "widths" a => a
#widths) forall a. Num a => a -> a -> a
- Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Num a => a -> a -> a
+Int
1)
gridMoveTo
:: Index
-> GridTabularList n e
-> GridTabularList n e
gridMoveTo :: forall n e. Index -> GridTabularList n e -> GridTabularList n e
gridMoveTo (Ix Int
n) GridTabularList n e
gl = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "list" a => a
#list forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "listSelected" a => a
#listSelected
then GridTabularList n e
gl
else GridTabularList n e
gl forall a b. a -> (a -> b) -> b
& forall a. IsLabel "currentColumn" a => a
#currentColumn forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a s. Coercible s a => Iso' s a
coercedTo @Int forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ forall a. Ord a => a -> a -> a
max Int
0 (forall a. Ord a => a -> a -> a
min (forall (t :: * -> *) a. Foldable t => t a -> Int
length (GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "widths" a => a
#widths) forall a. Num a => a -> a -> a
- Int
1) Int
n)
gridMoveToBeginning
:: GridTabularList n e
-> GridTabularList n e
gridMoveToBeginning :: forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToBeginning GridTabularList n e
gl = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "list" a => a
#list forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "listSelected" a => a
#listSelected
then GridTabularList n e
gl
else GridTabularList n e
gl forall a b. a -> (a -> b) -> b
& forall a. IsLabel "currentColumn" a => a
#currentColumn forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a s. Coercible s a => Iso' s a
coercedTo @Int forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Int
0
gridMoveToEnd
:: GridTabularList n e
-> GridTabularList n e
gridMoveToEnd :: forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToEnd GridTabularList n e
gl = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "list" a => a
#list forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "listSelected" a => a
#listSelected
then GridTabularList n e
gl
else GridTabularList n e
gl forall a b. a -> (a -> b) -> b
& forall a. IsLabel "currentColumn" a => a
#currentColumn forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a s. Coercible s a => Iso' s a
coercedTo @Int forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ forall (t :: * -> *) a. Foldable t => t a -> Int
length (GridTabularList n e
gl forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "widths" a => a
#widths) forall a. Num a => a -> a -> a
- Int
1
gridMovePage :: Ord n
=> GridRenderers n e
-> (VisibleGridColumns -> EventM n (GridTabularList n e) ())
-> EventM n (GridTabularList n e) ()
gridMovePage :: forall n e.
Ord n =>
GridRenderers n e
-> (VisibleGridColumns -> EventM n (GridTabularList n e) ())
-> EventM n (GridTabularList n e) ()
gridMovePage GridRenderers n e
r VisibleGridColumns -> EventM n (GridTabularList n e) ()
f = do
GridTabularList n e
l <- forall s (m :: * -> *). MonadState s m => m s
get
let l' :: GenericList n Seq e
l' = GridTabularList n e
l forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "list" a => a
#list
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ GenericList n Seq e
l' forall {s} {a}. s -> Getting a s a -> a
^^. forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL) forall a b. (a -> b) -> a -> b
$ do
Maybe Viewport
v <- forall n s. Ord n => n -> EventM n s (Maybe Viewport)
lookupViewport forall a b. (a -> b) -> a -> b
$ GenericList n Seq 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
case Maybe Viewport
v of
Maybe Viewport
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just Viewport
vp -> let
(Int
aW, Int
aH) = Viewport
vp forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "_vpSize" a => a
#_vpSize
RowHdrW Int
rhw = case GridRenderers n e
r forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall a. IsLabel "rowHdr" a => a
#rowHdr of
Maybe (RowHdr n e)
Nothing -> Int -> RowHdrWidth
RowHdrW Int
0
Just (RowHdr {AvailWidth -> [r] -> RowHdrWidth
width :: AvailWidth -> [r] -> RowHdrWidth
$sel:width:RowHdr :: ()
width, e -> Index -> r
toRH :: e -> Index -> r
$sel:toRH:RowHdr :: ()
toRH}) -> AvailWidth -> [r] -> RowHdrWidth
width (Int -> AvailWidth
AvlW Int
aW) forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith e -> Index -> r
toRH) forall a b. (a -> b) -> a -> b
$ forall n e. GenericList n Seq e -> AvailHeight -> ([e], [Index])
visibleRowIdx GenericList n Seq e
l' (Int -> AvailHeight
AvlH Int
aH)
in VisibleGridColumns -> EventM n (GridTabularList n e) ()
f forall a b. (a -> b) -> a -> b
$ forall n e. GridTabularList n e -> AvailWidth -> VisibleGridColumns
visibleGridColumns GridTabularList n e
l forall a b. (a -> b) -> a -> b
$ Int -> AvailWidth
AvlW forall a b. (a -> b) -> a -> b
$ Int
aW forall a. Num a => a -> a -> a
- Int
rhw
gridMovePageUp :: Ord n
=> GridRenderers n e
-> EventM n (GridTabularList n e) ()
gridMovePageUp :: forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageUp GridRenderers n e
r = forall n e.
Ord n =>
GridRenderers n e
-> (VisibleGridColumns -> EventM n (GridTabularList n e) ())
-> EventM n (GridTabularList n e) ()
gridMovePage GridRenderers n e
r forall a b. (a -> b) -> a -> b
$ \case
VisibleGridColumns
NoColumn -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
VisibleGridColumns
CurrentColumn -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveLeft
AnchoredLeft Index
_ -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToBeginning
MiddleColumns {Index
left :: Index
$sel:left:NoColumn :: VisibleGridColumns -> Index
left} -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall n e. Index -> GridTabularList n e -> GridTabularList n e
gridMoveTo Index
left
AnchoredRight {Index
left :: Index
$sel:left:NoColumn :: VisibleGridColumns -> Index
left} -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall n e. Index -> GridTabularList n e -> GridTabularList n e
gridMoveTo Index
left
gridMovePageDown :: Ord n
=> GridRenderers n e
-> EventM n (GridTabularList n e) ()
gridMovePageDown :: forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageDown GridRenderers n e
r = forall n e.
Ord n =>
GridRenderers n e
-> (VisibleGridColumns -> EventM n (GridTabularList n e) ())
-> EventM n (GridTabularList n e) ()
gridMovePage GridRenderers n e
r forall a b. (a -> b) -> a -> b
$ \case
VisibleGridColumns
NoColumn -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
VisibleGridColumns
CurrentColumn -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveRight
AnchoredLeft {Index
right :: Index
$sel:right:NoColumn :: VisibleGridColumns -> Index
right} -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall n e. Index -> GridTabularList n e -> GridTabularList n e
gridMoveTo Index
right
MiddleColumns {Index
right :: Index
$sel:right:NoColumn :: VisibleGridColumns -> Index
right} -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall n e. Index -> GridTabularList n e -> GridTabularList n e
gridMoveTo Index
right
AnchoredRight {} -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToEnd
handleGridListEvent :: Ord n
=> GridRenderers n e
-> Event -> EventM n (GridTabularList n e) ()
handleGridListEvent :: forall n e.
Ord n =>
GridRenderers n e -> Event -> EventM n (GridTabularList n e) ()
handleGridListEvent GridRenderers n e
r Event
e = case Event
e of
EvKey Key
KLeft [] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveLeft
EvKey Key
KRight [] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveRight
EvKey Key
KHome [Modifier
MCtrl] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToBeginning
EvKey Key
KEnd [Modifier
MCtrl] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToEnd
EvKey Key
KPageUp [Modifier
MCtrl] -> forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageUp GridRenderers n e
r
EvKey Key
KPageDown [Modifier
MCtrl] -> forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageDown GridRenderers n e
r
Event
_ -> forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom forall a. IsLabel "list" a => a
#list (forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n) =>
Event -> EventM n (GenericList n t e) ()
L.handleListEvent Event
e)
handleGridListEventVi :: Ord n
=> GridRenderers n e
-> Event -> EventM n (GridTabularList n e) ()
handleGridListEventVi :: forall n e.
Ord n =>
GridRenderers n e -> Event -> EventM n (GridTabularList n e) ()
handleGridListEventVi GridRenderers n e
r Event
e = case Event
e of
EvKey (KChar Char
'h') [] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveLeft
EvKey (KChar Char
'l') [] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveRight
EvKey (KChar Char
'H') [] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToBeginning
EvKey (KChar Char
'L') [] -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall n e. GridTabularList n e -> GridTabularList n e
gridMoveToEnd
EvKey (KChar Char
'h') [Modifier
MMeta] -> forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageUp GridRenderers n e
r
EvKey (KChar Char
'l') [Modifier
MMeta] -> forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageDown GridRenderers n e
r
EvKey (KChar Char
'h') [Modifier
MAlt] -> forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageUp GridRenderers n e
r
EvKey (KChar Char
'l') [Modifier
MAlt] -> forall n e.
Ord n =>
GridRenderers n e -> EventM n (GridTabularList n e) ()
gridMovePageDown GridRenderers n e
r
Event
_ -> forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom forall a. IsLabel "list" a => a
#list (forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n) =>
(Event -> EventM n (GenericList n t e) ())
-> Event -> EventM n (GenericList n t e) ()
L.handleListEventVi (\Event
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()) Event
e)