{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module IHaskell.Display.Widgets.Output
(
OutputWidget
, mkOutput
, appendStdout
, appendStderr
, appendDisplay
, clearOutput
, clearOutput_
, replaceOutput
) where
import Prelude
import Data.Aeson
import Data.IORef (newIORef)
import Data.Text
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
import IHaskell.IPython.Types (StreamType(..))
import IHaskell.IPython.Message.UUID as U
import IHaskell.Display.Widgets.Types
import IHaskell.Display.Widgets.Common
import IHaskell.Display.Widgets.Layout.LayoutWidget
type OutputWidget = IPythonWidget 'OutputType
mkOutput :: IO OutputWidget
mkOutput :: IO OutputWidget
mkOutput = do
UUID
wid <- IO UUID
U.random
IPythonWidget 'LayoutType
layout <- IO (IPythonWidget 'LayoutType)
mkLayout
let domAttrs :: Rec Attr DOMWidgetClass
domAttrs = FieldType 'ViewName
-> FieldType 'ModelName
-> IPythonWidget 'LayoutType
-> Rec Attr DOMWidgetClass
defaultDOMWidget Text
"OutputView" Text
"OutputModel" IPythonWidget 'LayoutType
layout
outAttrs :: Rec
Attr
'[ 'ViewModule, 'ModelModule, 'ViewModuleVersion,
'ModelModuleVersion, 'MsgID, 'Outputs]
outAttrs = (forall {a :: Field}. (a ~ 'ViewModule) => SField a
ViewModule forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Text
"@jupyter-widgets/output")
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'ModelModule) => SField a
ModelModule forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Text
"@jupyter-widgets/output")
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'ViewModuleVersion) => SField a
ViewModuleVersion forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Text
"1.0.0")
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'ModelModuleVersion) => SField a
ModelModuleVersion forall (f :: Field).
(SingI f, Typeable (FieldType f)) =>
Sing f -> FieldType f -> Attr f
=:! Text
"1.0.0")
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall {a :: Field}. (a ~ 'MsgID) => SField a
MsgID 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 ~ 'Outputs) => SField a
Outputs 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 {u} (a :: u -> *). Rec a '[]
RNil
widgetState :: WidgetState 'OutputType
widgetState = forall (w :: WidgetType).
Rec Attr (WidgetFields w) -> WidgetState w
WidgetState forall a b. (a -> b) -> a -> b
$ Rec Attr DOMWidgetClass
domAttrs forall {k} (f :: k -> *) (as :: [k]) (bs :: [k]).
Rec f as -> Rec f bs -> Rec f (as ++ bs)
<+> Rec
Attr
'[ 'ViewModule, 'ModelModule, 'ViewModuleVersion,
'ModelModuleVersion, 'MsgID, 'Outputs]
outAttrs
IORef (WidgetState 'OutputType)
stateIO <- forall a. a -> IO (IORef a)
newIORef WidgetState 'OutputType
widgetState
let widget :: OutputWidget
widget = forall (w :: WidgetType).
UUID -> IORef (WidgetState w) -> IPythonWidget w
IPythonWidget UUID
wid IORef (WidgetState 'OutputType)
stateIO
forall a. IHaskellWidget a => a -> Value -> IO ()
widgetSendOpen OutputWidget
widget forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Value
toJSON WidgetState 'OutputType
widgetState
forall (m :: * -> *) a. Monad m => a -> m a
return OutputWidget
widget
appendStd :: StreamType -> OutputWidget -> Text -> IO ()
appendStd :: StreamType -> OutputWidget -> Text -> IO ()
appendStd StreamType
n OutputWidget
out Text
t = do
forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w) =>
IPythonWidget w -> SField f -> IO (FieldType f)
getField OutputWidget
out forall {a :: Field}. (a ~ 'Outputs) => SField a
Outputs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField OutputWidget
out forall {a :: Field}. (a ~ 'Outputs) => SField a
Outputs forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OutputMsg] -> [OutputMsg]
updateOutputs
where updateOutputs :: [OutputMsg] -> [OutputMsg]
updateOutputs :: [OutputMsg] -> [OutputMsg]
updateOutputs = (forall a. [a] -> [a] -> [a]
++[StreamType -> Text -> OutputMsg
OutputStream StreamType
n Text
t])
appendStdout :: OutputWidget -> Text -> IO ()
appendStdout :: OutputWidget -> Text -> IO ()
appendStdout = StreamType -> OutputWidget -> Text -> IO ()
appendStd StreamType
Stdout
appendStderr :: OutputWidget -> Text -> IO ()
appendStderr :: OutputWidget -> Text -> IO ()
appendStderr = StreamType -> OutputWidget -> Text -> IO ()
appendStd StreamType
Stderr
clearOutput' :: OutputWidget -> IO ()
clearOutput' :: OutputWidget -> IO ()
clearOutput' OutputWidget
w = do
()
_ <- forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField OutputWidget
w forall {a :: Field}. (a ~ 'Outputs) => SField a
Outputs []
()
_ <- forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField OutputWidget
w forall {a :: Field}. (a ~ 'MsgID) => SField a
MsgID Text
""
forall (m :: * -> *) a. Monad m => a -> m a
return ()
appendDisplay :: IHaskellDisplay a => OutputWidget -> a -> IO ()
appendDisplay :: forall a. IHaskellDisplay a => OutputWidget -> a -> IO ()
appendDisplay OutputWidget
o a
d = do
[OutputMsg]
outputs <- forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w) =>
IPythonWidget w -> SField f -> IO (FieldType f)
getField OutputWidget
o forall {a :: Field}. (a ~ 'Outputs) => SField a
Outputs
Display
disp <- forall a. IHaskellDisplay a => a -> IO Display
display a
d
()
_ <- forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField OutputWidget
o forall {a :: Field}. (a ~ 'Outputs) => SField a
Outputs forall a b. (a -> b) -> a -> b
$ [OutputMsg]
outputs forall a. [a] -> [a] -> [a]
++ [Display -> OutputMsg
OutputData Display
disp]
forall (m :: * -> *) a. Monad m => a -> m a
return ()
clearOutput :: OutputWidget -> IO ()
clearOutput :: OutputWidget -> IO ()
clearOutput OutputWidget
widget = Bool -> IO ()
widgetClearOutput Bool
False forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> OutputWidget -> IO ()
clearOutput' OutputWidget
widget
clearOutput_ :: OutputWidget -> IO ()
clearOutput_ :: OutputWidget -> IO ()
clearOutput_ OutputWidget
widget = Bool -> IO ()
widgetClearOutput Bool
True forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> OutputWidget -> IO ()
clearOutput' OutputWidget
widget
replaceOutput :: IHaskellDisplay a => OutputWidget -> a -> IO ()
replaceOutput :: forall a. IHaskellDisplay a => OutputWidget -> a -> IO ()
replaceOutput OutputWidget
widget a
d = do
Display
disp <- forall a. IHaskellDisplay a => a -> IO Display
display a
d
forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField OutputWidget
widget forall {a :: Field}. (a ~ 'Outputs) => SField a
Outputs [Display -> OutputMsg
OutputData Display
disp]
instance IHaskellWidget OutputWidget where
getCommUUID :: OutputWidget -> UUID
getCommUUID = forall (w :: WidgetType). IPythonWidget w -> UUID
uuid