{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}

{-# OPTIONS_GHC -fno-warn-orphans  #-}

module IHaskell.Display.Widgets.Style.ButtonStyle
  ( -- * Button style
    ButtonStyle
    -- * Create a new button style
  , mkButtonStyle
  ) where

-- To keep `cabal repl` happy when running from the ihaskell repo
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

-- | A 'ButtonStyle' represents a Button Style from IPython.html.widgets.
type ButtonStyle = IPythonWidget 'ButtonStyleType

-- | Create a new button style
mkButtonStyle :: IO ButtonStyle
mkButtonStyle :: IO ButtonStyle
mkButtonStyle = do
  UUID
wid <- IO UUID
U.random

  let stl :: Rec Attr StyleWidgetClass
stl = FieldType 'ModelName -> Rec Attr StyleWidgetClass
defaultStyleWidget Text
"ButtonStyleModel"
      but :: Rec Attr '[ 'ButtonColor, 'FontWeight]
but = (forall {a :: Field}. (a ~ 'ButtonColor) => SField a
ButtonColor forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:: forall a. Maybe a
Nothing)
            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 'ButtonStyleType
btnStlState = forall (w :: WidgetType).
Rec Attr (WidgetFields w) -> WidgetState w
WidgetState (Rec
  Attr
  '[ 'ModelName, 'ViewName, 'ViewModule, 'ViewModuleVersion,
     'ModelModule, 'ModelModuleVersion]
stl forall {k} (f :: k -> *) (as :: [k]) (bs :: [k]).
Rec f as -> Rec f bs -> Rec f (as ++ bs)
<+> Rec Attr '[ 'ButtonColor, 'FontWeight]
but)

  IORef (WidgetState 'ButtonStyleType)
stateIO <- forall a. a -> IO (IORef a)
newIORef WidgetState 'ButtonStyleType
btnStlState

  let style :: ButtonStyle
style = forall (w :: WidgetType).
UUID -> IORef (WidgetState w) -> IPythonWidget w
IPythonWidget UUID
wid IORef (WidgetState 'ButtonStyleType)
stateIO

  -- Open a comm for this widget, and store it in the kernel state
  forall a. IHaskellWidget a => a -> Value -> IO ()
widgetSendOpen ButtonStyle
style forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Value
toJSON WidgetState 'ButtonStyleType
btnStlState

  -- Return the style widget
  forall (m :: * -> *) a. Monad m => a -> m a
return ButtonStyle
style

instance IHaskellWidget ButtonStyle where
  getCommUUID :: ButtonStyle -> UUID
getCommUUID = forall (w :: WidgetType). IPythonWidget w -> UUID
uuid