Commit e1dafd07 authored by Sumit Sahrawat's avatar Sumit Sahrawat

Fix formatting issues

- Make verify_formatting.py skip Types.hs and Common.hs
- Fix formatting issues in rest of the files
parent 112c046b
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Bool.CheckBox ( module IHaskell.Display.Widgets.Bool.CheckBox (
-- * The CheckBox Widget -- * The CheckBox Widget
CheckBoxWidget, CheckBoxWidget,
-- * Constructor -- * Constructor
mkCheckBoxWidget, mkCheckBoxWidget) 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
...@@ -18,7 +17,7 @@ import Data.Aeson ...@@ -18,7 +17,7 @@ import Data.Aeson
import Data.HashMap.Strict as HM import Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -41,7 +40,8 @@ mkCheckBoxWidget = do ...@@ -41,7 +40,8 @@ mkCheckBoxWidget = 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.Checkbox"] initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Checkbox"]
-- 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,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Bool.ToggleButton ( module IHaskell.Display.Widgets.Bool.ToggleButton (
-- * The ToggleButton Widget -- * The ToggleButton Widget
ToggleButton, ToggleButton,
-- * Constructor -- * Constructor
mkToggleButton, mkToggleButton) 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
...@@ -18,7 +17,7 @@ import Data.Aeson ...@@ -18,7 +17,7 @@ import Data.Aeson
import Data.HashMap.Strict as HM import Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -38,15 +37,16 @@ mkToggleButton = do ...@@ -38,15 +37,16 @@ mkToggleButton = do
let boolState = defaultBoolWidget "ToggleButtonView" let boolState = defaultBoolWidget "ToggleButtonView"
toggleState = (STooltip =:: "") toggleState = (STooltip =:: "")
:& (SIcon =:: "") :& (SIcon =:: "")
:& (SButtonStyle =:: DefaultButton) :& (SButtonStyle =:: DefaultButton)
:& RNil :& RNil
widgetState = WidgetState (boolState <+> toggleState) widgetState = WidgetState (boolState <+> toggleState)
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.ToggleButton"] initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.ToggleButton"]
-- 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,13 +4,12 @@ ...@@ -4,13 +4,12 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Button ( module IHaskell.Display.Widgets.Button (
-- * The Button Widget -- * The Button Widget
Button, Button,
-- * Create a new button -- * Create a new button
mkButton, mkButton,
-- * Click manipulation -- * Click manipulation
triggerClick, triggerClick) 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
...@@ -20,7 +19,7 @@ import Data.Aeson ...@@ -20,7 +19,7 @@ import Data.Aeson
import Data.HashMap.Strict as HM import Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -40,22 +39,19 @@ mkButton = do ...@@ -40,22 +39,19 @@ mkButton = do
let dom = defaultDOMWidget "ButtonView" let dom = defaultDOMWidget "ButtonView"
but = (SDescription =:: "") but = (SDescription =:: "")
:& (STooltip =:: "") :& (STooltip =:: "")
:& (SDisabled =:: False) :& (SDisabled =:: False)
:& (SIcon =:: "") :& (SIcon =:: "")
:& (SButtonStyle =:: DefaultButton) :& (SButtonStyle =:: DefaultButton)
:& (SClickHandler =:: return ()) :& (SClickHandler =:: return ())
:& RNil :& RNil
buttonState = WidgetState (dom <+> but) buttonState = WidgetState (dom <+> but)
stateIO <- newIORef buttonState stateIO <- newIORef buttonState
let button = IPythonWidget uuid stateIO let button = IPythonWidget uuid stateIO
let initData = object let initData = object ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Button"]
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.Button"
]
-- 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 button initData $ toJSON buttonState widgetSendOpen button initData $ toJSON buttonState
......
...@@ -158,3 +158,6 @@ instance ToJSON ImageFormatValue where ...@@ -158,3 +158,6 @@ instance ToJSON ImageFormatValue where
-- | Options for selection widgets. -- | Options for selection widgets.
data SelectionOptions = OptionLabels [Text] | OptionDict [(Text, Text)] data SelectionOptions = OptionLabels [Text] | OptionDict [(Text, Text)]
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Image ( module IHaskell.Display.Widgets.Image (
-- * The Image Widget -- * The Image Widget
ImageWidget, ImageWidget,
-- * Constructor -- * Constructor
mkImageWidget, mkImageWidget) 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
...@@ -19,7 +18,7 @@ import Data.HashMap.Strict as HM ...@@ -19,7 +18,7 @@ import Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Monoid (mempty) import Data.Monoid (mempty)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -39,18 +38,15 @@ mkImageWidget = do ...@@ -39,18 +38,15 @@ mkImageWidget = do
let dom = defaultDOMWidget "ImageView" let dom = defaultDOMWidget "ImageView"
img = (SImageFormat =:: PNG) img = (SImageFormat =:: PNG)
:& (SB64Value =:: mempty) :& (SB64Value =:: mempty)
:& RNil :& RNil
widgetState = WidgetState (dom <+> img) widgetState = WidgetState (dom <+> img)
stateIO <- newIORef widgetState stateIO <- newIORef widgetState
let widget = IPythonWidget uuid stateIO let widget = IPythonWidget uuid stateIO
let initData = object let initData = object ["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Image"]
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.Image"
]
-- 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
......
...@@ -23,7 +23,7 @@ import Data.Aeson ...@@ -23,7 +23,7 @@ import Data.Aeson
import Data.HashMap.Strict as HM import Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Selection.Dropdown ( module IHaskell.Display.Widgets.Selection.Dropdown (
-- * The Dropdown Widget -- * The Dropdown Widget
Dropdown, Dropdown,
-- * Constructor -- * Constructor
mkDropdown, mkDropdown) 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
...@@ -18,7 +17,7 @@ import Data.Aeson ...@@ -18,7 +17,7 @@ import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -42,7 +41,8 @@ mkDropdown = do ...@@ -42,7 +41,8 @@ mkDropdown = 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.Dropdown"] initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Dropdown"]
-- 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
...@@ -71,9 +71,10 @@ instance IHaskellWidget Dropdown where ...@@ -71,9 +71,10 @@ instance IHaskellWidget Dropdown where
OptionLabels _ -> do OptionLabels _ -> do
setField' widget SSelectedLabel label setField' widget SSelectedLabel label
setField' widget SSelectedValue label setField' widget SSelectedValue label
OptionDict ps -> case lookup label ps of OptionDict ps ->
Nothing -> return () case lookup label ps of
Just value -> do Nothing -> return ()
setField' widget SSelectedLabel label Just value -> do
setField' widget SSelectedValue value setField' widget SSelectedLabel label
setField' widget SSelectedValue value
triggerSelection widget triggerSelection widget
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Selection.RadioButtons ( module IHaskell.Display.Widgets.Selection.RadioButtons (
-- * The RadioButtons Widget -- * The RadioButtons Widget
RadioButtons, RadioButtons,
-- * Constructor -- * Constructor
mkRadioButtons, mkRadioButtons) 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
...@@ -18,7 +17,7 @@ import Data.Aeson ...@@ -18,7 +17,7 @@ import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -40,7 +39,8 @@ mkRadioButtons = do ...@@ -40,7 +39,8 @@ mkRadioButtons = 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.RadioButtons"] initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.RadioButtons"]
-- 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
...@@ -69,9 +69,10 @@ instance IHaskellWidget RadioButtons where ...@@ -69,9 +69,10 @@ instance IHaskellWidget RadioButtons where
OptionLabels _ -> do OptionLabels _ -> do
setField' widget SSelectedLabel label setField' widget SSelectedLabel label
setField' widget SSelectedValue label setField' widget SSelectedValue label
OptionDict ps -> case lookup label ps of OptionDict ps ->
Nothing -> return () case lookup label ps of
Just value -> do Nothing -> return ()
setField' widget SSelectedLabel label Just value -> do
setField' widget SSelectedValue value setField' widget SSelectedLabel label
setField' widget SSelectedValue value
triggerSelection widget triggerSelection widget
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Selection.Select ( module IHaskell.Display.Widgets.Selection.Select (
-- * The Select Widget -- * The Select Widget
SelectWidget, SelectWidget,
-- * Constructor -- * Constructor
mkSelectWidget, mkSelectWidget) 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
...@@ -18,7 +17,7 @@ import Data.Aeson ...@@ -18,7 +17,7 @@ import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -69,9 +68,10 @@ instance IHaskellWidget SelectWidget where ...@@ -69,9 +68,10 @@ instance IHaskellWidget SelectWidget where
OptionLabels _ -> do OptionLabels _ -> do
setField' widget SSelectedLabel label setField' widget SSelectedLabel label
setField' widget SSelectedValue label setField' widget SSelectedValue label
OptionDict ps -> case lookup label ps of OptionDict ps ->
Nothing -> return () case lookup label ps of
Just value -> do Nothing -> return ()
setField' widget SSelectedLabel label Just value -> do
setField' widget SSelectedValue value setField' widget SSelectedLabel label
setField' widget SSelectedValue value
triggerSelection widget triggerSelection widget
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Selection.SelectMultiple ( module IHaskell.Display.Widgets.Selection.SelectMultiple (
-- * The SelectMultiple Widget -- * The SelectMultiple Widget
SelectMultipleWidget, SelectMultipleWidget,
-- * Constructor -- * Constructor
mkSelectMultipleWidget, mkSelectMultipleWidget) 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
...@@ -19,7 +18,7 @@ import qualified Data.HashMap.Strict as HM ...@@ -19,7 +18,7 @@ import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Vector as V import qualified Data.Vector as V
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -41,7 +40,10 @@ mkSelectMultipleWidget = do ...@@ -41,7 +40,10 @@ mkSelectMultipleWidget = 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.SelectMultiple"] initData = object
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.SelectMultiple"
]
-- 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
...@@ -71,9 +73,10 @@ instance IHaskellWidget SelectMultipleWidget where ...@@ -71,9 +73,10 @@ instance IHaskellWidget SelectMultipleWidget where
OptionLabels _ -> do OptionLabels _ -> do
setField' widget SSelectedLabels labelList setField' widget SSelectedLabels labelList
setField' widget SSelectedValues labelList setField' widget SSelectedValues labelList
OptionDict ps -> case sequence $ map (`lookup` ps) labelList of OptionDict ps ->
Nothing -> return () case sequence $ map (`lookup` ps) labelList of
Just valueList -> do Nothing -> return ()
setField' widget SSelectedLabels labelList Just valueList -> do
setField' widget SSelectedValues valueList setField' widget SSelectedLabels labelList
setField' widget SSelectedValues valueList
triggerSelection widget triggerSelection widget
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.Selection.ToggleButtons ( module IHaskell.Display.Widgets.Selection.ToggleButtons (
-- * The ToggleButtons Widget -- * The ToggleButtons Widget
ToggleButtons, ToggleButtons,
-- * Constructor -- * Constructor
mkToggleButtons, mkToggleButtons) 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
...@@ -18,7 +17,7 @@ import Data.Aeson ...@@ -18,7 +17,7 @@ import Data.Aeson
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -37,15 +36,18 @@ mkToggleButtons = do ...@@ -37,15 +36,18 @@ mkToggleButtons = do
uuid <- U.random uuid <- U.random
let selectionAttrs = defaultSelectionWidget "ToggleButtonsView" let selectionAttrs = defaultSelectionWidget "ToggleButtonsView"
toggleButtonsAttrs = (STooltips =:: []) toggleButtonsAttrs = (STooltips =:: [])
:& (SIcons =:: []) :& (SIcons =:: [])
:& (SButtonStyle =:: DefaultButton) :& (SButtonStyle =:: DefaultButton)
:& RNil :& RNil
widgetState = WidgetState $ selectionAttrs <+> toggleButtonsAttrs widgetState = WidgetState $ selectionAttrs <+> toggleButtonsAttrs
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.ToggleButtons"] initData = object
[ "model_name" .= str "WidgetModel"
, "widget_class" .= str "IPython.ToggleButtons"
]
-- 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
...@@ -74,9 +76,10 @@ instance IHaskellWidget ToggleButtons where ...@@ -74,9 +76,10 @@ instance IHaskellWidget ToggleButtons where
OptionLabels _ -> do OptionLabels _ -> do
setField' widget SSelectedLabel label setField' widget SSelectedLabel label
setField' widget SSelectedValue label setField' widget SSelectedValue label
OptionDict ps -> case lookup label ps of OptionDict ps ->
Nothing -> return () case lookup label ps of
Just value -> do Nothing -> return ()
setField' widget SSelectedLabel label Just value -> do
setField' widget SSelectedValue value setField' widget SSelectedLabel label
setField' widget SSelectedValue value
triggerSelection widget triggerSelection widget
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.String.HTML ( module IHaskell.Display.Widgets.String.HTML (
-- * The HTML Widget -- * The HTML Widget
HTMLWidget, HTMLWidget,
-- * Constructor -- * Constructor
mkHTMLWidget, mkHTMLWidget) 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
...@@ -17,7 +16,7 @@ import Control.Monad (when, join) ...@@ -17,7 +16,7 @@ import Control.Monad (when, join)
import Data.Aeson import Data.Aeson
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.String.Latex ( module IHaskell.Display.Widgets.String.Latex (
-- * The Latex Widget -- * The Latex Widget
LatexWidget, LatexWidget,
-- * Constructor -- * Constructor
mkLatexWidget, mkLatexWidget) 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
...@@ -17,7 +16,7 @@ import Control.Monad (when, join) ...@@ -17,7 +16,7 @@ import Control.Monad (when, join)
import Data.Aeson import Data.Aeson
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
......
...@@ -4,13 +4,12 @@ ...@@ -4,13 +4,12 @@
{-# 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,
-- * Submit handling -- * Submit handling
triggerSubmit, triggerSubmit) 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
...@@ -20,7 +19,7 @@ import Data.Aeson ...@@ -20,7 +19,7 @@ import Data.Aeson
import qualified Data.HashMap.Strict as Map import qualified Data.HashMap.Strict as Map
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
......
...@@ -4,11 +4,10 @@ ...@@ -4,11 +4,10 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module IHaskell.Display.Widgets.String.TextArea ( module IHaskell.Display.Widgets.String.TextArea (
-- * The TextArea Widget -- * The TextArea Widget
TextAreaWidget, TextAreaWidget,
-- * Constructor -- * Constructor
mkTextAreaWidget, mkTextAreaWidget) 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
...@@ -17,7 +16,7 @@ import Control.Monad (when, join) ...@@ -17,7 +16,7 @@ import Control.Monad (when, join)
import Data.Aeson import Data.Aeson
import Data.IORef (newIORef) import Data.IORef (newIORef)
import Data.Text (Text) import Data.Text (Text)
import Data.Vinyl (Rec (..), (<+>)) import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display import IHaskell.Display
import IHaskell.Eval.Widgets import IHaskell.Eval.Widgets
...@@ -38,7 +37,8 @@ mkTextAreaWidget = do ...@@ -38,7 +37,8 @@ mkTextAreaWidget = 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.Textarea"] initData = object
["model_name" .= str "WidgetModel", "widget_class" .= str "IPython.Textarea"]
-- 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
......
...@@ -329,3 +329,6 @@ str = id ...@@ -329,3 +329,6 @@ str = id
instance ToJSON Natural where instance ToJSON Natural where
toJSON 0 = String "" toJSON 0 = String ""
toJSON n = String . pack $ show n toJSON n = String . pack $ show n
...@@ -51,9 +51,14 @@ for source_dir in ["src", "ipython-kernel", "ihaskell-display"]: ...@@ -51,9 +51,14 @@ for source_dir in ["src", "ipython-kernel", "ihaskell-display"]:
continue continue
for filename in filenames: for filename in filenames:
# Take Haskell files, but ignore the Cabal Setup.hs if "ihaskell-display/ihaskell-widgets/src/IHaskell/Display/Widgets" in root:
# Also ignore IHaskellPrelude.hs, it uses CPP in weird places # Ignore Types.hs and Common.hs from ihaskell-widgets
ignored_files = ["Setup.hs", "IHaskellPrelude.hs"] # They cause issues with hindent, due to promoted types
ignored_files = ["Types.hs", "Common.hs"]
else:
# Take Haskell files, but ignore the Cabal Setup.hs
# Also ignore IHaskellPrelude.hs, it uses CPP in weird places
ignored_files = ["Setup.hs", "IHaskellPrelude.hs"]
if filename.endswith(".hs") and filename not in ignored_files: if filename.endswith(".hs") and filename not in ignored_files:
sources.append(os.path.join(root, filename)) sources.append(os.path.join(root, filename))
......
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