Commit 16d38400 authored by Andrei Barbu's avatar Andrei Barbu

FlexBox is gone

parent 79ade02c
...@@ -57,7 +57,6 @@ library ...@@ -57,7 +57,6 @@ library
-- Modules included in this library but not exported. -- Modules included in this library but not exported.
other-modules: IHaskell.Display.Widgets.Button other-modules: IHaskell.Display.Widgets.Button
IHaskell.Display.Widgets.Box.Box IHaskell.Display.Widgets.Box.Box
IHaskell.Display.Widgets.Box.FlexBox
IHaskell.Display.Widgets.Box.SelectionContainer.Accordion IHaskell.Display.Widgets.Box.SelectionContainer.Accordion
IHaskell.Display.Widgets.Box.SelectionContainer.Tab IHaskell.Display.Widgets.Box.SelectionContainer.Tab
IHaskell.Display.Widgets.Bool.CheckBox IHaskell.Display.Widgets.Bool.CheckBox
......
...@@ -3,7 +3,6 @@ module IHaskell.Display.Widgets (module X) where ...@@ -3,7 +3,6 @@ module IHaskell.Display.Widgets (module X) where
import IHaskell.Display.Widgets.Button as X import IHaskell.Display.Widgets.Button as X
import IHaskell.Display.Widgets.Box.Box as X import IHaskell.Display.Widgets.Box.Box as X
import IHaskell.Display.Widgets.Box.FlexBox as X
import IHaskell.Display.Widgets.Box.SelectionContainer.Accordion as X import IHaskell.Display.Widgets.Box.SelectionContainer.Accordion as X
import IHaskell.Display.Widgets.Box.SelectionContainer.Tab as X import IHaskell.Display.Widgets.Box.SelectionContainer.Tab as X
......
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.FlexBox (
-- * The FlexBox widget
FlexBox,
-- * Constructor
mkFlexBox) 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
-- | A 'FlexBox' represents a FlexBox widget from IPython.html.widgets.
type FlexBox = IPythonWidget FlexBoxType
-- | Create a new box
mkFlexBox :: IO FlexBox
mkFlexBox = do
-- Default properties, with a random uuid
uuid <- U.random
let boxAttrs = defaultBoxWidget "FlexBoxView" "FlexBoxModel"
flxAttrs = (Orientation =:: HorizontalOrientation)
:& (Flex =:: 0)
:& (Pack =:: StartLocation)
:& (Align =:: StartLocation)
:& RNil
widgetState = WidgetState $ boxAttrs <+> flxAttrs
stateIO <- newIORef widgetState
let box = IPythonWidget uuid stateIO
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen box $ toJSON widgetState
-- Return the widget
return box
instance IHaskellDisplay FlexBox where
display b = do
widgetSendView b
return $ Display []
instance IHaskellWidget FlexBox where
getCommUUID = uuid
...@@ -25,7 +25,7 @@ import IHaskell.Display.Widgets.Types ...@@ -25,7 +25,7 @@ import IHaskell.Display.Widgets.Types
import IHaskell.Display.Widgets.Common import IHaskell.Display.Widgets.Common
import qualified IHaskell.Display.Widgets.Singletons as S (SField, Field(..)) import qualified IHaskell.Display.Widgets.Singletons as S (SField, Field(..))
import IHaskell.Display.Widgets.Box.FlexBox import IHaskell.Display.Widgets.Box.Box
import IHaskell.Display.Widgets.Bool.CheckBox import IHaskell.Display.Widgets.Bool.CheckBox
import IHaskell.Display.Widgets.String.Text import IHaskell.Display.Widgets.String.Text
import IHaskell.Display.Widgets.Int.BoundedInt.IntSlider import IHaskell.Display.Widgets.Int.BoundedInt.IntSlider
...@@ -120,23 +120,23 @@ instance (FromWidget t, MakeConfs ts) => MakeConfs (t ': ts) where ...@@ -120,23 +120,23 @@ instance (FromWidget t, MakeConfs ts) => MakeConfs (t ': ts) where
mkConfs _ = WidgetConf wrapped :& mkConfs (Proxy :: Proxy ts) mkConfs _ = WidgetConf wrapped :& mkConfs (Proxy :: Proxy ts)
interactive :: (IHaskellDisplay r, MakeConfs ts) interactive :: (IHaskellDisplay r, MakeConfs ts)
=> (HList ts -> r) -> Rec Argument ts -> IO FlexBox => (HList ts -> r) -> Rec Argument ts -> IO Box
interactive func = interactive func =
let confs = mkConfs Proxy let confs = mkConfs Proxy
in liftToWidgets func confs in liftToWidgets func confs
-- | Transform a function (HList ts -> r) to one which: 1) Uses widgets to accept the arguments 2) -- | Transform a function (HList ts -> r) to one which: 1) Uses widgets to accept the arguments 2)
-- Accepts initial values for the arguments 3) Creates a compound FlexBox widget with an embedded -- Accepts initial values for the arguments 3) Creates a compound Box widget with an embedded
-- OutputWidget for display -- OutputWidget for display
liftToWidgets :: IHaskellDisplay r liftToWidgets :: IHaskellDisplay r
=> (HList ts -> r) -> Rec WidgetConf ts -> Rec Argument ts -> IO FlexBox => (HList ts -> r) -> Rec WidgetConf ts -> Rec Argument ts -> IO Box
liftToWidgets func rc initvals = do liftToWidgets func rc initvals = do
let constructors = rmap extractConstructor rc let constructors = rmap extractConstructor rc
getters = rmap extractGetter rc getters = rmap extractGetter rc
eventSetters = rmap extractEventSetter rc eventSetters = rmap extractEventSetter rc
initializers = rmap extractInitializer rc initializers = rmap extractInitializer rc
bx <- mkFlexBox bx <- mkBox
out <- mkOutputWidget out <- mkOutputWidget
-- Create a list of widgets -- Create a list of widgets
...@@ -153,9 +153,11 @@ liftToWidgets func rc initvals = do ...@@ -153,9 +153,11 @@ liftToWidgets func rc initvals = do
setInitialValues initializers widgets initvals setInitialValues initializers widgets initvals
-- applyValueSetters valueSetters widgets $ getList defvals -- applyValueSetters valueSetters widgets $ getList defvals
setField out Width 500 setField out Width 500
setField bx Orientation VerticalOrientation -- TODO This can't be set right now since we switched FlexBox to a regular
-- Box. This is a styling/layout parameter now but these haven't been implemented yet.
-- setField bx Orientation VerticalOrientation
-- Set children for the FlexBox -- Set children for the Box
let children = mkChildren widgets let children = mkChildren widgets
setField bx Children $ children ++ [ChildWidget out] setField bx Children $ children ++ [ChildWidget out]
......
...@@ -263,7 +263,6 @@ data WidgetType = ButtonType ...@@ -263,7 +263,6 @@ data WidgetType = ButtonType
| FloatProgressType | FloatProgressType
| FloatRangeSliderType | FloatRangeSliderType
| BoxType | BoxType
| FlexBoxType
| AccordionType | AccordionType
| TabType | TabType
...@@ -313,8 +312,6 @@ type family WidgetFields (w :: WidgetType) :: [Field] where ...@@ -313,8 +312,6 @@ type family WidgetFields (w :: WidgetType) :: [Field] where
BoundedFloatRangeClass :++ BoundedFloatRangeClass :++
'[S.Orientation, S.ShowRange, S.ReadOut, S.SliderColor] '[S.Orientation, S.ShowRange, S.ReadOut, S.SliderColor]
WidgetFields BoxType = BoxClass WidgetFields BoxType = BoxClass
WidgetFields FlexBoxType =
BoxClass :++ '[S.Orientation, S.Flex, S.Pack, S.Align]
WidgetFields AccordionType = SelectionContainerClass WidgetFields AccordionType = SelectionContainerClass
WidgetFields TabType = SelectionContainerClass WidgetFields TabType = SelectionContainerClass
......
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