module Simple.UI.Widgets.Properties.Selected (
HasSelected,
selected,
selectedGetColors
) where
import qualified Graphics.Vty as Vty
import Simple.UI.Core.Attribute
import Simple.UI.Core.Draw
import Simple.UI.Core.Internal.UIApp
import Simple.UI.Widgets.Widget
class WidgetClass w => HasSelected w where
selected :: w -> Attribute Bool
selectedGetColors :: w -> UIApp u (Vty.Color, Vty.Color, DrawStyle)
selectedGetColors w
widget = do
Bool
sel <- w
-> (w -> Attribute Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute Bool
forall w. HasSelected w => w -> Attribute Bool
selected
if Bool
sel
then do
Color
fg <- w
-> (w -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorForegroundSelected
Color
bg <- w
-> (w -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorBackgroundSelected
DrawStyle
style <- w
-> (w -> Attribute DrawStyle)
-> ReaderT (AppConfig u) (StateT AppState IO) DrawStyle
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute DrawStyle
forall w. WidgetClass w => w -> Attribute DrawStyle
colorStyleSelected
(Color, Color, DrawStyle) -> UIApp u (Color, Color, DrawStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Color
fg, Color
bg, DrawStyle
style)
else do
Color
fg <- w
-> (w -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorForeground
Color
bg <- w
-> (w -> Attribute Color)
-> ReaderT (AppConfig u) (StateT AppState IO) Color
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute Color
forall w. WidgetClass w => w -> Attribute Color
colorBackground
DrawStyle
style <- w
-> (w -> Attribute DrawStyle)
-> ReaderT (AppConfig u) (StateT AppState IO) DrawStyle
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get w
widget w -> Attribute DrawStyle
forall w. WidgetClass w => w -> Attribute DrawStyle
colorStyle
(Color, Color, DrawStyle) -> UIApp u (Color, Color, DrawStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Color
fg, Color
bg, DrawStyle
style)