{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module IHaskell.Display.Widgets.Style.ToggleButtonsStyle
(
ToggleButtonsStyle
, mkToggleButtonsStyle
) where
import Prelude
import Data.Aeson
import Data.IORef (newIORef)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
import IHaskell.IPython.Message.UUID as U
import IHaskell.Display.Widgets.Types
import IHaskell.Display.Widgets.Common
type ToggleButtonsStyle = IPythonWidget 'ToggleButtonsStyleType
mkToggleButtonsStyle :: IO ToggleButtonsStyle
mkToggleButtonsStyle :: IO ToggleButtonsStyle
mkToggleButtonsStyle = do
UUID
wid <- IO UUID
U.random
let stl :: Rec Attr DescriptionStyleClass
stl = FieldType 'ModelName -> Rec Attr DescriptionStyleClass
defaultDescriptionStyleWidget Text
"ToggleButtonsStyleModel"
but :: Rec Attr '[ 'ButtonWidth, 'FontWeight]
but = (forall {a :: Field}. (a ~ 'ButtonWidth) => SField a
ButtonWidth forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:: String
"")
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'FontWeight) => SField a
FontWeight forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:: FontWeightValue
DefaultWeight)
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& forall {u} (a :: u -> *). Rec a '[]
RNil
btnStlState :: WidgetState 'ToggleButtonsStyleType
btnStlState = forall (w :: WidgetType).
Rec Attr (WidgetFields w) -> WidgetState w
WidgetState (Rec
Attr
'[ 'ModelName, 'ViewName, 'ViewModule, 'ViewModuleVersion,
'ModelModule, 'ModelModuleVersion, 'DescriptionWidth]
stl forall {k} (f :: k -> *) (as :: [k]) (bs :: [k]).
Rec f as -> Rec f bs -> Rec f (as ++ bs)
<+> Rec Attr '[ 'ButtonWidth, 'FontWeight]
but)
IORef (WidgetState 'ToggleButtonsStyleType)
stateIO <- forall a. a -> IO (IORef a)
newIORef WidgetState 'ToggleButtonsStyleType
btnStlState
let style :: ToggleButtonsStyle
style = forall (w :: WidgetType).
UUID -> IORef (WidgetState w) -> IPythonWidget w
IPythonWidget UUID
wid IORef (WidgetState 'ToggleButtonsStyleType)
stateIO
forall a. IHaskellWidget a => a -> Value -> IO ()
widgetSendOpen ToggleButtonsStyle
style forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Value
toJSON WidgetState 'ToggleButtonsStyleType
btnStlState
forall (m :: * -> *) a. Monad m => a -> m a
return ToggleButtonsStyle
style
instance IHaskellWidget ToggleButtonsStyle where
getCommUUID :: ToggleButtonsStyle -> UUID
getCommUUID = forall (w :: WidgetType). IPythonWidget w -> UUID
uuid