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

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

module IHaskell.Display.Widgets.Controller.Controller
  ( -- * The Controller Widget
    Controller
    -- * Constructor
  , mkController
  ) where

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

import           Control.Monad (void)

import           Data.Aeson
import           Data.Aeson.Types (parse)
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
import           IHaskell.Display.Widgets.Layout.LayoutWidget

-- | 'Controller' represents an Controller widget from IPython.html.widgets.
type Controller = IPythonWidget 'ControllerType

-- | Create a new widget
mkController :: IO Controller
mkController :: IO Controller
mkController = do
  -- Default properties, with a random uuid
  UUID
wid <- IO UUID
U.random
  IPythonWidget 'LayoutType
layout <- IO (IPythonWidget 'LayoutType)
mkLayout

  let domAttrs :: Rec Attr (CoreWidgetClass ++ DOMWidgetClass)
domAttrs = Rec Attr CoreWidgetClass
defaultCoreWidget forall {k} (f :: k -> *) (as :: [k]) (bs :: [k]).
Rec f as -> Rec f bs -> Rec f (as ++ bs)
<+> FieldType 'ViewName
-> FieldType 'ModelName
-> IPythonWidget 'LayoutType
-> Rec Attr DOMWidgetClass
defaultDOMWidget Text
"ControllerView" Text
"ControllerModel" IPythonWidget 'LayoutType
layout
      ctrlAttrs :: Rec
  Attr
  '[ 'Index, 'Name, 'Mapping, 'Connected, 'Timestamp, 'Buttons,
     'Axes, 'ChangeHandler]
ctrlAttrs = (forall {a :: Field}. (a ~ 'Index) => SField a
Index forall (f :: Field).
(SingI f, Num (FieldType f), CustomBounded (FieldType f),
 Ord (FieldType f), Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:+ Integer
0)
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Name) => SField a
Name forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Text
"")
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Mapping) => SField a
Mapping forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Text
"")
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Connected) => SField a
Connected forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Bool
False)
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Timestamp) => SField a
Timestamp forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Double
0.0)
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Buttons) => SField a
Buttons forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! [])
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Axes) => SField a
Axes forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! [])
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'ChangeHandler) => SField a
ChangeHandler forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:: forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
                  forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& forall {u} (a :: u -> *). Rec a '[]
RNil
      widgetState :: WidgetState 'ControllerType
widgetState = forall (w :: WidgetType).
Rec Attr (WidgetFields w) -> WidgetState w
WidgetState forall a b. (a -> b) -> a -> b
$ Rec
  Attr
  ('ViewModule
     : 'ViewModuleVersion : 'ModelModule : 'ModelModuleVersion
     : DOMWidgetClass)
domAttrs forall {k} (f :: k -> *) (as :: [k]) (bs :: [k]).
Rec f as -> Rec f bs -> Rec f (as ++ bs)
<+> Rec
  Attr
  '[ 'Index, 'Name, 'Mapping, 'Connected, 'Timestamp, 'Buttons,
     'Axes, 'ChangeHandler]
ctrlAttrs

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

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

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

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

instance IHaskellWidget Controller where
  getCommUUID :: Controller -> UUID
getCommUUID = forall (w :: WidgetType). IPythonWidget w -> UUID
uuid
  comm :: Controller -> Value -> (Value -> IO ()) -> IO ()
comm Controller
widget Value
val Value -> IO ()
_ =
    case Value -> [Text] -> Maybe Value
nestedObjectLookup Value
val [Text
"state"] of
        Just (Object Object
o) -> do
            forall {f :: Field}.
(FromJSON (FieldType f),
 RecElem
   Rec
   f
   f
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   (RIndex
      f
      '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
         'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
         'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
         'Timestamp, 'Buttons, 'Axes, 'ChangeHandler])) =>
SField f -> Key -> IO ()
parseAndSet forall {a :: Field}. (a ~ 'Name) => SField a
Name Key
"name"
            forall {f :: Field}.
(FromJSON (FieldType f),
 RecElem
   Rec
   f
   f
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   (RIndex
      f
      '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
         'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
         'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
         'Timestamp, 'Buttons, 'Axes, 'ChangeHandler])) =>
SField f -> Key -> IO ()
parseAndSet forall {a :: Field}. (a ~ 'Mapping) => SField a
Mapping Key
"mapping"
            forall {f :: Field}.
(FromJSON (FieldType f),
 RecElem
   Rec
   f
   f
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   (RIndex
      f
      '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
         'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
         'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
         'Timestamp, 'Buttons, 'Axes, 'ChangeHandler])) =>
SField f -> Key -> IO ()
parseAndSet forall {a :: Field}. (a ~ 'Connected) => SField a
Connected Key
"connected"
            forall {f :: Field}.
(FromJSON (FieldType f),
 RecElem
   Rec
   f
   f
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
      'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
      'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
      'Timestamp, 'Buttons, 'Axes, 'ChangeHandler]
   (RIndex
      f
      '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
         'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
         'Layout, 'DisplayHandler, 'Index, 'Name, 'Mapping, 'Connected,
         'Timestamp, 'Buttons, 'Axes, 'ChangeHandler])) =>
SField f -> Key -> IO ()
parseAndSet forall {a :: Field}. (a ~ 'Timestamp) => SField a
Timestamp Key
"timestamp"
            forall (w :: WidgetType).
('ChangeHandler ∈ WidgetFields w) =>
IPythonWidget w -> IO ()
triggerChange Controller
widget
            where parseAndSet :: SField f -> Key -> IO ()
parseAndSet SField f
f Key
s = case forall a b. (a -> Parser b) -> a -> Result b
parse (forall a. FromJSON a => Object -> Key -> Parser a
.: Key
s) Object
o of
                    Success FieldType f
x -> forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w)) =>
IPythonWidget w -> SField f -> FieldType f -> IO (Attr f)
setField' Controller
widget SField f
f FieldType f
x
                    Result (FieldType f)
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Maybe Value
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()