diff --git a/html/custom.js b/html/kernel.js
similarity index 100%
rename from html/custom.js
rename to html/kernel.js
diff --git a/ihaskell.cabal b/ihaskell.cabal
index 7e02b4d0..a25ed0bd 100644
--- a/ihaskell.cabal
+++ b/ihaskell.cabal
@@ -43,8 +43,7 @@ build-type: Simple
cabal-version: >=1.16
data-files:
- html/custom.css
- html/custom.js
+ html/kernel.js
html/logo-64x64.png
library
@@ -136,6 +135,7 @@ executable IHaskell
ghc ==7.6.* || == 7.8.*,
ihaskell -any,
MissingH >=1.2,
+ here ==1.2.*,
text -any,
ipython-kernel >= 0.2,
unix >= 2.6
diff --git a/src/IHaskell/IPython.hs b/src/IHaskell/IPython.hs
index 2e1f2b1c..f3d19cd7 100644
--- a/src/IHaskell/IPython.hs
+++ b/src/IHaskell/IPython.hs
@@ -185,6 +185,10 @@ installKernelspec = void $ do
mkdir_p kernelDir
writefile filename $ toStrict $ toLazyText $ encodeToTextBuilder $ toJSON kernelSpec
+ let files = ["kernel.js", "logo-64x64.png"]
+ forM_ files $ \file -> do
+ src <- liftIO $ Paths.getDataFileName $ "html/" ++ file
+ cp (fpFromString src) (tmp > kernelName > fpFromString file)
Just ipython <- which "ipython"
silently $ run ipython ["kernelspec", "install", "--user", fpToText kernelDir]
diff --git a/src/Main.hs b/src/Main.hs
index e432c047..b19d8104 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE NoImplicitPrelude, CPP, OverloadedStrings, ScopedTypeVariables #-}
+{-# LANGUAGE NoImplicitPrelude, CPP, OverloadedStrings, ScopedTypeVariables, QuasiQuotes #-}
-- | Description : Argument parsing and basic messaging loop, using Haskell
-- Chans to communicate with the ZeroMQ sockets.
module Main where
@@ -17,6 +17,7 @@ import System.Exit (exitSuccess)
import Text.Printf
import System.Posix.Signals
import qualified Data.Map as Map
+import Data.String.Here (hereFile)
-- IHaskell imports.
import IHaskell.Convert (convert)
@@ -44,6 +45,9 @@ ghcVersionInts = map read . words . map dotToSpace $ VERSION_ghc
dotToSpace '.' = ' '
dotToSpace x = x
+ihaskellCSS :: String
+ihaskellCSS = [hereFile|html/custom.css|]
+
consoleBanner :: Text
consoleBanner =
"Welcome to IHaskell! Run `IHaskell --help` for more information.\n" ++
@@ -65,7 +69,6 @@ ihaskell (Args Console flags) = showingHelp Console flags $ do
withIPython $ do
flags <- addDefaultConfFile flags
info <- initInfo IPythonConsole flags
- putStrLn "Noo"
runConsole info
ihaskell (Args mode@(View (Just fmt) (Just name)) args) = showingHelp mode args $ withIPython $
nbconvert fmt name
@@ -286,12 +289,15 @@ replyTo interface req@ExecuteRequest{ getCode = code } replyHeader state = do
sendOutput (ManyDisplay manyOuts) = mapM_ sendOutput manyOuts
sendOutput (Display outs) = do
header <- dupHeader replyHeader DisplayDataMessage
- send $ PublishDisplayData header "haskell" $ map convertSvgToHtml outs
+ send $ PublishDisplayData header "haskell" $ map (convertSvgToHtml . prependCss) outs
convertSvgToHtml (DisplayData MimeSvg svg) = html $ makeSvgImg $ base64 $ encodeUtf8 svg
convertSvgToHtml x = x
makeSvgImg base64data = unpack $ "
"
+ prependCss (DisplayData MimeHtml html) = DisplayData MimeHtml $ concat ["", html]
+ prependCss x = x
+
startComm :: CommInfo -> IO ()
startComm (CommInfo widget uuid target) = do
-- Send the actual comm open.