IHaskell/src/Main.hs

385 lines
14 KiB
Haskell
Raw Normal View History

2013-10-20 13:22:56 -07:00
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | Description : Argument parsing and basic messaging loop, using Haskell
-- Chans to communicate with the ZeroMQ sockets.
module Main where
2013-10-12 22:31:47 -07:00
import ClassyPrelude hiding (liftIO)
2013-12-28 23:21:04 -05:00
import Prelude (last)
import Control.Concurrent.Chan
import Control.Concurrent (threadDelay)
import Data.Aeson
2013-10-27 19:08:41 -07:00
import Text.Printf
2013-11-09 17:01:18 -08:00
import System.Exit (exitSuccess)
import System.Directory
2013-12-28 23:21:04 -05:00
import System.Console.CmdArgs.Explicit hiding (complete)
import qualified Data.Map as Map
import IHaskell.Types
2013-08-26 14:47:27 -07:00
import IHaskell.ZeroMQ
import qualified IHaskell.Message.UUID as UUID
2013-10-10 22:52:32 -07:00
import IHaskell.Eval.Evaluate
import IHaskell.Eval.Completion (complete)
import IHaskell.Eval.Info
2013-10-10 22:52:32 -07:00
import qualified Data.ByteString.Char8 as Chars
2013-10-20 20:16:34 -07:00
import IHaskell.IPython
2013-12-28 23:21:04 -05:00
import GHC hiding (extensions)
import Outputable (showSDoc, ppr)
2013-12-28 23:21:04 -05:00
-- Command line arguments to IHaskell. A set of aruments is annotated with
-- the mode being invoked.
data Args = Args IHaskellMode [Argument]
data Argument
= ServeFrom String -- ^ Which directory to serve notebooks from.
| Extension String -- ^ An extension to load at startup.
| ConfFile String -- ^ A file with commands to load at startup.
| Help -- ^ Display help text.
deriving (Eq, Show)
-- Which mode IHaskell is being invoked in.
-- `None` means no mode was specified.
data IHaskellMode
= None
| Notebook
| Console
| UpdateIPython
| Kernel (Maybe String)
2014-01-01 15:21:28 -05:00
| View (Maybe ViewFormat) (Maybe String)
2013-12-28 23:21:04 -05:00
deriving (Eq, Show)
main :: IO ()
main = do
2013-12-28 23:21:04 -05:00
stringArgs <- map unpack <$> getArgs
case process ihaskellArgs stringArgs of
Left errmsg -> putStrLn $ pack errmsg
Right args ->
ihaskell args
universalFlags :: [Flag Args]
universalFlags = [
flagReq ["extension","e", "X"] (store Extension) "<ghc-extension>" "Extension to enable at start.",
flagReq ["conf","c"] (store ConfFile) "<file.hs>" "File with commands to execute at start.",
flagHelpSimple (add Help)
]
where
add flag (Args mode flags) = Args mode $ flag : flags
store :: (String -> Argument) -> String -> Args -> Either String Args
store constructor str (Args mode prev) = Right $ Args mode $ constructor str : prev
notebook :: Mode Args
notebook = mode "notebook" (Args Notebook []) "Browser-based notebook interface." noArgs $
flagReq ["serve","s"] (store ServeFrom) "<dir>" "Directory to serve notebooks from.":
universalFlags
console :: Mode Args
console = mode "console" (Args Console []) "Console-based interactive repl." noArgs universalFlags
kernel = mode "kernel" (Args (Kernel Nothing) []) "Invoke the IHaskell kernel." kernelArg []
where
kernelArg = flagArg update "<json-kernel-file>"
update filename (Args _ flags) = Right $ Args (Kernel $ Just filename) flags
update :: Mode Args
update = mode "update" (Args UpdateIPython []) "Update IPython frontends." noArgs []
2014-01-01 15:21:28 -05:00
view :: Mode Args
view = (modeEmpty $ Args (View Nothing Nothing) []) {
modeNames = ["view"],
modeCheck =
\a@(Args (View fmt file) _) ->
if not (isJust fmt && isJust file)
then Left "Syntax: IHaskell view <format> <name>[.ipynb]"
else Right a,
modeHelp = concat [
"Convert an IHaskell notebook to another format.\n",
"Notebooks are searched in the IHaskell directory and the current directory.\n",
"Available formats are " ++ intercalate ", " (map show
["pdf", "html", "ipynb", "markdown", "latex"]),
"."
],
modeArgs = ([formatArg, filenameArg], Nothing)
}
where
formatArg = flagArg updateFmt "<format>"
filenameArg = flagArg updateFile "<name>[.ipynb]"
updateFmt fmtStr (Args (View _ s) flags) =
case readMay fmtStr of
Just fmt -> Right $ Args (View (Just fmt) s) flags
Nothing -> Left $ "Invalid format '" ++ fmtStr ++ "'."
updateFile name (Args (View f _) flags) = Right $ Args (View f (Just name)) flags
2013-12-28 23:21:04 -05:00
ihaskellArgs :: Mode Args
2013-12-29 12:46:45 -05:00
ihaskellArgs =
2014-01-01 15:21:28 -05:00
let descr = "Haskell for Interactive Computing."
2013-12-29 12:46:45 -05:00
onlyHelp = [flagHelpSimple (add Help)]
noMode = mode "IHaskell" (Args None []) descr noArgs onlyHelp in
2014-01-01 15:21:28 -05:00
noMode { modeGroupModes = toGroup [console, notebook, view, update, kernel] }
2013-12-29 12:46:45 -05:00
where
add flag (Args mode flags) = Args mode $ flag : flags
2013-12-28 23:21:04 -05:00
noArgs = flagArg unexpected ""
where
unexpected a = error $ "Unexpected argument: " ++ a
ihaskell :: Args -> IO ()
-- If no mode is specified, print help text.
ihaskell (Args None _) =
print $ helpText [] HelpFormatAll ihaskellArgs
-- Update IPython: remove then reinstall.
-- This is in case cabal updates IHaskell but the corresponding IPython
-- isn't updated. This is hard to detect since versions of IPython might
-- not change!
ihaskell (Args UpdateIPython _) = do
2014-01-01 15:21:28 -05:00
setupIPython
2013-12-28 23:21:04 -05:00
putStrLn "IPython updated."
ihaskell (Args Console flags) = showingHelp Console flags $ do
2014-01-01 15:21:28 -05:00
setupIPython
2013-10-27 19:08:41 -07:00
2013-12-28 23:21:04 -05:00
flags <- addDefaultConfFile flags
info <- initInfo flags
runConsole info
2013-10-20 20:16:34 -07:00
2014-01-01 15:21:28 -05:00
ihaskell (Args (View (Just fmt) (Just name)) []) =
nbconvert fmt name
2013-12-28 23:21:04 -05:00
ihaskell (Args Notebook flags) = showingHelp Notebook flags $ do
2014-01-01 15:21:28 -05:00
setupIPython
2013-10-20 20:16:34 -07:00
2013-12-28 23:21:04 -05:00
let server = case mapMaybe serveDir flags of
[] -> Nothing
xs -> Just $ last xs
flags <- addDefaultConfFile flags
2014-01-01 21:36:11 -05:00
undirInfo <- initInfo flags
curdir <- getCurrentDirectory
let info = undirInfo { initDir = curdir }
2013-12-28 23:21:04 -05:00
runNotebook info server
where
serveDir (ServeFrom dir) = Just dir
serveDir _ = Nothing
ihaskell (Args (Kernel (Just filename)) _) = do
initInfo <- readInitInfo
runKernel filename initInfo
-- | Add a conf file to the arguments if none exists.
addDefaultConfFile :: [Argument] -> IO [Argument]
addDefaultConfFile flags = do
def <- defaultConfFile
case (find isConfFile flags, def) of
(Nothing, Just file) -> return $ ConfFile file : flags
_ -> return flags
where
isConfFile (ConfFile _) = True
isConfFile _ = False
showingHelp :: IHaskellMode -> [Argument] -> IO () -> IO ()
showingHelp mode flags act =
case find (==Help) flags of
Just _ ->
print $ helpText [] HelpFormatAll $ chooseMode mode
Nothing ->
act
where
chooseMode Console = console
chooseMode Notebook = notebook
chooseMode (Kernel _) = kernel
chooseMode UpdateIPython = update
-- | Parse initialization information from the flags.
initInfo :: [Argument] -> IO InitInfo
2014-01-01 21:36:11 -05:00
initInfo [] = return InitInfo { extensions = [], initCells = [], initDir = "."}
2013-12-28 23:21:04 -05:00
initInfo (flag:flags) = do
info <- initInfo flags
case flag of
Extension ext -> return info { extensions = ext:extensions info }
ConfFile filename -> do
cell <- readFile (fpFromText $ pack filename)
return info { initCells = cell:initCells info }
2013-12-29 12:46:45 -05:00
_ -> return info
2013-10-20 20:16:34 -07:00
-- | Run the IHaskell language kernel.
2013-12-28 23:21:04 -05:00
runKernel :: String -- ^ Filename of profile JSON file.
-> InitInfo -- ^ Initialization information from the invocation.
-> IO ()
runKernel profileSrc initInfo = do
2014-01-01 21:36:11 -05:00
setCurrentDirectory $ initDir initInfo
2013-08-26 14:47:27 -07:00
-- Parse the profile file.
2013-10-20 20:16:34 -07:00
Just profile <- liftM decode . readFile . fpFromText $ pack profileSrc
2013-08-26 14:47:27 -07:00
-- Serve on all sockets and ports defined in the profile.
interface <- serveProfile profile
2014-01-01 21:36:11 -05:00
-- Create initial state in the directory the kernel *should* be in.
2013-08-26 14:47:27 -07:00
state <- initialKernelState
2013-08-26 14:47:27 -07:00
-- Receive and reply to all messages on the shell socket.
2013-12-28 23:21:04 -05:00
interpret $ do
-- Initialize the context by evaluating everything we got from the
-- command line flags. This includes enabling some extensions and also
-- running some code.
let extLines = map (":extension " ++) $ extensions initInfo
noPublish _ _ = return ()
evaluator line = do
-- Create a new state each time.
stateVar <- liftIO initialKernelState
state <- liftIO $ takeMVar stateVar
evaluate state line noPublish
2013-12-28 23:21:04 -05:00
mapM_ evaluator extLines
mapM_ evaluator $ initCells initInfo
forever $ do
-- Read the request from the request channel.
request <- liftIO $ readChan $ shellRequestChannel interface
-- Create a header for the reply.
replyHeader <- createReplyHeader (header request)
-- Create the reply, possibly modifying kernel state.
oldState <- liftIO $ takeMVar state
(newState, reply) <- replyTo interface request replyHeader oldState
liftIO $ putMVar state newState
-- Write the reply to the reply channel.
liftIO $ writeChan (shellReplyChannel interface) reply
2013-08-26 14:47:27 -07:00
-- Initial kernel state.
initialKernelState :: IO (MVar KernelState)
2013-10-12 22:31:47 -07:00
initialKernelState =
newMVar defaultKernelState
2013-10-10 22:52:32 -07:00
-- | Duplicate a message header, giving it a new UUID and message type.
dupHeader :: MessageHeader -> MessageType -> IO MessageHeader
2013-10-10 22:52:32 -07:00
dupHeader header messageType = do
2013-10-12 22:31:47 -07:00
uuid <- liftIO UUID.random
2013-10-10 22:52:32 -07:00
return header { messageId = uuid, msgType = messageType }
2013-08-26 14:47:27 -07:00
-- | Create a new message header, given a parent message header.
2013-10-20 12:22:27 -07:00
createReplyHeader :: MessageHeader -> Interpreter MessageHeader
2013-08-26 14:47:27 -07:00
createReplyHeader parent = do
-- Generate a new message UUID.
2013-10-20 12:22:27 -07:00
newMessageId <- liftIO UUID.random
2013-08-26 14:47:27 -07:00
return MessageHeader {
identifiers = identifiers parent,
parentHeader = Just parent,
metadata = Map.fromList [],
messageId = newMessageId,
sessionId = sessionId parent,
username = username parent,
msgType = replyType $ msgType parent
}
2013-10-20 12:22:27 -07:00
-- | Compute a reply to a message.
2013-10-12 22:31:47 -07:00
replyTo :: ZeroMQInterface -> Message -> MessageHeader -> KernelState -> Interpreter (KernelState, Message)
2013-10-20 12:22:27 -07:00
-- Reply to kernel info requests with a kernel info reply. No computation
-- needs to be done, as a kernel info reply is a static object (all info is
-- hard coded into the representation of that message type).
2013-08-26 14:47:27 -07:00
replyTo _ KernelInfoRequest{} replyHeader state = return (state, KernelInfoReply { header = replyHeader })
2013-08-26 16:14:48 -07:00
2013-11-09 17:01:18 -08:00
-- Reply to a shutdown request by exiting the main thread.
-- Before shutdown, reply to the request to let the frontend know shutdown
-- is happening.
replyTo interface ShutdownRequest{restartPending = restartPending} replyHeader _ = liftIO $ do
writeChan (shellReplyChannel interface) $ ShutdownReply replyHeader restartPending
exitSuccess
2013-11-09 17:01:18 -08:00
2013-10-20 12:22:27 -07:00
-- Reply to an execution request. The reply itself does not require
-- computation, but this causes messages to be sent to the IOPub socket
-- with the output of the code in the execution request.
2013-10-10 22:52:32 -07:00
replyTo interface ExecuteRequest{ getCode = code } replyHeader state = do
-- Convenience function to send a message to the IOPub socket.
let send msg = liftIO $ writeChan (iopubChannel interface) msg
2013-10-07 21:32:51 -07:00
2013-10-20 12:22:27 -07:00
-- Notify the frontend that the kernel is busy computing.
-- All the headers are copies of the reply header with a different
-- message type, because this preserves the session ID, parent header,
-- and other important information.
busyHeader <- liftIO $ dupHeader replyHeader StatusMessage
2013-10-10 22:52:32 -07:00
send $ PublishStatus busyHeader Busy
-- Construct a function for publishing output as this is going.
-- This function accepts a boolean indicating whether this is the final
-- output and the thing to display. Store the final outputs in a list so
-- that when we receive an updated non-final output, we can clear the
-- entire output and re-display with the updated output.
displayed <- liftIO $ newMVar []
updateNeeded <- liftIO $ newMVar False
let clearOutput = do
header <- dupHeader replyHeader ClearOutputMessage
send $ ClearOutput header True
sendOutput outs = do
header <- dupHeader replyHeader DisplayDataMessage
send $ PublishDisplayData header "haskell" outs
publish :: Bool -> [DisplayData] -> IO ()
publish final outputs = do
-- If necessary, clear all previous output and redraw.
clear <- readMVar updateNeeded
when clear $ do
clearOutput
disps <- readMVar displayed
mapM_ sendOutput $ reverse disps
-- Draw this message.
sendOutput outputs
-- If this is the final message, add it to the list of completed
-- messages. If it isn't, make sure we clear it later by marking
-- update needed as true.
modifyMVar_ updateNeeded (const $ return $ not final)
when final $
modifyMVar_ displayed (return . (outputs:))
-- Run code and publish to the frontend as we go.
let execCount = getExecutionCounter state
updatedState <- evaluate state (Chars.unpack code) publish
2013-10-20 12:22:27 -07:00
-- Notify the frontend that we're done computing.
idleHeader <- liftIO $ dupHeader replyHeader StatusMessage
2013-10-20 12:22:27 -07:00
send $ PublishStatus idleHeader Idle
return (updatedState, ExecuteReply {
2013-08-27 09:46:31 -07:00
header = replyHeader,
2013-10-10 22:52:32 -07:00
executionCounter = execCount,
status = Ok
2013-08-27 09:46:31 -07:00
})
replyTo _ req@CompleteRequest{} replyHeader state = do
(matchedText, completions) <- complete (Chars.unpack $ getCodeLine req) (getCursorPos req)
let reply = CompleteReply replyHeader (map Chars.pack completions) (Chars.pack matchedText) (getCodeLine req) True
return (state, reply)
-- | Reply to the object_info_request message. Given an object name, return
-- | the associated type calculated by GHC.
replyTo _ ObjectInfoRequest{objectName=oname} replyHeader state = do
docs <- info $ Chars.unpack oname
let reply = ObjectInfoReply {
header = replyHeader,
objectName = oname,
objectFound = docs == "",
objectTypeString = Chars.pack docs,
objectDocString = Chars.pack docs
}
return (state, reply)