Commit 74e36155 authored by David Davó's avatar David Davó

Updated Box widgets

parent f9abfc19
......@@ -64,6 +64,9 @@ library
IHaskell.Display.Widgets.ColorPicker
IHaskell.Display.Widgets.DatePicker
IHaskell.Display.Widgets.Box.Box
IHaskell.Display.Widgets.Box.GridBox
IHaskell.Display.Widgets.Box.HBox
IHaskell.Display.Widgets.Box.VBox
IHaskell.Display.Widgets.Box.SelectionContainer.Accordion
IHaskell.Display.Widgets.Box.SelectionContainer.Tab
IHaskell.Display.Widgets.Bool.CheckBox
......
......@@ -5,6 +5,9 @@ import IHaskell.Display.Widgets.ColorPicker as X
import IHaskell.Display.Widgets.DatePicker as X
import IHaskell.Display.Widgets.Box.Box as X
import IHaskell.Display.Widgets.Box.GridBox as X
import IHaskell.Display.Widgets.Box.HBox as X
import IHaskell.Display.Widgets.Box.VBox as X
import IHaskell.Display.Widgets.Box.SelectionContainer.Accordion as X
import IHaskell.Display.Widgets.Box.SelectionContainer.Tab as X
......
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module IHaskell.Display.Widgets.Box.GridBox
( -- * The GridBox widget
GridBox
-- * Constructor
, mkGridBox
) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
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
-- | A 'GridBox' represents a GridBox widget from IPython.html.widgets.
type GridBox = IPythonWidget 'GridBoxType
-- | Create a new GridBox
mkGridBox :: IO GridBox
mkGridBox = do
-- Default properties, with a random uuid
wid <- U.random
let widgetState = WidgetState $ defaultBoxWidget "GridBoxView" "GridBoxModel"
stateIO <- newIORef widgetState
let gridBox = IPythonWidget wid stateIO
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen gridBox $ toJSON widgetState
-- Return the widget
return gridBox
instance IHaskellWidget GridBox where
getCommUUID = uuid
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module IHaskell.Display.Widgets.Box.HBox
( -- * The HBox widget
HBox
-- * Constructor
, mkHBox
) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
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
-- | A 'HBox' represents a HBox widget from IPython.html.widgets.
type HBox = IPythonWidget 'HBoxType
-- | Create a new HBox
mkHBox :: IO HBox
mkHBox = do
-- Default properties, with a random uuid
wid <- U.random
let widgetState = WidgetState $ defaultBoxWidget "HBoxView" "HBoxModel"
stateIO <- newIORef widgetState
let hBox = IPythonWidget wid stateIO
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen hBox $ toJSON widgetState
-- Return the widget
return hBox
instance IHaskellWidget HBox where
getCommUUID = uuid
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module IHaskell.Display.Widgets.Box.VBox
( -- * The VBox widget
VBox
-- * Constructor
, mkVBox
) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
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
-- | A 'VBox' represents a VBox widget from IPython.html.widgets.
type VBox = IPythonWidget 'VBoxType
-- | Create a new VBox
mkVBox :: IO VBox
mkVBox = do
-- Default properties, with a random uuid
wid <- U.random
let widgetState = WidgetState $ defaultBoxWidget "VBoxView" "VBoxModel"
stateIO <- newIORef widgetState
let vbox = IPythonWidget wid stateIO
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen vbox $ toJSON widgetState
-- Return the widget
return vbox
instance IHaskellWidget VBox where
getCommUUID = uuid
......@@ -161,7 +161,7 @@ type FloatRangeClass = FloatClass :++ '[ 'S.FloatPairValue ]
type BoundedFloatRangeClass = FloatRangeClass :++ ['S.StepFloat, 'S.MinFloat, 'S.MaxFloat]
type BoxClass = DOMWidgetClass :++ ['S.Children, 'S.OverflowX, 'S.OverflowY, 'S.BoxStyle]
type BoxClass = CoreWidgetClass :++ DOMWidgetClass :++ ['S.Children, 'S.BoxStyle]
type SelectionContainerClass = BoxClass :++ ['S.Titles, 'S.SelectedIndex, 'S.ChangeHandler]
......@@ -322,6 +322,9 @@ data WidgetType = ButtonType
| FloatProgressType
| FloatRangeSliderType
| BoxType
| GridBoxType
| HBoxType
| VBoxType
| AccordionType
| TabType
| ControllerButtonType
......@@ -401,6 +404,9 @@ type family WidgetFields (w :: WidgetType) :: [Field] where
BoundedFloatRangeClass :++
['S.StepFloat, 'S.Orientation, 'S.ReadOut, 'S.ReadOutFormat, 'S.ContinuousUpdate, 'S.Disabled ]
WidgetFields 'BoxType = BoxClass
WidgetFields 'GridBoxType = BoxClass
WidgetFields 'HBoxType = BoxClass
WidgetFields 'VBoxType = BoxClass
WidgetFields 'AccordionType = SelectionContainerClass
WidgetFields 'TabType = SelectionContainerClass
WidgetFields 'ControllerType =
......@@ -907,11 +913,9 @@ defaultBoundedFloatRangeWidget viewName modelName = defaultFloatRangeWidget view
-- | A record representing a widget of the _Box class from IPython
defaultBoxWidget :: FieldType 'S.ViewName -> FieldType 'S.ModelName -> Rec Attr BoxClass
defaultBoxWidget viewName modelName = defaultDOMWidget viewName modelName <+> intAttrs
defaultBoxWidget viewName modelName = defaultCoreWidget <+> defaultDOMWidget viewName modelName <+> intAttrs
where
intAttrs = (Children =:: [])
:& (OverflowX =:: DefaultOverflow)
:& (OverflowY =:: DefaultOverflow)
:& (BoxStyle =:: DefaultBox)
:& RNil
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment