{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
module Simple.UI.Widgets.TextListView (
TextListView,
TextListViewClass,
castToTextListView,
textListViewNew,
textListViewCenterAt,
textListViewReset,
textListViewGetPos,
textListViewGoUp,
textListViewGoDown,
textListViewUpdate,
textItemActivated
) where
import Control.Lens (makeLensesFor, (.=))
import Control.Monad
import qualified Data.Vector as V
import qualified Graphics.Vty as Vty
import Simple.UI.Core.Internal.UIApp
import Simple.UI.Core.Attribute
import Simple.UI.Core.Draw
import Simple.UI.Core.ListenerList
import Simple.UI.Widgets.Text
import Simple.UI.Widgets.TextItem
import Simple.UI.Widgets.Widget
data TextListView a = TextListView
{ TextListView a -> Widget
_textListViewParent :: Widget
, TextListView a -> Attribute Int
_textListViewYOffset :: Attribute Int
, TextListView a -> Attribute Int
_textListViewPos :: Attribute Int
, TextListView a -> Attribute Int
_textListViewHeight :: Attribute Int
, TextListView a -> Attribute (Vector (TextItem a))
_textListViewItems :: Attribute (V.Vector (TextItem a))
, TextListView a -> Attribute Int
_textListViewLength :: Attribute Int
, TextListView a -> ListenerList (TextItem a -> UIApp' ())
_textListViewTextItemActivated :: ListenerList (TextItem a -> UIApp' ())
, TextListView a -> TextItem a -> Int -> UIApp' ()
_textListViewContentProvider :: TextItem a -> Int -> UIApp' ()
}
makeLensesFor [("_textListViewParent", "textListViewParent")] ''TextListView
class TextListViewClass w where
castToTextListView :: w a -> TextListView a
textItemActivated :: w a -> ListenerList (TextItem a -> UIApp' ())
textItemActivated = TextListView a -> ListenerList (TextItem a -> UIApp' ())
forall a. TextListView a -> ListenerList (TextItem a -> UIApp' ())
_textListViewTextItemActivated (TextListView a -> ListenerList (TextItem a -> UIApp' ()))
-> (w a -> TextListView a)
-> w a
-> ListenerList (TextItem a -> UIApp' ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView
textListViewCenterAt :: w a -> Int -> Int -> UIApp u ()
textListViewCenterAt w a
_ Int
_ Int
0 = () -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
textListViewCenterAt (w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView -> TextListView a
textListView) Int
index Int
listLength = do
Int
height <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewHeight
let heightDivided :: Int
heightDivided = Int
height Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
if | Int
index Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
heightDivided Bool -> Bool -> Bool
|| Int
listLength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
height -> do
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos Int
index
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int
0
| Int
index Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
heightDivided Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
listLength -> do
let offset :: Int
offset = Int
index Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
heightDivided
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int
offset
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos (Int
index Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
offset)
| Bool
otherwise -> do
let offset :: Int
offset = Int
listLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
height
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int
offset
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos (Int
index Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
offset)
() -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
textListViewReset :: w a -> UIApp u ()
textListViewReset (w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView -> TextListView a
textListView) = do
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos Int
0
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int
0
textListViewGetPos :: w a -> UIApp u Int
textListViewGetPos (w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView -> TextListView a
textListView) = do
Int
pos <- TextListView a -> (TextListView a -> Attribute Int) -> UIApp u Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Int
yOffset <- TextListView a -> (TextListView a -> Attribute Int) -> UIApp u Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
Int -> UIApp u Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yOffset)
textListViewGoUp :: w a -> UIApp u ()
textListViewGoUp = TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goUp (TextListView a -> UIApp u ())
-> (w a -> TextListView a) -> w a -> UIApp u ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView
textListViewGoDown :: w a -> UIApp u ()
textListViewGoDown = TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goDown (TextListView a -> UIApp u ())
-> (w a -> TextListView a) -> w a -> UIApp u ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView
textListViewUpdate :: w a -> UIApp u ()
textListViewUpdate = TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
textListViewUpdateState (TextListView a -> UIApp u ())
-> (w a -> TextListView a) -> w a -> UIApp u ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w a -> TextListView a
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> TextListView a
castToTextListView
instance TextListViewClass TextListView where
castToTextListView :: TextListView a -> TextListView a
castToTextListView = TextListView a -> TextListView a
forall a. a -> a
id
instance WidgetClass (TextListView a) where
castToWidget :: TextListView a -> Widget
castToWidget = Widget -> Widget
forall w. WidgetClass w => w -> Widget
castToWidget (Widget -> Widget)
-> (TextListView a -> Widget) -> TextListView a -> Widget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextListView a -> Widget
forall a. TextListView a -> Widget
_textListViewParent
overrideWidget :: TextListView a -> State VirtualWidget () -> TextListView a
overrideWidget = Lens' (TextListView a) Widget
-> TextListView a -> State VirtualWidget () -> TextListView a
forall p w.
WidgetClass p =>
Lens' w p -> w -> State VirtualWidget () -> w
overrideWidgetHelper forall a. Lens' (TextListView a) Widget
Lens' (TextListView a) Widget
textListViewParent
textListViewNew :: (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNew :: (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNew TextItem a -> Int -> UIApp' ()
contentProvider = do
TextListView a
textListView <- (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
forall a u.
(TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNewOverride TextItem a -> Int -> UIApp' ()
contentProvider
TextListView a
-> (TextListView a
-> ListenerList (Drawing -> Int -> Int -> UIApp' ()))
-> (Drawing -> Int -> Int -> UIApp' ())
-> UIApp u ()
forall w a u. w -> (w -> ListenerList a) -> a -> UIApp u ()
on_ TextListView a
textListView TextListView a -> ListenerList (Drawing -> Int -> Int -> UIApp' ())
forall w.
WidgetClass w =>
w -> ListenerList (Drawing -> Int -> Int -> UIApp' ())
draw ((Drawing -> Int -> Int -> UIApp' ()) -> UIApp u ())
-> (Drawing -> Int -> Int -> UIApp' ()) -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ TextListView a
-> (TextItem a -> Int -> UIApp' ())
-> Drawing
-> Int
-> Int
-> UIApp' ()
forall a u.
TextListView a
-> (TextItem a -> Int -> UIApp' ())
-> Drawing
-> Int
-> Int
-> UIApp u ()
textListViewDraw TextListView a
textListView TextItem a -> Int -> UIApp' ()
contentProvider
TextListView a
-> (TextListView a
-> ListenerList (Key -> [Modifier] -> UIApp' ()))
-> (Key -> [Modifier] -> UIApp' ())
-> UIApp u ()
forall w a u. w -> (w -> ListenerList a) -> a -> UIApp u ()
on_ TextListView a
textListView TextListView a -> ListenerList (Key -> [Modifier] -> UIApp' ())
forall w.
WidgetClass w =>
w -> ListenerList (Key -> [Modifier] -> UIApp' ())
keyPressed ((Key -> [Modifier] -> UIApp' ()) -> UIApp u ())
-> (Key -> [Modifier] -> UIApp' ()) -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ TextListView a -> Key -> [Modifier] -> UIApp' ()
forall a u. TextListView a -> Key -> [Modifier] -> UIApp u ()
textListViewKeyPressed TextListView a
textListView
TextListView a -> UIApp u (TextListView a)
forall (m :: * -> *) a. Monad m => a -> m a
return TextListView a
textListView
textListViewNewOverride :: (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNewOverride :: (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNewOverride TextItem a -> Int -> UIApp' ()
contentProvider = TextListView a -> TextListView a
forall p. WidgetClass p => p -> p
override (TextListView a -> TextListView a)
-> UIApp u (TextListView a) -> UIApp u (TextListView a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
forall a u.
(TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNewDefault TextItem a -> Int -> UIApp' ()
contentProvider
where
textListViewComputeSize :: p -> m (a, b)
textListViewComputeSize p
_ = (a, b) -> m (a, b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
1, b
1)
override :: p -> p
override p
textView = p -> State VirtualWidget () -> p
forall w. WidgetClass w => w -> State VirtualWidget () -> w
overrideWidget p
textView (State VirtualWidget () -> p) -> State VirtualWidget () -> p
forall a b. (a -> b) -> a -> b
$ do
(String -> Identity String)
-> VirtualWidget -> Identity VirtualWidget
Lens' VirtualWidget String
virtualWidgetName ((String -> Identity String)
-> VirtualWidget -> Identity VirtualWidget)
-> String -> State VirtualWidget ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
"textlistview"
(UIApp' (Int, Int) -> Identity (UIApp' (Int, Int)))
-> VirtualWidget -> Identity VirtualWidget
Lens' VirtualWidget (UIApp' (Int, Int))
virtualWidgetComputeSize ((UIApp' (Int, Int) -> Identity (UIApp' (Int, Int)))
-> VirtualWidget -> Identity VirtualWidget)
-> UIApp' (Int, Int) -> State VirtualWidget ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= p -> UIApp' (Int, Int)
forall (m :: * -> *) a b p.
(Monad m, Num a, Num b) =>
p -> m (a, b)
textListViewComputeSize p
textView
textListViewNewDefault :: (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNewDefault :: (TextItem a -> Int -> UIApp' ()) -> UIApp u (TextListView a)
textListViewNewDefault TextItem a -> Int -> UIApp' ()
contentProvider = do
Widget
parent <- UIApp u Widget
forall u. UIApp u Widget
widgetNew
Attribute Int
yOffset <- Int -> ReaderT (AppConfig u) (StateT AppState IO) (Attribute Int)
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew Int
0
Attribute Int
pos <- Int -> ReaderT (AppConfig u) (StateT AppState IO) (Attribute Int)
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew Int
0
Attribute Int
height <- Int -> ReaderT (AppConfig u) (StateT AppState IO) (Attribute Int)
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew Int
0
Attribute (Vector (TextItem a))
items <- Vector (TextItem a)
-> ReaderT
(AppConfig u)
(StateT AppState IO)
(Attribute (Vector (TextItem a)))
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew Vector (TextItem a)
forall a. Vector a
V.empty
Attribute Int
l <- Int -> ReaderT (AppConfig u) (StateT AppState IO) (Attribute Int)
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew Int
0
ListenerList (TextItem a -> UIApp' ())
itemActivated <- ReaderT
(AppConfig u)
(StateT AppState IO)
(ListenerList (TextItem a -> UIApp' ()))
forall (m :: * -> *) a. MonadIO m => m (ListenerList a)
listenerNew
TextListView a -> UIApp u (TextListView a)
forall (m :: * -> *) a. Monad m => a -> m a
return TextListView :: forall a.
Widget
-> Attribute Int
-> Attribute Int
-> Attribute Int
-> Attribute (Vector (TextItem a))
-> Attribute Int
-> ListenerList (TextItem a -> UIApp' ())
-> (TextItem a -> Int -> UIApp' ())
-> TextListView a
TextListView
{ _textListViewParent :: Widget
_textListViewParent = Widget
parent
, _textListViewYOffset :: Attribute Int
_textListViewYOffset = Attribute Int
yOffset
, _textListViewPos :: Attribute Int
_textListViewPos = Attribute Int
pos
, _textListViewHeight :: Attribute Int
_textListViewHeight = Attribute Int
height
, _textListViewItems :: Attribute (Vector (TextItem a))
_textListViewItems = Attribute (Vector (TextItem a))
items
, _textListViewLength :: Attribute Int
_textListViewLength = Attribute Int
l
, _textListViewTextItemActivated :: ListenerList (TextItem a -> UIApp' ())
_textListViewTextItemActivated = ListenerList (TextItem a -> UIApp' ())
itemActivated
, _textListViewContentProvider :: TextItem a -> Int -> UIApp' ()
_textListViewContentProvider = TextItem a -> Int -> UIApp' ()
contentProvider
}
textListViewDraw :: TextListView a -> (TextItem a -> Int -> UIApp' ()) -> Drawing -> Int -> Int -> UIApp u ()
textListViewDraw :: TextListView a
-> (TextItem a -> Int -> UIApp' ())
-> Drawing
-> Int
-> Int
-> UIApp u ()
textListViewDraw TextListView a
textListView TextItem a -> Int -> UIApp' ()
contentProvider Drawing
drawing Int
width Int
height = do
Int
oldHeight <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewHeight
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
height Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
oldHeight) (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ do
Vector (TextItem a)
_items <- Int
-> (Int -> ReaderT (AppConfig u) (StateT AppState IO) (TextItem a))
-> ReaderT (AppConfig u) (StateT AppState IO) (Vector (TextItem a))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
V.generateM Int
height ((Int -> ReaderT (AppConfig u) (StateT AppState IO) (TextItem a))
-> ReaderT
(AppConfig u) (StateT AppState IO) (Vector (TextItem a)))
-> (Int -> ReaderT (AppConfig u) (StateT AppState IO) (TextItem a))
-> ReaderT (AppConfig u) (StateT AppState IO) (Vector (TextItem a))
forall a b. (a -> b) -> a -> b
$ \Int
_ -> do
TextItem a
item <- Maybe String
-> ReaderT (AppConfig u) (StateT AppState IO) (TextItem a)
forall u a. Maybe String -> UIApp u (TextItem a)
textItemNew Maybe String
forall a. Maybe a
Nothing
TextListView a
-> UIApp u (Color, Color, DrawStyle, Color, Color, DrawStyle)
forall w u.
WidgetClass w =>
w -> UIApp u (Color, Color, DrawStyle, Color, Color, DrawStyle)
getColors TextListView a
textListView UIApp u (Color, Color, DrawStyle, Color, Color, DrawStyle)
-> ((Color, Color, DrawStyle, Color, Color, DrawStyle)
-> UIApp u ())
-> UIApp u ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TextItem a
-> (Color, Color, DrawStyle, Color, Color, DrawStyle) -> UIApp u ()
forall w u.
WidgetClass w =>
w
-> (Color, Color, DrawStyle, Color, Color, DrawStyle) -> UIApp u ()
setColors TextItem a
item
TextItem a
-> ReaderT (AppConfig u) (StateT AppState IO) (TextItem a)
forall (m :: * -> *) a. Monad m => a -> m a
return TextItem a
item
TextListView a
-> (TextListView a -> Attribute (Vector (TextItem a)))
-> Vector (TextItem a)
-> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute (Vector (TextItem a))
forall a. TextListView a -> Attribute (Vector (TextItem a))
_textListViewItems Vector (TextItem a)
_items
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewHeight Int
height
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
textListViewUpdateState TextListView a
textListView
Color
fg <- TextListView a
-> (TextListView a -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorForeground
Color
bg <- TextListView a
-> (TextListView a -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorBackground
Color
selectedBg <- TextListView a
-> (TextListView a -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorBackgroundSelected
Drawing -> DrawingBuilder () -> UIApp u ()
forall (m :: * -> *) a.
MonadIO m =>
Drawing -> DrawingBuilder a -> m a
drawingRun Drawing
drawing (DrawingBuilder () -> UIApp u ())
-> DrawingBuilder () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ do
Color -> Color -> DrawStyle -> DrawingBuilder ()
drawingSetAttrs Color
fg Color
bg DrawStyle
DrawStyleNormal
DrawingBuilder ()
drawingClear
Int
pos <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Int
yOffset <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
Vector (TextItem a)
items <- TextListView a
-> (TextListView a -> Attribute (Vector (TextItem a)))
-> ReaderT (AppConfig u) (StateT AppState IO) (Vector (TextItem a))
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute (Vector (TextItem a))
forall a. TextListView a -> Attribute (Vector (TextItem a))
_textListViewItems
[Int] -> (Int -> UIApp u ()) -> UIApp u ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
0 .. Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> UIApp u ()) -> UIApp u ())
-> (Int -> UIApp u ()) -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ \Int
y -> do
let item :: TextItem a
item = Vector (TextItem a)
items Vector (TextItem a) -> Int -> TextItem a
forall a. Vector a -> Int -> a
V.! Int
y
UIApp' () -> UIApp u ()
forall a u. UIApp' a -> UIApp u a
liftUIApp' (UIApp' () -> UIApp u ()) -> UIApp' () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ TextItem a -> Int -> UIApp' ()
contentProvider TextItem a
item (Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yOffset)
Drawing
drawing' <- Drawing
-> Int
-> Int
-> Int
-> Int
-> ReaderT (AppConfig u) (StateT AppState IO) Drawing
forall (m :: * -> *).
MonadIO m =>
Drawing -> Int -> Int -> Int -> Int -> m Drawing
drawingSliceNew Drawing
drawing Int
0 Int
y Int
width Int
1
if Int
y Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pos
then TextItem a
-> (TextItem a -> Attribute Color) -> Color -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextItem a
item TextItem a -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorBackground Color
selectedBg
else TextItem a
-> (TextItem a -> Attribute Color) -> Color -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextItem a
item TextItem a -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorBackground Color
bg
TextItem a
-> (TextItem a
-> ListenerList (Drawing -> Int -> Int -> UIApp' ()))
-> (Drawing, Int, Int)
-> UIApp u ()
forall a b w u.
Fire a b =>
w -> (w -> ListenerList a) -> b -> UIApp u ()
fire TextItem a
item TextItem a -> ListenerList (Drawing -> Int -> Int -> UIApp' ())
forall w.
WidgetClass w =>
w -> ListenerList (Drawing -> Int -> Int -> UIApp' ())
draw (Drawing
drawing', Int
width, Int
1 :: Int)
textListViewUpdateState :: TextListView a -> UIApp u ()
textListViewUpdateState :: TextListView a -> UIApp u ()
textListViewUpdateState TextListView a
textListView = do
let contentProvider :: TextItem a -> Int -> UIApp' ()
contentProvider = TextListView a -> TextItem a -> Int -> UIApp' ()
forall a. TextListView a -> TextItem a -> Int -> UIApp' ()
_textListViewContentProvider TextListView a
textListView
Vector (TextItem a)
items <- TextListView a
-> (TextListView a -> Attribute (Vector (TextItem a)))
-> ReaderT (AppConfig u) (StateT AppState IO) (Vector (TextItem a))
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute (Vector (TextItem a))
forall a. TextListView a -> Attribute (Vector (TextItem a))
_textListViewItems
Int
height <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewHeight
Int
yOffset <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
[Bool]
hasText <- [Int]
-> (Int -> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) [Bool]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0 .. Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) [Bool])
-> (Int -> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) [Bool]
forall a b. (a -> b) -> a -> b
$ \Int
y -> do
let item :: TextItem a
item = Vector (TextItem a)
items Vector (TextItem a) -> Int -> TextItem a
forall a. Vector a -> Int -> a
V.! Int
y
UIApp' () -> UIApp u ()
forall a u. UIApp' a -> UIApp u a
liftUIApp' (UIApp' () -> UIApp u ()) -> UIApp' () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ TextItem a -> Int -> UIApp' ()
contentProvider TextItem a
item (Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yOffset)
Maybe String
maybeText <- TextItem a
-> (TextItem a -> Attribute (Maybe String))
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe String)
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextItem a
item TextItem a -> Attribute (Maybe String)
forall w. TextClass w => w -> Attribute (Maybe String)
text
case Maybe String
maybeText of
Just String
_ -> Bool -> ReaderT (AppConfig u) (StateT AppState IO) Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Maybe String
Nothing -> Bool -> ReaderT (AppConfig u) (StateT AppState IO) Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
let listLength :: Int
listLength = [Bool] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Bool] -> Int) -> [Bool] -> Int
forall a b. (a -> b) -> a -> b
$ (Bool -> Bool) -> [Bool] -> [Bool]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
True) [Bool]
hasText
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewLength Int
listLength
Int
pos <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
listLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$
if Int
yOffset Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset (Int
yOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
listLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
else TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos (Int
listLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
listLength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos Int
0
textListViewKeyPressed :: TextListView a -> Vty.Key -> [Vty.Modifier]-> UIApp u ()
textListViewKeyPressed :: TextListView a -> Key -> [Modifier] -> UIApp u ()
textListViewKeyPressed TextListView a
textListView Key
key [Modifier]
_ = do
Int
height <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewHeight
case Key
key of
Key
Vty.KUp ->
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goUp TextListView a
textListView
Key
Vty.KDown ->
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goDown TextListView a
textListView
Key
Vty.KPageUp ->
[Int] -> (Int -> UIApp u ()) -> UIApp u ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int
1..Int
height Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2] :: [Int]) ((Int -> UIApp u ()) -> UIApp u ())
-> (Int -> UIApp u ()) -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ UIApp u () -> Int -> UIApp u ()
forall a b. a -> b -> a
const (TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goUp TextListView a
textListView)
Key
Vty.KPageDown ->
[Int] -> (Int -> UIApp u ()) -> UIApp u ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int
1..Int
height Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2] :: [Int]) ((Int -> UIApp u ()) -> UIApp u ())
-> (Int -> UIApp u ()) -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ UIApp u () -> Int -> UIApp u ()
forall a b. a -> b -> a
const (TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goDown TextListView a
textListView)
Key
Vty.KHome ->
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goHome TextListView a
textListView
Key
Vty.KEnd ->
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goEnd TextListView a
textListView
Key
Vty.KEnter -> do
Int
pos <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0) (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ do
Vector (TextItem a)
items <- TextListView a
-> (TextListView a -> Attribute (Vector (TextItem a)))
-> ReaderT (AppConfig u) (StateT AppState IO) (Vector (TextItem a))
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute (Vector (TextItem a))
forall a. TextListView a -> Attribute (Vector (TextItem a))
_textListViewItems
TextListView a
-> (TextListView a -> ListenerList (TextItem a -> UIApp' ()))
-> TextItem a
-> UIApp u ()
forall a b w u.
Fire a b =>
w -> (w -> ListenerList a) -> b -> UIApp u ()
fire TextListView a
textListView TextListView a -> ListenerList (TextItem a -> UIApp' ())
forall (w :: * -> *) a.
TextListViewClass w =>
w a -> ListenerList (TextItem a -> UIApp' ())
textItemActivated (Vector (TextItem a)
items Vector (TextItem a) -> Int -> TextItem a
forall a. Vector a -> Int -> a
V.! Int
pos)
Key
_ ->
() -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
hasNthItem :: TextListView a -> Int -> UIApp u Bool
hasNthItem :: TextListView a -> Int -> UIApp u Bool
hasNthItem TextListView a
textListView Int
pos = do
let contentProvider :: TextItem a -> Int -> UIApp' ()
contentProvider = TextListView a -> TextItem a -> Int -> UIApp' ()
forall a. TextListView a -> TextItem a -> Int -> UIApp' ()
_textListViewContentProvider TextListView a
textListView
TextItem a
item <- Maybe String -> UIApp u (TextItem a)
forall u a. Maybe String -> UIApp u (TextItem a)
textItemNew Maybe String
forall a. Maybe a
Nothing
UIApp' () -> UIApp u ()
forall a u. UIApp' a -> UIApp u a
liftUIApp' (UIApp' () -> UIApp u ()) -> UIApp' () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$ TextItem a -> Int -> UIApp' ()
contentProvider TextItem a
item Int
pos
Maybe String
_text <- TextItem a
-> (TextItem a -> Attribute (Maybe String))
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe String)
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextItem a
item TextItem a -> Attribute (Maybe String)
forall w. TextClass w => w -> Attribute (Maybe String)
text
case Maybe String
_text of
Just String
_ -> Bool -> UIApp u Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Maybe String
Nothing -> Bool -> UIApp u Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
goUp :: TextListView a -> UIApp u ()
goUp :: TextListView a -> UIApp u ()
goUp TextListView a
textListView = do
Int
pos <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Int
yOffset <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
if Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
else
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
yOffset Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$
TextListView a
-> (TextListView a -> Attribute Int) -> (Int -> Int) -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> (a -> a) -> m ()
modify TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int -> Int
forall a. Enum a => a -> a
pred
goDown :: TextListView a -> UIApp u ()
goDown :: TextListView a -> UIApp u ()
goDown TextListView a
textListView = do
Int
l <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewLength
Int
pos <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Int
yOffset <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
if Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
then
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else do
Bool
hasItem <- TextListView a -> Int -> UIApp u Bool
forall a u. TextListView a -> Int -> UIApp u Bool
hasNthItem TextListView a
textListView (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
hasItem (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$
TextListView a
-> (TextListView a -> Attribute Int) -> (Int -> Int) -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> (a -> a) -> m ()
modify TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int -> Int
forall a. Enum a => a -> a
succ
goHome :: TextListView a -> UIApp u ()
goHome :: TextListView a -> UIApp u ()
goHome TextListView a
textListView = do
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos Int
0
TextListView a
-> (TextListView a -> Attribute Int) -> Int -> UIApp u ()
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> a -> m ()
set TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset Int
0
goEnd :: TextListView a -> UIApp u ()
goEnd :: TextListView a -> UIApp u ()
goEnd TextListView a
textListView = do
Int
pos <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Int
yOffset <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goDown TextListView a
textListView
Int
pos' <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewPos
Int
yOffset' <- TextListView a
-> (TextListView a -> Attribute Int)
-> ReaderT (AppConfig u) (StateT AppState IO) Int
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get TextListView a
textListView TextListView a -> Attribute Int
forall a. TextListView a -> Attribute Int
_textListViewYOffset
Bool -> UIApp u () -> UIApp u ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yOffset Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
pos' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yOffset') (UIApp u () -> UIApp u ()) -> UIApp u () -> UIApp u ()
forall a b. (a -> b) -> a -> b
$
TextListView a -> UIApp u ()
forall a u. TextListView a -> UIApp u ()
goEnd TextListView a
textListView