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(..))
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Box.Box (
-- * The Box widget
Box,
-- * The Box widget
Box,
-- * Constructor
mkBox,
) where
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,
-- * The FlexBox widget
FlexBox,
-- * Constructor
mkFlexBox,
) where
mkFlexBox) 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.SelectionContainer.Accordion (
-- * The Accordion widget
Accordion,
-- * The Accordion widget
Accordion,
-- * Constructor
mkAccordion,
) where
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,
-- * The Tab widget
TabWidget,
-- * Constructor
mkTabWidget,
) where
mkTabWidget) where
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
......
......@@ -4,8 +4,9 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.BoundedFloatText (
-- * The BoundedFloatText Widget
BoundedFloatText,
-- * The BoundedFloatText
-- Widget
BoundedFloatText,
-- * Constructor
mkBoundedFloatText) where
......
......@@ -4,15 +4,15 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.FloatProgress (
-- * The FloatProgress Widget
FloatProgress,
-- * 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,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.BoundedFloat.FloatSlider (
-- * The FloatSlider Widget
FloatSlider,
-- * The FloatSlider Widget
FloatSlider,
-- * Constructor
mkFloatSlider) where
......@@ -48,9 +48,7 @@ mkFloatSlider = do
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,
-- * 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
......
......@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Float.FloatText (
-- * The FloatText Widget
FloatText,
-- * The FloatText Widget
FloatText,
-- * Constructor
mkFloatText) where
......@@ -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
......
......@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.BoundedIntText (
-- * The BoundedIntText Widget
BoundedIntText,
-- * The BoundedIntText Widget
BoundedIntText,
-- * Constructor
mkBoundedIntText) where
......
......@@ -4,15 +4,15 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.IntProgress (
-- * The IntProgress Widget
IntProgress,
-- * 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,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedInt.IntSlider (
-- * The IntSlider Widget
IntSlider,
-- * The IntSlider Widget
IntSlider,
-- * Constructor
mkIntSlider) where
......@@ -48,9 +48,7 @@ mkIntSlider = do
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,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.BoundedIntRange.IntRangeSlider (
-- * The IntRangeSlider Widget
IntRangeSlider,
-- * The IntRangeSlider Widget
IntRangeSlider,
-- * Constructor
mkIntRangeSlider) where
......
......@@ -4,8 +4,8 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Int.IntText (
-- * The IntText Widget
IntText,
-- * The IntText Widget
IntText,
-- * Constructor
mkIntText) where
......
......@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.String.Text (
-- * The Text Widget
TextWidget,
-- * The Text Widget
TextWidget,
-- * Constructor
mkTextWidget,
) where
mkTextWidget) 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