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

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

module IHaskell.Display.Widgets.Media.Image
  ( -- * The Image Widget
    ImageWidget
    -- * Constructor
  , mkImage
  ) 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
import           IHaskell.Display.Widgets.Layout.LayoutWidget

-- | An 'ImageWidget' represents a Image widget from IPython.html.widgets.
type ImageWidget = IPythonWidget 'ImageType

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

  let mediaAttrs :: Rec Attr MediaClass
mediaAttrs = FieldType 'ViewName
-> FieldType 'ModelName
-> IPythonWidget 'LayoutType
-> Rec Attr MediaClass
defaultMediaWidget Text
"ImageView" Text
"ImageModel" IPythonWidget 'LayoutType
layout
      imageAttrs :: Rec Attr '[ 'ImageFormat, 'Width, 'Height]
imageAttrs = (forall {a :: Field}. (a ~ 'ImageFormat) => SField a
ImageFormat forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:: ImageFormatValue
PNG)
                   forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Width) => SField a
Width forall (f :: Field).
(SingI f, Num (FieldType f), CustomBounded (FieldType f),
 Ord (FieldType f), Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:+ PixCount
0)
                   forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'Height) => SField a
Height forall (f :: Field).
(SingI f, Num (FieldType f), CustomBounded (FieldType f),
 Ord (FieldType f), Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:+ PixCount
0)
                   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 'ImageType
widgetState = forall (w :: WidgetType).
Rec Attr (WidgetFields w) -> WidgetState w
WidgetState (Rec
  Attr
  '[ 'ViewModule, 'ViewModuleVersion, 'ModelModule,
     'ModelModuleVersion, 'ModelName, 'ViewName, 'DOMClasses, 'Tooltip,
     'Layout, 'DisplayHandler, 'BSValue]
mediaAttrs forall {k} (f :: k -> *) (as :: [k]) (bs :: [k]).
Rec f as -> Rec f bs -> Rec f (as ++ bs)
<+> Rec Attr '[ 'ImageFormat, 'Width, 'Height]
imageAttrs)

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

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

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

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

instance IHaskellWidget ImageWidget where
  getCommUUID :: ImageWidget -> UUID
getCommUUID = forall (w :: WidgetType). IPythonWidget w -> UUID
uuid
  getBufferPaths :: ImageWidget -> [[Text]]
getBufferPaths ImageWidget
_ = [[Text
"value"]]