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 ...@@ -40,10 +40,6 @@ import IHaskell.Display.Widgets.String.TextArea as X
import IHaskell.Display.Widgets.Common 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 (setField, getField, properties)
import IHaskell.Display.Widgets.Types as X ( triggerDisplay import IHaskell.Display.Widgets.Types as X (triggerDisplay, triggerChange, triggerClick,
, triggerChange triggerSelection, triggerSubmit,
, triggerClick ChildWidget(..))
, triggerSelection
, triggerSubmit
, ChildWidget (..)
)
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.Box ( module IHaskell.Display.Widgets.Box.Box (
-- * The Box widget -- * The Box widget
Box, Box,
-- * Constructor -- * Constructor
mkBox, mkBox) where
) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.FlexBox ( module IHaskell.Display.Widgets.Box.FlexBox (
-- * The FlexBox widget -- * The FlexBox widget
FlexBox, FlexBox,
-- * Constructor -- * Constructor
mkFlexBox, mkFlexBox) where
) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.SelectionContainer.Accordion ( module IHaskell.Display.Widgets.Box.SelectionContainer.Accordion (
-- * The Accordion widget -- * The Accordion widget
Accordion, Accordion,
-- * Constructor -- * Constructor
mkAccordion, mkAccordion) where
) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
...@@ -42,7 +41,8 @@ mkAccordion = do ...@@ -42,7 +41,8 @@ mkAccordion = do
stateIO <- newIORef widgetState stateIO <- newIORef widgetState
let box = IPythonWidget uuid stateIO 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 -- Open a comm for this widget, and store it in the kernel state
widgetSendOpen box initData $ toJSON widgetState widgetSendOpen box initData $ toJSON widgetState
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.SelectionContainer.Tab ( module IHaskell.Display.Widgets.Box.SelectionContainer.Tab (
-- * The Tab widget -- * The Tab widget
TabWidget, TabWidget,
-- * Constructor -- * Constructor
mkTabWidget, mkTabWidget) where
) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
......
...@@ -4,8 +4,9 @@ ...@@ -4,8 +4,9 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.BoundedFloatText ( module IHaskell.Display.Widgets.Float.BoundedFloat.BoundedFloatText (
-- * The BoundedFloatText Widget -- * The BoundedFloatText
BoundedFloatText, -- Widget
BoundedFloatText,
-- * Constructor -- * Constructor
mkBoundedFloatText) where mkBoundedFloatText) where
......
...@@ -4,15 +4,15 @@ ...@@ -4,15 +4,15 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.FloatProgress ( module IHaskell.Display.Widgets.Float.BoundedFloat.FloatProgress (
-- * The FloatProgress Widget -- * The FloatProgress Widget
FloatProgress, FloatProgress,
-- * Constructor -- * Constructor
mkFloatProgress) where mkFloatProgress) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
import Control.Exception (throw, ArithException (LossOfPrecision)) import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join) import Control.Monad (when, join)
import Data.Aeson import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
......
...@@ -4,8 +4,8 @@ ...@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.FloatSlider ( module IHaskell.Display.Widgets.Float.BoundedFloat.FloatSlider (
-- * The FloatSlider Widget -- * The FloatSlider Widget
FloatSlider, FloatSlider,
-- * Constructor -- * Constructor
mkFloatSlider) where mkFloatSlider) where
...@@ -48,9 +48,7 @@ mkFloatSlider = do ...@@ -48,9 +48,7 @@ mkFloatSlider = do
let widget = IPythonWidget uuid stateIO let widget = IPythonWidget uuid stateIO
initData = object initData = object
[ "model_name" .= str "WidgetModel" ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.FloatSlider"]
, "widget_class" .= str "IPython.FloatSlider"
]
-- Open a comm for this widget, and store it in the kernel state -- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState widgetSendOpen widget initData $ toJSON widgetState
......
...@@ -4,15 +4,16 @@ ...@@ -4,15 +4,16 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloatRange.FloatRangeSlider ( module IHaskell.Display.Widgets.Float.BoundedFloatRange.FloatRangeSlider (
-- * The FloatRangeSlider Widget -- * The FloatRangeSlider
FloatRangeSlider, -- Widget
FloatRangeSlider,
-- * Constructor -- * Constructor
mkFloatRangeSlider) where mkFloatRangeSlider) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
import Control.Exception (throw, ArithException (LossOfPrecision)) import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join, void) import Control.Monad (when, join, void)
import Data.Aeson import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
......
...@@ -4,8 +4,8 @@ ...@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.FloatText ( module IHaskell.Display.Widgets.Float.FloatText (
-- * The FloatText Widget -- * The FloatText Widget
FloatText, FloatText,
-- * Constructor -- * Constructor
mkFloatText) where mkFloatText) where
...@@ -41,7 +41,8 @@ mkFloatText = do ...@@ -41,7 +41,8 @@ mkFloatText = do
stateIO <- newIORef widgetState stateIO <- newIORef widgetState
let widget = IPythonWidget uuid stateIO 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 -- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState widgetSendOpen widget initData $ toJSON widgetState
......
...@@ -4,8 +4,8 @@ ...@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.BoundedIntText ( module IHaskell.Display.Widgets.Int.BoundedInt.BoundedIntText (
-- * The BoundedIntText Widget -- * The BoundedIntText Widget
BoundedIntText, BoundedIntText,
-- * Constructor -- * Constructor
mkBoundedIntText) where mkBoundedIntText) where
......
...@@ -4,15 +4,15 @@ ...@@ -4,15 +4,15 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.IntProgress ( module IHaskell.Display.Widgets.Int.BoundedInt.IntProgress (
-- * The IntProgress Widget -- * The IntProgress Widget
IntProgress, IntProgress,
-- * Constructor -- * Constructor
mkIntProgress) where mkIntProgress) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude import Prelude
import Control.Exception (throw, ArithException (LossOfPrecision)) import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join) import Control.Monad (when, join)
import Data.Aeson import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
...@@ -45,9 +45,7 @@ mkIntProgress = do ...@@ -45,9 +45,7 @@ mkIntProgress = do
let widget = IPythonWidget uuid stateIO let widget = IPythonWidget uuid stateIO
initData = object initData = object
[ "model_name" .= str "WidgetModel" ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.IntProgress"]
, "widget_class" .= str "IPython.IntProgress"
]
-- Open a comm for this widget, and store it in the kernel state -- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState widgetSendOpen widget initData $ toJSON widgetState
......
...@@ -4,8 +4,8 @@ ...@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.IntSlider ( module IHaskell.Display.Widgets.Int.BoundedInt.IntSlider (
-- * The IntSlider Widget -- * The IntSlider Widget
IntSlider, IntSlider,
-- * Constructor -- * Constructor
mkIntSlider) where mkIntSlider) where
...@@ -48,9 +48,7 @@ mkIntSlider = do ...@@ -48,9 +48,7 @@ mkIntSlider = do
let widget = IPythonWidget uuid stateIO let widget = IPythonWidget uuid stateIO
initData = object initData = object
[ "model_name" .= str "WidgetModel" ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.IntSlider"]
, "widget_class" .= str "IPython.IntSlider"
]
-- Open a comm for this widget, and store it in the kernel state -- Open a comm for this widget, and store it in the kernel state
widgetSendOpen widget initData $ toJSON widgetState widgetSendOpen widget initData $ toJSON widgetState
......
...@@ -4,8 +4,8 @@ ...@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedIntRange.IntRangeSlider ( module IHaskell.Display.Widgets.Int.BoundedIntRange.IntRangeSlider (
-- * The IntRangeSlider Widget -- * The IntRangeSlider Widget
IntRangeSlider, IntRangeSlider,
-- * Constructor -- * Constructor
mkIntRangeSlider) where mkIntRangeSlider) where
......
...@@ -4,8 +4,8 @@ ...@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.IntText ( module IHaskell.Display.Widgets.Int.IntText (
-- * The IntText Widget -- * The IntText Widget
IntText, IntText,
-- * Constructor -- * Constructor
mkIntText) where mkIntText) where
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.String.Text ( module IHaskell.Display.Widgets.String.Text (
-- * The Text Widget -- * The Text Widget
TextWidget, TextWidget,
-- * Constructor -- * Constructor
mkTextWidget, mkTextWidget) where
) where
-- To keep `cabal repl` happy when running from the ihaskell repo -- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude 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