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

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

module IHaskell.Display.Widgets.String.Text
  ( -- * The Text Widget
    TextWidget
    -- * Constructor
  , mkText
  ) where

-- To keep `cabal repl` happy when running from the ihaskell repo
import           Prelude

import           Control.Monad (when)
import           Data.Aeson
import           Data.IORef (newIORef)

import           IHaskell.Display
import           IHaskell.Eval.Widgets
import           IHaskell.IPython.Message.UUID as U

import           IHaskell.Display.Widgets.Types
import           IHaskell.Display.Widgets.Common
import           IHaskell.Display.Widgets.Layout.LayoutWidget
import           IHaskell.Display.Widgets.Style.DescriptionStyle

-- | A 'TextWidget' represents a Text widget from IPython.html.widgets.
type TextWidget = IPythonWidget 'TextType

-- | Create a new Text widget
mkText :: IO TextWidget
mkText :: IO TextWidget
mkText = do
  -- Default properties, with a random uuid
  UUID
wid <- IO UUID
U.random
  IPythonWidget 'LayoutType
layout <- IO (IPythonWidget 'LayoutType)
mkLayout
  DescriptionStyle
dstyle <- IO DescriptionStyle
mkDescriptionStyle

  let widgetState :: WidgetState 'TextType
widgetState = forall (w :: WidgetType).
Rec Attr (WidgetFields w) -> WidgetState w
WidgetState forall a b. (a -> b) -> a -> b
$ FieldType 'ViewName
-> FieldType 'ModelName
-> IPythonWidget 'LayoutType
-> StyleWidget
-> Rec Attr TextClass
defaultTextWidget Text
"TextView" Text
"TextModel" IPythonWidget 'LayoutType
layout forall a b. (a -> b) -> a -> b
$ forall (w :: WidgetType).
RecAll Attr (WidgetFields w) ToPairs =>
IPythonWidget w -> StyleWidget
StyleWidget DescriptionStyle
dstyle

  IORef (WidgetState 'TextType)
stateIO <- forall a. a -> IO (IORef a)
newIORef WidgetState 'TextType
widgetState

  let widget :: TextWidget
widget = forall (w :: WidgetType).
UUID -> IORef (WidgetState w) -> IPythonWidget w
IPythonWidget UUID
wid IORef (WidgetState 'TextType)
stateIO

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

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

instance IHaskellWidget TextWidget where
  getCommUUID :: TextWidget -> UUID
getCommUUID = forall (w :: WidgetType). IPythonWidget w -> UUID
uuid
  -- Two possibilities: 1. content -> event -> "submit" 2. state -> value -> <new_value>
  comm :: TextWidget -> Value -> (Value -> IO ()) -> IO ()
comm TextWidget
tw Value
val Value -> IO ()
_ = do
    case Value -> [Text] -> Maybe Value
nestedObjectLookup Value
val [Text
"state", Text
"value"] of
      Just (String Text
value) -> forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w)) =>
IPythonWidget w -> SField f -> FieldType f -> IO (Attr f)
setField' TextWidget
tw forall {a :: Field}. (a ~ 'StringValue) => SField a
StringValue Text
value forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (w :: WidgetType).
('ChangeHandler ∈ WidgetFields w) =>
IPythonWidget w -> IO ()
triggerChange TextWidget
tw
      Maybe Value
_                 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    case Value -> [Text] -> Maybe Value
nestedObjectLookup Value
val [Text
"content", Text
"event"] of
      Just (String Text
event) -> forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
event forall a. Eq a => a -> a -> Bool
== Text
"submit") forall a b. (a -> b) -> a -> b
$ forall (w :: WidgetType).
('SubmitHandler ∈ WidgetFields w) =>
IPythonWidget w -> IO ()
triggerSubmit TextWidget
tw
      Maybe Value
_                   -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()