Commit 1c232f17 authored by Andrew Gibiansky's avatar Andrew Gibiansky

Fixing notebook invocation to start jupyter; also making console default

parent b4cc01df
......@@ -62,17 +62,20 @@ data IHaskellMode = ShowHelp String
-- | Given a list of command-line arguments, return the IHaskell mode and
-- arguments to process.
parseFlags :: [String] -> Either String Args
parseFlags flags =
let modeIndex = findIndex (`elem` modeFlags) flags in
case modeIndex of
Nothing -> Left $ "No mode provided. Modes available are: " ++ show modeFlags ++ "\n" ++
pack (showText (Wrap 100) $ helpText [] HelpFormatAll ihaskellArgs)
Just 0 -> process ihaskellArgs flags
parseFlags flags =
let modeIndex = findIndex (`elem` modeFlags) flags
in case modeIndex of
Nothing ->
-- Treat no mode as 'console'.
if "--help" `elem` flags
then Left $ pack (showText (Wrap 100) $ helpText [] HelpFormatAll ihaskellArgs)
else process ihaskellArgs $ "console" : flags
Just 0 -> process ihaskellArgs flags
Just idx ->
-- If mode not first, move it to be first.
Just idx ->
let (start, first:end) = splitAt idx flags in
process ihaskellArgs $ first:start ++ end
let (start, first:end) = splitAt idx flags
in process ihaskellArgs $ first : start ++ end
where
modeFlags = concatMap modeNames allModes
......
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DoAndIfThenElse #-}
-- | Description : Shell scripting wrapper using @Shelly@ for the @notebook@, and
......@@ -27,6 +28,7 @@ import qualified Filesystem.Path.CurrentOS as FS
import Data.List.Utils (split)
import Data.String.Utils (rstrip, endswith, strip, replace)
import Text.Printf
import qualified Data.Text as T
import Data.Maybe (fromJust)
import System.Exit (exitFailure)
import Data.Aeson (toJSON)
......@@ -55,7 +57,7 @@ ipython suppress args = do
liftIO $ installHandler keyboardSignal (CatchOnce $ return ()) Nothing
-- We have this because using `run` does not let us use stdin.
runHandles "ipython" (args ++ kernelArgs) handles doNothing
runHandles "ipython" args handles doNothing
where
handles = [InHandle Inherit, outHandle suppress, errorHandle suppress]
......@@ -137,14 +139,15 @@ nbconvert fmt name = void . shelly $ do
-- This ensures that an IHaskell kernelspec exists; if it doesn't, it creates it.
-- Note that this exits with an error if IPython isn't installed properly.
withIPython :: IO a -> IO a
withIPython act = do
withIPython act = shelly $ do
verifyIPythonVersion
installKernelspec
act
kernelspecExists <- kernelSpecCreated
unless kernelspecExists installKernelspec
liftIO act
-- | Verify that a proper version of IPython is installed and accessible.
verifyIPythonVersion :: IO ()
verifyIPythonVersion = shelly $ do
verifyIPythonVersion :: Sh ()
verifyIPythonVersion = do
pathMay <- which "ipython"
case pathMay of
Nothing -> badIPython "No IPython detected -- install IPython 3.0+ before using IHaskell."
......@@ -165,8 +168,8 @@ verifyIPythonVersion = shelly $ do
-- | Install an IHaskell kernelspec into the right location.
-- The right location is determined by using `ipython kernelspec install --user`.
installKernelspec :: IO ()
installKernelspec = void $ shelly $ do
installKernelspec :: Sh ()
installKernelspec = void $ do
ihaskellPath <- getIHaskellPath
let kernelSpec = KernelSpec {
kernelDisplayName = "Haskell",
......@@ -184,7 +187,14 @@ installKernelspec = void $ shelly $ do
writefile filename $ toStrict $ toLazyText $ encodeToTextBuilder $ toJSON kernelSpec
Just ipython <- which "ipython"
run ipython ["kernelspec", "install", "--user", fpToText kernelDir]
silently $ run ipython ["kernelspec", "install", "--user", fpToText kernelDir]
kernelSpecCreated :: Sh Bool
kernelSpecCreated = do
Just ipython <- which "ipython"
out <- silently $ run ipython ["kernelspec", "list"]
let kernelspecs = map T.strip $ lines out
return $ kernelName `elem` kernelspecs
-- | Replace "~" with $HOME if $HOME is defined.
-- Otherwise, do nothing.
......@@ -223,7 +233,7 @@ parseVersion versionStr =
runConsole :: InitInfo -> IO ()
runConsole initInfo = void . shelly $ do
writeInitInfo initInfo
ipython False ["console"]
ipython False $ "console" : "--no-banner" : kernelArgs
runNotebook :: InitInfo -> Maybe Text -> IO ()
runNotebook initInfo maybeServeDir = void . shelly $ do
......
......@@ -44,6 +44,10 @@ ghcVersionInts = map read . words . map dotToSpace $ VERSION_ghc
dotToSpace '.' = ' '
dotToSpace x = x
consoleBanner :: Text
consoleBanner =
"Welcome to IHaskell! Run `IHaskell --help` for more information.\n" ++
"Enter `:help` to learn more about IHaskell built-ins."
main :: IO ()
main = do
......@@ -56,10 +60,12 @@ ihaskell :: Args -> IO ()
ihaskell (Args (ShowHelp help) _) = putStrLn $ pack help
ihaskell (Args ConvertLhs args) = showingHelp ConvertLhs args $ convert args
ihaskell (Args InstallKernelSpec _) = withIPython $ return ()
ihaskell (Args Console flags) = showingHelp Console flags $ withIPython $ do
flags <- addDefaultConfFile flags
info <- initInfo IPythonConsole flags
runConsole info
ihaskell (Args Console flags) = showingHelp Console flags $ do
putStrLn consoleBanner
withIPython $ do
flags <- addDefaultConfFile flags
info <- initInfo IPythonConsole flags
runConsole info
ihaskell (Args mode@(View (Just fmt) (Just name)) args) = showingHelp mode args $ withIPython $
nbconvert fmt name
ihaskell (Args Notebook flags) = showingHelp Notebook flags $ withIPython $ do
......
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