{-# LANGUAGE TemplateHaskell #-}
module Simple.UI.Widgets.Text (
TextAlign (..),
Text,
TextClass,
castToText,
textNew,
text,
align
) where
import Control.Lens (makeLensesFor)
import Simple.UI.Core.Internal.UIApp
import Simple.UI.Core.Attribute
import Simple.UI.Widgets.Widget
data TextAlign = TextAlignLeft
| TextAlignRight
| TextAlignCenter
data Text = Text
{ Text -> Widget
_textParent :: Widget
, Text -> Attribute (Maybe String)
_textText :: Attribute (Maybe String)
, Text -> Attribute TextAlign
_textAlign :: Attribute TextAlign
}
makeLensesFor [("_textParent", "textParent")] ''Text
class WidgetClass w => TextClass w where
castToText :: w -> Text
text :: w -> Attribute (Maybe String)
text = Text -> Attribute (Maybe String)
_textText (Text -> Attribute (Maybe String))
-> (w -> Text) -> w -> Attribute (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w -> Text
forall w. TextClass w => w -> Text
castToText
align :: w -> Attribute TextAlign
align = Text -> Attribute TextAlign
_textAlign (Text -> Attribute TextAlign)
-> (w -> Text) -> w -> Attribute TextAlign
forall b c a. (b -> c) -> (a -> b) -> a -> c
. w -> Text
forall w. TextClass w => w -> Text
castToText
instance TextClass Text where
castToText :: Text -> Text
castToText = Text -> Text
forall a. a -> a
id
instance WidgetClass Text where
castToWidget :: Text -> Widget
castToWidget = Text -> Widget
_textParent
overrideWidget :: Text -> State VirtualWidget () -> Text
overrideWidget = Lens' Text Widget -> Text -> State VirtualWidget () -> Text
forall p w.
WidgetClass p =>
Lens' w p -> w -> State VirtualWidget () -> w
overrideWidgetHelper Lens' Text Widget
textParent
textNew :: Maybe String -> UIApp u Text
textNew :: Maybe String -> UIApp u Text
textNew Maybe String
s = do
Widget
parent <- UIApp u Widget
forall u. UIApp u Widget
widgetNew
Attribute (Maybe String)
t <- Maybe String
-> ReaderT
(AppConfig u) (StateT AppState IO) (Attribute (Maybe String))
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew Maybe String
s
Attribute TextAlign
a <- TextAlign
-> ReaderT (AppConfig u) (StateT AppState IO) (Attribute TextAlign)
forall (m :: * -> *) a. MonadIO m => a -> m (Attribute a)
attributeNew TextAlign
TextAlignLeft
Text -> UIApp u Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text :: Widget -> Attribute (Maybe String) -> Attribute TextAlign -> Text
Text
{ _textParent :: Widget
_textParent = Widget
parent
, _textText :: Attribute (Maybe String)
_textText = Attribute (Maybe String)
t
, _textAlign :: Attribute TextAlign
_textAlign = Attribute TextAlign
a
}