Commit 44b39799 authored by Sumit Sahrawat's avatar Sumit Sahrawat

Formatting + Remove examples (for now)

parent b87b0927
......@@ -40,10 +40,6 @@ import IHaskell.Display.Widgets.String.TextArea as X
import IHaskell.Display.Widgets.Common as X
import IHaskell.Display.Widgets.Types as X (setField, getField, properties)
import IHaskell.Display.Widgets.Types as X ( triggerDisplay
, triggerChange
, triggerClick
, triggerSelection
, triggerSubmit
, ChildWidget (..)
)
import IHaskell.Display.Widgets.Types as X (triggerDisplay, triggerChange, triggerClick,
triggerSelection, triggerSubmit,
ChildWidget(..))
......@@ -5,9 +5,9 @@
module IHaskell.Display.Widgets.Bool.CheckBox (
-- * The CheckBox Widget
CheckBox,
-- * Constructor
mkCheckBox) where
CheckBox,
-- * Constructor
mkCheckBox) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -5,7 +5,7 @@
module IHaskell.Display.Widgets.Bool.ToggleButton (
-- * The ToggleButton Widget
ToggleButton,
ToggleButton,
-- * Constructor
mkToggleButton) where
......
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.Box (
-- * The Box widget
Box,
-- * Constructor
mkBox,
) where
-- * The Box widget
Box,
-- * Constructor
mkBox) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.FlexBox (
-- * The FlexBox widget
FlexBox,
-- * Constructor
mkFlexBox,
) where
-- * The FlexBox widget
FlexBox,
-- * Constructor
mkFlexBox) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......@@ -38,10 +37,10 @@ mkFlexBox = do
let boxAttrs = defaultBoxWidget "FlexBoxView"
flxAttrs = (SOrientation =:: HorizontalOrientation)
:& (SFlex =:: 0)
:& (SPack =:: StartLocation)
:& (SAlign =:: StartLocation)
:& RNil
:& (SFlex =:: 0)
:& (SPack =:: StartLocation)
:& (SAlign =:: StartLocation)
:& RNil
widgetState = WidgetState $ boxAttrs <+> flxAttrs
stateIO <- newIORef widgetState
......
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.SelectionContainer.Accordion (
-- * The Accordion widget
Accordion,
-- * Constructor
mkAccordion,
) where
-- * The Accordion widget
Accordion,
-- * Constructor
mkAccordion) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......@@ -42,7 +41,8 @@ mkAccordion = do
stateIO <- newIORef widgetState
let box = IPythonWidget uuid stateIO
initData = object ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Accordion"]
initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Accordion"]
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen box initData $ toJSON widgetState
......
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.SelectionContainer.Tab (
-- * The Tab widget
TabWidget,
-- * Constructor
mkTabWidget,
) where
-- * The Tab widget
TabWidget,
-- * Constructor
mkTabWidget) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -5,7 +5,7 @@
module IHaskell.Display.Widgets.Button (
-- * The Button Widget
Button,
Button,
-- * Create a new button
mkButton) where
......
......@@ -4,10 +4,11 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.BoundedFloatText (
-- * The BoundedFloatText Widget
BoundedFloatText,
-- * Constructor
mkBoundedFloatText) where
-- * The BoundedFloatText
-- Widget
BoundedFloatText,
-- * Constructor
mkBoundedFloatText) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -4,15 +4,15 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.FloatProgress (
-- * The FloatProgress Widget
FloatProgress,
-- * Constructor
mkFloatProgress) where
-- * The FloatProgress Widget
FloatProgress,
-- * Constructor
mkFloatProgress) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Exception (throw, ArithException (LossOfPrecision))
import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
......
......@@ -4,10 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.FloatSlider (
-- * The FloatSlider Widget
FloatSlider,
-- * Constructor
mkFloatSlider) where
-- * The FloatSlider Widget
FloatSlider,
-- * Constructor
mkFloatSlider) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......@@ -38,19 +38,17 @@ mkFloatSlider = do
let boundedFloatAttrs = defaultBoundedFloatWidget "FloatSliderView"
sliderAttrs = (SOrientation =:: HorizontalOrientation)
:& (SShowRange =:: False)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
:& (SShowRange =:: False)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
widgetState = WidgetState $ boundedFloatAttrs <+> sliderAttrs
stateIO <- newIORef widgetState
let widget = IPythonWidget uuid stateIO
initData = object
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.FloatSlider"
]
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.FloatSlider"]
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState
......
......@@ -4,15 +4,16 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloatRange.FloatRangeSlider (
-- * The FloatRangeSlider Widget
FloatRangeSlider,
-- * Constructor
mkFloatRangeSlider) where
-- * The FloatRangeSlider
-- Widget
FloatRangeSlider,
-- * Constructor
mkFloatRangeSlider) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Exception (throw, ArithException (LossOfPrecision))
import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
......@@ -40,10 +41,10 @@ mkFloatRangeSlider = do
let boundedFloatAttrs = defaultBoundedFloatRangeWidget "FloatSliderView"
sliderAttrs = (SOrientation =:: HorizontalOrientation)
:& (SShowRange =:: True)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
:& (SShowRange =:: True)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
widgetState = WidgetState $ boundedFloatAttrs <+> sliderAttrs
stateIO <- newIORef widgetState
......
......@@ -4,10 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.FloatText (
-- * The FloatText Widget
FloatText,
-- * Constructor
mkFloatText) where
-- * The FloatText Widget
FloatText,
-- * Constructor
mkFloatText) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......@@ -41,7 +41,8 @@ mkFloatText = do
stateIO <- newIORef widgetState
let widget = IPythonWidget uuid stateIO
initData = object ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.FloatText"]
initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.FloatText"]
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState
......
......@@ -5,7 +5,7 @@
module IHaskell.Display.Widgets.Image (
-- * The Image Widget
ImageWidget,
ImageWidget,
-- * Constructor
mkImageWidget) where
......
......@@ -4,10 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.BoundedIntText (
-- * The BoundedIntText Widget
BoundedIntText,
-- * Constructor
mkBoundedIntText) where
-- * The BoundedIntText Widget
BoundedIntText,
-- * Constructor
mkBoundedIntText) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -4,15 +4,15 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.IntProgress (
-- * The IntProgress Widget
IntProgress,
-- * Constructor
mkIntProgress) where
-- * The IntProgress Widget
IntProgress,
-- * Constructor
mkIntProgress) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Exception (throw, ArithException (LossOfPrecision))
import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
......@@ -45,9 +45,7 @@ mkIntProgress = do
let widget = IPythonWidget uuid stateIO
initData = object
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.IntProgress"
]
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.IntProgress"]
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState
......
......@@ -4,10 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.IntSlider (
-- * The IntSlider Widget
IntSlider,
-- * Constructor
mkIntSlider) where
-- * The IntSlider Widget
IntSlider,
-- * Constructor
mkIntSlider) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......@@ -38,19 +38,17 @@ mkIntSlider = do
let boundedIntAttrs = defaultBoundedIntWidget "IntSliderView"
sliderAttrs = (SOrientation =:: HorizontalOrientation)
:& (SShowRange =:: False)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
:& (SShowRange =:: False)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
widgetState = WidgetState $ boundedIntAttrs <+> sliderAttrs
stateIO <- newIORef widgetState
let widget = IPythonWidget uuid stateIO
initData = object
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.IntSlider"
]
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.IntSlider"]
-- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState
......
......@@ -4,10 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedIntRange.IntRangeSlider (
-- * The IntRangeSlider Widget
IntRangeSlider,
-- * Constructor
mkIntRangeSlider) where
-- * The IntRangeSlider Widget
IntRangeSlider,
-- * Constructor
mkIntRangeSlider) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......@@ -39,10 +39,10 @@ mkIntRangeSlider = do
let boundedIntAttrs = defaultBoundedIntRangeWidget "IntSliderView"
sliderAttrs = (SOrientation =:: HorizontalOrientation)
:& (SShowRange =:: True)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
:& (SShowRange =:: True)
:& (SReadOut =:: True)
:& (SSliderColor =:: "")
:& RNil
widgetState = WidgetState $ boundedIntAttrs <+> sliderAttrs
stateIO <- newIORef widgetState
......
......@@ -4,10 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.IntText (
-- * The IntText Widget
IntText,
-- * Constructor
mkIntText) where
-- * The IntText Widget
IntText,
-- * Constructor
mkIntText) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -5,7 +5,7 @@
module IHaskell.Display.Widgets.Selection.Dropdown (
-- * The Dropdown Widget
Dropdown,
Dropdown,
-- * Constructor
mkDropdown) where
......
......@@ -5,7 +5,7 @@
module IHaskell.Display.Widgets.Selection.RadioButtons (
-- * The RadioButtons Widget
RadioButtons,
RadioButtons,
-- * Constructor
mkRadioButtons) where
......
......@@ -5,9 +5,9 @@
module IHaskell.Display.Widgets.Selection.Select (
-- * The Select Widget
Select,
-- * Constructor
mkSelect) where
Select,
-- * Constructor
mkSelect) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -5,9 +5,9 @@
module IHaskell.Display.Widgets.Selection.SelectMultiple (
-- * The SelectMultiple Widget
SelectMultiple,
-- * Constructor
mkSelectMultiple) where
SelectMultiple,
-- * Constructor
mkSelectMultiple) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -5,7 +5,7 @@
module IHaskell.Display.Widgets.Selection.ToggleButtons (
-- * The ToggleButtons Widget
ToggleButtons,
ToggleButtons,
-- * Constructor
mkToggleButtons) where
......
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.String.Text (
-- * The Text Widget
TextWidget,
-- * Constructor
mkTextWidget,
) where
-- * The Text Widget
TextWidget,
-- * Constructor
mkTextWidget) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -5,9 +5,9 @@
module IHaskell.Display.Widgets.String.TextArea (
-- * The TextArea Widget
TextArea,
-- * Constructor
mkTextArea) where
TextArea,
-- * Constructor
mkTextArea) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
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