Commit 7a534cee authored by Sumit Sahrawat's avatar Sumit Sahrawat

Apply an untested fix for ghc-7.8

+ Some minor formatting fixes.
+ Add IHaskell.Display.Widgets.Types to hindent ignored_files.
+ Remove some extensions and unused imports.
parent 8925bdce
......@@ -12,12 +12,10 @@ CheckBox,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,7 +12,6 @@ ToggleButton,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -12,11 +12,8 @@ ValidWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
......
......@@ -12,19 +12,14 @@ Box,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
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 'Box' represents a Box widget from IPython.html.widgets.
type Box = IPythonWidget BoxType
......
......@@ -12,11 +12,8 @@ FlexBox,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
......
......@@ -12,11 +12,8 @@ PlaceProxy,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import Data.Vinyl.Lens (rput)
......
......@@ -12,11 +12,8 @@ ProxyWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import Data.Vinyl.Lens (rput)
......
......@@ -12,13 +12,11 @@ Accordion,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,13 +12,11 @@ TabWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,7 +12,7 @@ Button,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Control.Monad (when)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -5,12 +5,14 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE AutoDeriveTypeable #-}
{-# LANGUAGE DeriveDataTypeable #-}
module IHaskell.Display.Widgets.Common where
import Data.Aeson
import Data.Aeson.Types (emptyObject)
import Data.Text (pack, Text)
import Data.Typeable (Typeable)
import IHaskell.Display (IHaskellWidget)
import IHaskell.Eval.Widgets (widgetSendClose)
......@@ -99,7 +101,7 @@ closeWidget :: IHaskellWidget w => w -> IO ()
closeWidget w = widgetSendClose w emptyObject
newtype PixCount = PixCount Integer
deriving (Num, Ord, Eq, Enum)
deriving (Num, Ord, Eq, Enum, Typeable)
instance ToJSON PixCount where
toJSON (PixCount x) = toJSON . pack $ show x ++ "px"
......@@ -202,7 +204,7 @@ instance ToJSON BarStyleValue where
data ImageFormatValue = PNG
| SVG
| JPG
deriving Eq
deriving (Eq, Typeable)
instance Show ImageFormatValue where
show PNG = "png"
......
......@@ -13,13 +13,11 @@ BoundedFloatText,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,13 +12,8 @@ FloatProgress,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
......
......@@ -12,7 +12,6 @@ FloatSlider,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -13,8 +13,6 @@ FloatRangeSlider,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -12,13 +12,11 @@ FloatText,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,12 +12,9 @@ ImageWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Monoid (mempty)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
......
......@@ -12,13 +12,11 @@ BoundedIntText,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,13 +12,8 @@ IntProgress,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Exception (throw, ArithException(LossOfPrecision))
import Control.Monad (when, join)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
......
......@@ -12,7 +12,6 @@ IntSlider,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -12,7 +12,6 @@ IntRangeSlider,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -12,13 +12,11 @@ IntText,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import qualified Data.Scientific as Sci
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PatternSynonyms #-}
module IHaskell.Display.Widgets.Interactive (interactive, uncurryHList, Rec(..), Argument(..)) where
......@@ -25,7 +22,7 @@ import IHaskell.Display
import IHaskell.Display.Widgets.Types
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.Bool.CheckBox
......@@ -44,10 +41,6 @@ data WidgetConf a where
a
-> WidgetConf a
newtype WrappedConstructor a =
WrappedConstructor
{ wrappedConstructor :: IO (IPythonWidget (SuitableWidget a)) }
type family WithTypes (ts :: [*]) (r :: *) :: * where
WithTypes '[] r = r
......@@ -70,8 +63,6 @@ newtype EventSetter a = EventSetter (IPythonWidget (SuitableWidget a) -> IO () -
newtype Initializer a = Initializer (IPythonWidget (SuitableWidget a) -> Argument a -> IO ())
newtype Trigger a = Trigger (IPythonWidget (SuitableWidget a) -> IO ())
data RequiredWidget a where
RequiredWidget ::
......@@ -107,11 +98,8 @@ extractGetter (WidgetConf wr) = Getter $ getValue wr
extractEventSetter :: WidgetConf x -> EventSetter x
extractEventSetter (WidgetConf wr) = EventSetter $ setEvent wr
extractTrigger :: WidgetConf x -> Trigger x
extractTrigger (WidgetConf wr) = Trigger $ trigger wr
extractInitializer :: WidgetConf x -> Initializer x
extractInitializer (WidgetConf wr) = Initializer initializer
extractInitializer WidgetConf{} = Initializer initializer
createWidget :: Constructor a -> IO (RequiredWidget a)
createWidget (Constructor con) = fmap RequiredWidget con
......@@ -146,7 +134,6 @@ liftToWidgets func rc initvals = do
getters = rmap extractGetter rc
eventSetters = rmap extractEventSetter rc
initializers = rmap extractInitializer rc
triggers = rmap extractTrigger rc
bx <- mkFlexBox
out <- mkOutputWidget
......@@ -188,15 +175,9 @@ construct (WrappedWidget cons _ _) = cons
getValue :: WrappedWidget w h f a -> IPythonWidget w -> IO a
getValue (WrappedWidget _ _ field) widget = getField widget field
setValue :: WrappedWidget w h f a -> IPythonWidget w -> a -> IO ()
setValue (WrappedWidget _ _ field) widget = setField widget field
setEvent :: WrappedWidget w h f a -> IPythonWidget w -> IO () -> IO ()
setEvent (WrappedWidget _ h _) widget = setField widget h
trigger :: WrappedWidget w h f a -> IPythonWidget w -> IO ()
trigger (WrappedWidget _ h _) = triggerEvent h
class RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs => FromWidget a where
type SuitableWidget a :: WidgetType
type SuitableHandler a :: S.Field
......
......@@ -18,12 +18,8 @@ module IHaskell.Display.Widgets.Output (
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,7 +12,7 @@ Dropdown,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Control.Monad (void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -12,12 +12,11 @@ RadioButtons,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Control.Monad (when, void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,13 +12,12 @@ SelectMultiple,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (fmap, join, sequence, void)
import Control.Monad (void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
import Data.Text (Text)
import qualified Data.Vector as V
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,7 +12,7 @@ ToggleButtons,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join, void)
import Control.Monad (void)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -12,11 +12,8 @@ HTMLWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,11 +12,8 @@ LatexWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
import IHaskell.Eval.Widgets
......
......@@ -12,11 +12,10 @@ TextWidget,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Control.Monad (when)
import Data.Aeson
import qualified Data.HashMap.Strict as Map
import Data.IORef (newIORef)
import Data.Text (Text)
import Data.Vinyl (Rec(..), (<+>))
import IHaskell.Display
......
......@@ -12,7 +12,6 @@ TextArea,
-- To keep `cabal repl` happy when running from the ihaskell repo
import Prelude
import Control.Monad (when, join)
import Data.Aeson
import qualified Data.HashMap.Strict as HM
import Data.IORef (newIORef)
......
......@@ -61,10 +61,10 @@ module IHaskell.Display.Widgets.Types where
--
-- Widgets are not able to do console input, the reason for that can be found in the messaging
-- specification.
import Control.Monad (unless, join, when, void, mapM_)
import Control.Monad (unless, join, when, void)
import Control.Applicative ((<$>))
import qualified Control.Exception as Ex
import Data.Typeable
import Data.Typeable (Typeable, TypeRep, typeOf)
import Data.IORef (IORef, readIORef, modifyIORef)
import Data.Text (Text, pack)
import System.IO.Error
......@@ -87,7 +87,8 @@ import GHC.IO.Exception
import IHaskell.Eval.Widgets (widgetSendUpdate)
import IHaskell.Display (Base64, IHaskellWidget(..))
import IHaskell.IPython.Message.UUID
import IHaskell.Display.Widgets.Singletons (Field, SField(..))
import IHaskell.Display.Widgets.Singletons (Field, SField)
import qualified IHaskell.Display.Widgets.Singletons as S
import IHaskell.Display.Widgets.Common
......@@ -131,7 +132,7 @@ type BoxClass = DOMWidgetClass :++ '[S.Children, S.OverflowX, S.OverflowY, S.Box
type SelectionContainerClass = BoxClass :++ '[S.Titles, S.SelectedIndex, S.ChangeHandler]
-- Types associated with Fields.
type family FieldType (f :: Field) :: * where
FieldType S.ViewModule = Text
FieldType S.ViewName = Text
......@@ -269,7 +270,7 @@ data WidgetType = ButtonType
| TabType
-- Fields associated with a widget
type family WidgetFields (w :: WidgetType) :: [Field] where
WidgetFields ButtonType =
DOMWidgetClass :++
......
......@@ -102,7 +102,8 @@ kernelDebugFlag = flagNone ["debug"] addDebug "Print debugging output from the k
addDebug (Args mode prev) = Args mode (KernelDebug : prev)
kernelStackFlag :: Flag Args
kernelStackFlag = flagNone ["stack"] addStack "Inherit environment from `stack` when it is installed"
kernelStackFlag = flagNone ["stack"] addStack
"Inherit environment from `stack` when it is installed"
where
addStack (Args mode prev) = Args mode (KernelspecUseStack : prev)
......
......@@ -190,7 +190,7 @@ installKernelspec replace opts = void $ do
Nothing -> []
Just file -> ["--conf", file])
++ ["--ghclib", kernelSpecGhcLibdir opts]
++ ["--stack" | kernelSpecUseStack opts]
++ ["--stack" | kernelSpecUseStack opts]
let kernelSpec = KernelSpec
{ kernelDisplayName = "Haskell"
......
......@@ -52,7 +52,10 @@ for source_dir in ["src", "ipython-kernel", "ihaskell-display"]:
continue
# Ignore IHaskellPrelude.hs, it uses CPP in weird places
ignored_files = ["IHaskellPrelude.hs"]
if widget_dir in root:
ignored_files = ["Types.hs"]
else:
ignored_files = ["IHaskellPrelude.hs"]
for filename in filenames:
if filename.endswith(".hs") and filename not in ignored_files:
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