Commit c7b11432 authored by Andrew Gibiansky's avatar Andrew Gibiansky

stdin works

parent 70f414f9
...@@ -7,7 +7,7 @@ name: ihaskell ...@@ -7,7 +7,7 @@ name: ihaskell
-- PVP summary: +-+------- breaking API changes -- PVP summary: +-+------- breaking API changes
-- | | +----- non-breaking API additions -- | | +----- non-breaking API additions
-- | | | +--- code changes with no API change -- | | | +--- code changes with no API change
version: 0.2.0.5 version: 0.2.0.6
-- A short (one-line) description of the package. -- A short (one-line) description of the package.
synopsis: A Haskell backend kernel for the IPython project. synopsis: A Haskell backend kernel for the IPython project.
...@@ -76,10 +76,20 @@ library ...@@ -76,10 +76,20 @@ library
cereal ==0.3.*, cereal ==0.3.*,
text >=0.11, text >=0.11,
mtl >= 2.1 mtl >= 2.1
exposed-modules: IHaskell.Display, exposed-modules: IHaskell.Display
Paths_ihaskell, IHaskell.Eval.Completion
IHaskell.Types, IHaskell.Eval.Evaluate
IHaskell.Eval.Info
IHaskell.Eval.Lint
IHaskell.Eval.Parser
IHaskell.Eval.Stdin
IHaskell.IPython
IHaskell.Message.Parser
IHaskell.Message.UUID IHaskell.Message.UUID
IHaskell.Message.Writer
IHaskell.Types
IHaskell.ZeroMQ
Paths_ihaskell
executable IHaskell executable IHaskell
-- .hs or .lhs file containing the Main module. -- .hs or .lhs file containing the Main module.
...@@ -95,6 +105,7 @@ executable IHaskell ...@@ -95,6 +105,7 @@ executable IHaskell
IHaskell.Eval.Info IHaskell.Eval.Info
IHaskell.Eval.Evaluate IHaskell.Eval.Evaluate
IHaskell.Eval.Parser IHaskell.Eval.Parser
IHaskell.Eval.Stdin
IHaskell.IPython IHaskell.IPython
IHaskell.Message.Parser IHaskell.Message.Parser
IHaskell.Message.UUID IHaskell.Message.UUID
......
No preview for this file type
...@@ -83,6 +83,7 @@ type Interpreter = Ghc ...@@ -83,6 +83,7 @@ type Interpreter = Ghc
globalImports :: [String] globalImports :: [String]
globalImports = globalImports =
[ "import IHaskell.Display" [ "import IHaskell.Display"
, "import qualified IHaskell.Eval.Stdin"
, "import Control.Applicative ((<$>))" , "import Control.Applicative ((<$>))"
, "import GHC.IO.Handle (hDuplicateTo, hDuplicate, hClose)" , "import GHC.IO.Handle (hDuplicateTo, hDuplicate, hClose)"
, "import System.Posix.IO" , "import System.Posix.IO"
...@@ -103,7 +104,7 @@ interpret action = runGhc (Just libdir) $ do ...@@ -103,7 +104,7 @@ interpret action = runGhc (Just libdir) $ do
-- Close stdin so it can't be used. -- Close stdin so it can't be used.
-- Otherwise it'll block the kernel forever. -- Otherwise it'll block the kernel forever.
runStmt "System.IO.hClose System.IO.stdin" RunToCompletion runStmt "IHaskell.Eval.Stdin.fixStdin" RunToCompletion
initializeItVariable initializeItVariable
......
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings, DoAndIfThenElse #-}
module IHaskell.Eval.Stdin (fixStdin, recordParentHeader, recordKernelProfile) where
import ClassyPrelude hiding (hPutStrLn, readFile, writeFile)
import Prelude (read)
import Control.Concurrent (forkIO, threadDelay)
import Control.Concurrent.Chan
import Control.Monad
import GHC.IO.Handle
import GHC.IO.Handle.Types
import System.IO
import System.Posix.IO
import System.IO.Unsafe
import qualified Data.Map as Map
import IHaskell.Types
import IHaskell.IPython
import IHaskell.ZeroMQ
import IHaskell.Message.UUID as UUID
stdinInterface :: MVar ZeroMQStdin
stdinInterface = unsafePerformIO newEmptyMVar
-- | Manipulate standard input so that it is sourced from the IPython
-- frontend. This function is build on layers of deep magical hackery, so
-- be careful modifying it.
fixStdin :: IO ()
fixStdin = do
-- Initialize the stdin interface.
dir <- getIHaskellDir
profile <- read <$> readFile (dir ++ "/.kernel-profile")
interface <- serveStdin profile
putMVar stdinInterface interface
void $ forkIO stdinOnce
stdinOnce :: IO ()
stdinOnce = do
-- Create a pipe using and turn it into handles.
(readEnd, writeEnd) <- createPipe
newStdin <- fdToHandle readEnd
stdinInput <- fdToHandle writeEnd
hSetBuffering newStdin NoBuffering
hSetBuffering stdinInput NoBuffering
-- Store old stdin and swap in new stdin.
oldStdin <- hDuplicate stdin
hDuplicateTo newStdin stdin
loop stdinInput oldStdin newStdin
where
loop stdinInput oldStdin newStdin = do
let FileHandle _ mvar = stdin
threadDelay $ 150 * 1000
empty <- isEmptyMVar mvar
if not empty
then loop stdinInput oldStdin newStdin
else do
line <- getInputLine
hPutStr stdinInput $ line ++ "\n"
loop stdinInput oldStdin newStdin
-- | Get a line of input from the IPython frontend.
getInputLine :: IO String
getInputLine = do
StdinChannel req rep <- readMVar stdinInterface
-- Send a request for input.
uuid <- UUID.random
dir <- getIHaskellDir
parentHeader <- read <$> readFile (dir ++ "/.last-req-header")
let header = MessageHeader {
username = username parentHeader,
identifiers = identifiers parentHeader,
parentHeader = Just parentHeader,
messageId = uuid,
sessionId = sessionId parentHeader,
metadata = Map.fromList [],
msgType = InputRequestMessage
}
let msg = RequestInput header ""
writeChan req msg
-- Get the reply.
InputReply _ value <- readChan rep
hPrint stderr value
return value
recordParentHeader :: MessageHeader -> IO ()
recordParentHeader header = do
dir <- getIHaskellDir
writeFile (dir ++ "/.last-req-header") $ show header
recordKernelProfile :: Profile -> IO ()
recordKernelProfile profile = do
dir <- getIHaskellDir
writeFile (dir ++ "/.kernel-profile") $ show profile
...@@ -77,6 +77,7 @@ parser ExecuteRequestMessage = executeRequestParser ...@@ -77,6 +77,7 @@ parser ExecuteRequestMessage = executeRequestParser
parser CompleteRequestMessage = completeRequestParser parser CompleteRequestMessage = completeRequestParser
parser ObjectInfoRequestMessage = objectInfoRequestParser parser ObjectInfoRequestMessage = objectInfoRequestParser
parser ShutdownRequestMessage = shutdownRequestParser parser ShutdownRequestMessage = shutdownRequestParser
parser InputReplyMessage = inputReplyParser
parser other = error $ "Unknown message type " ++ show other parser other = error $ "Unknown message type " ++ show other
-- | Parse a kernel info request. -- | Parse a kernel info request.
...@@ -141,3 +142,12 @@ shutdownRequestParser content = parsed ...@@ -141,3 +142,12 @@ shutdownRequestParser content = parsed
return $ ShutdownRequest noHeader code return $ ShutdownRequest noHeader code
Just decoded = decode content Just decoded = decode content
inputReplyParser :: LByteString -> Message
inputReplyParser content = parsed
where
Success parsed = flip parse decoded $ \ obj -> do
value <- obj .: "value"
return $ InputReply noHeader value
Just decoded = decode content
...@@ -12,6 +12,10 @@ import Control.Monad (mzero) ...@@ -12,6 +12,10 @@ import Control.Monad (mzero)
import Data.Aeson import Data.Aeson
import Data.UUID.V4 (nextRandom) import Data.UUID.V4 (nextRandom)
import Text.Read as Read hiding (pfail, String)
import Text.ParserCombinators.ReadP
-- We use an internal string representation because for the purposes of -- We use an internal string representation because for the purposes of
-- IPython, it matters whether the letters are uppercase or lowercase and -- IPython, it matters whether the letters are uppercase or lowercase and
-- whether the dashes are present in the correct locations. For the -- whether the dashes are present in the correct locations. For the
...@@ -20,10 +24,7 @@ import Data.UUID.V4 (nextRandom) ...@@ -20,10 +24,7 @@ import Data.UUID.V4 (nextRandom)
-- them. -- them.
-- | A UUID (universally unique identifier). -- | A UUID (universally unique identifier).
data UUID = UUID String deriving Eq data UUID = UUID String deriving (Show, Read, Eq)
instance Show UUID where
show (UUID s) = s
-- | Generate a list of random UUIDs. -- | Generate a list of random UUIDs.
randoms :: Int -- ^ Number of UUIDs to generate. randoms :: Int -- ^ Number of UUIDs to generate.
......
...@@ -80,6 +80,10 @@ instance ToJSON Message where ...@@ -80,6 +80,10 @@ instance ToJSON Message where
"wait" .= wait "wait" .= wait
] ]
toJSON RequestInput{inputPrompt = prompt} = object [
"prompt" .= prompt
]
toJSON body = error $ "Do not know how to convert to JSON for message " ++ show body toJSON body = error $ "Do not know how to convert to JSON for message " ++ show body
......
...@@ -7,7 +7,7 @@ module IHaskell.Types ( ...@@ -7,7 +7,7 @@ module IHaskell.Types (
MessageHeader (..), MessageHeader (..),
MessageType(..), MessageType(..),
Username, Username,
Metadata, Metadata(..),
Port, Port,
replyType, replyType,
ExecutionState (..), ExecutionState (..),
...@@ -43,7 +43,7 @@ data Profile = Profile { ...@@ -43,7 +43,7 @@ data Profile = Profile {
shellPort :: Port, -- ^ The shell command port. shellPort :: Port, -- ^ The shell command port.
iopubPort :: Port, -- ^ The Iopub port. iopubPort :: Port, -- ^ The Iopub port.
key :: ByteString -- ^ The HMAC encryption key. key :: ByteString -- ^ The HMAC encryption key.
} deriving Show } deriving (Show, Read)
-- Convert the kernel profile to and from JSON. -- Convert the kernel profile to and from JSON.
instance FromJSON Profile where instance FromJSON Profile where
...@@ -112,7 +112,7 @@ data MessageHeader = MessageHeader { ...@@ -112,7 +112,7 @@ data MessageHeader = MessageHeader {
sessionId :: UUID, -- ^ A unique session UUID. sessionId :: UUID, -- ^ A unique session UUID.
username :: Username, -- ^ The user who sent this message. username :: Username, -- ^ The user who sent this message.
msgType :: MessageType -- ^ The message type. msgType :: MessageType -- ^ The message type.
} deriving Show } deriving (Show, Read)
-- Convert a message header into the JSON field for the header. -- Convert a message header into the JSON field for the header.
-- This field does not actually have all the record fields. -- This field does not actually have all the record fields.
...@@ -121,7 +121,7 @@ instance ToJSON MessageHeader where ...@@ -121,7 +121,7 @@ instance ToJSON MessageHeader where
"msg_id" .= messageId header, "msg_id" .= messageId header,
"session" .= sessionId header, "session" .= sessionId header,
"username" .= username header, "username" .= username header,
"msg_type" .= show (msgType header) "msg_type" .= showMessageType (msgType header)
] ]
-- | A username for the source of a message. -- | A username for the source of a message.
...@@ -147,24 +147,29 @@ data MessageType = KernelInfoReplyMessage ...@@ -147,24 +147,29 @@ data MessageType = KernelInfoReplyMessage
| ShutdownRequestMessage | ShutdownRequestMessage
| ShutdownReplyMessage | ShutdownReplyMessage
| ClearOutputMessage | ClearOutputMessage
| InputRequestMessage
instance Show MessageType where | InputReplyMessage
show KernelInfoReplyMessage = "kernel_info_reply" deriving (Show, Read)
show KernelInfoRequestMessage = "kernel_info_request"
show ExecuteReplyMessage = "execute_reply" showMessageType :: MessageType -> String
show ExecuteRequestMessage = "execute_request" showMessageType KernelInfoReplyMessage = "kernel_info_reply"
show StatusMessage = "status" showMessageType KernelInfoRequestMessage = "kernel_info_request"
show StreamMessage = "stream" showMessageType ExecuteReplyMessage = "execute_reply"
show DisplayDataMessage = "display_data" showMessageType ExecuteRequestMessage = "execute_request"
show OutputMessage = "pyout" showMessageType StatusMessage = "status"
show InputMessage = "pyin" showMessageType StreamMessage = "stream"
show CompleteRequestMessage = "complete_request" showMessageType DisplayDataMessage = "display_data"
show CompleteReplyMessage = "complete_reply" showMessageType OutputMessage = "pyout"
show ObjectInfoRequestMessage = "object_info_request" showMessageType InputMessage = "pyin"
show ObjectInfoReplyMessage = "object_info_reply" showMessageType CompleteRequestMessage = "complete_request"
show ShutdownRequestMessage = "shutdown_request" showMessageType CompleteReplyMessage = "complete_reply"
show ShutdownReplyMessage = "shutdown_reply" showMessageType ObjectInfoRequestMessage = "object_info_request"
show ClearOutputMessage = "clear_output" showMessageType ObjectInfoReplyMessage = "object_info_reply"
showMessageType ShutdownRequestMessage = "shutdown_request"
showMessageType ShutdownReplyMessage = "shutdown_reply"
showMessageType ClearOutputMessage = "clear_output"
showMessageType InputRequestMessage = "input_request"
showMessageType InputReplyMessage = "input_reply"
instance FromJSON MessageType where instance FromJSON MessageType where
parseJSON (String s) = case s of parseJSON (String s) = case s of
...@@ -184,6 +189,8 @@ instance FromJSON MessageType where ...@@ -184,6 +189,8 @@ instance FromJSON MessageType where
"shutdown_request" -> return ShutdownRequestMessage "shutdown_request" -> return ShutdownRequestMessage
"shutdown_reply" -> return ShutdownReplyMessage "shutdown_reply" -> return ShutdownReplyMessage
"clear_output" -> return ClearOutputMessage "clear_output" -> return ClearOutputMessage
"input_request" -> return InputRequestMessage
"input_reply" -> return InputReplyMessage
_ -> fail ("Unknown message type: " ++ show s) _ -> fail ("Unknown message type: " ++ show s)
parseJSON _ = fail "Must be a string." parseJSON _ = fail "Must be a string."
...@@ -294,6 +301,16 @@ data Message ...@@ -294,6 +301,16 @@ data Message
wait :: Bool -- ^ Whether to wait to redraw until there is more output. wait :: Bool -- ^ Whether to wait to redraw until there is more output.
} }
| RequestInput {
header :: MessageHeader,
inputPrompt :: String
}
| InputReply {
header :: MessageHeader,
inputValue :: String
}
deriving Show deriving Show
-- | Possible statuses in the execution reply messages. -- | Possible statuses in the execution reply messages.
......
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-} {-# LANGUAGE NoImplicitPrelude, OverloadedStrings, DoAndIfThenElse #-}
-- | Description : Low-level ZeroMQ communication wrapper. -- | Description : Low-level ZeroMQ communication wrapper.
-- --
-- The "ZeroMQ" module abstracts away the low-level 0MQ based interface with IPython, -- The "ZeroMQ" module abstracts away the low-level 0MQ based interface with IPython,
...@@ -6,7 +6,9 @@ ...@@ -6,7 +6,9 @@
-- takes a IPython profile specification and returns the channel interface to use. -- takes a IPython profile specification and returns the channel interface to use.
module IHaskell.ZeroMQ ( module IHaskell.ZeroMQ (
ZeroMQInterface (..), ZeroMQInterface (..),
serveProfile ZeroMQStdin(..),
serveProfile,
serveStdin,
) where ) where
import ClassyPrelude hiding (stdin) import ClassyPrelude hiding (stdin)
...@@ -20,6 +22,8 @@ import IHaskell.Types ...@@ -20,6 +22,8 @@ import IHaskell.Types
import IHaskell.Message.Parser import IHaskell.Message.Parser
import IHaskell.Message.Writer import IHaskell.Message.Writer
import System.IO.Unsafe
-- | The channel interface to the ZeroMQ sockets. All communication is done via -- | The channel interface to the ZeroMQ sockets. All communication is done via
-- Messages, which are encoded and decoded into a lower level form before being -- Messages, which are encoded and decoded into a lower level form before being
-- transmitted to IPython. These channels should functionally serve as -- transmitted to IPython. These channels should functionally serve as
...@@ -34,6 +38,11 @@ data ZeroMQInterface = Channels { ...@@ -34,6 +38,11 @@ data ZeroMQInterface = Channels {
iopubChannel :: Chan Message -- ^ Writing to this channel sends an iopub message to the frontend. iopubChannel :: Chan Message -- ^ Writing to this channel sends an iopub message to the frontend.
} }
data ZeroMQStdin = StdinChannel {
stdinRequestChannel :: Chan Message,
stdinReplyChannel :: Chan Message
}
-- | Start responding on all ZeroMQ channels used to communicate with IPython -- | Start responding on all ZeroMQ channels used to communicate with IPython
-- | via the provided profile. Return a set of channels which can be used to -- | via the provided profile. Return a set of channels which can be used to
-- | communicate with IPython in a more structured manner. -- | communicate with IPython in a more structured manner.
...@@ -55,7 +64,6 @@ serveProfile profile = do ...@@ -55,7 +64,6 @@ serveProfile profile = do
forkIO $ serveSocket context Rep (hbPort profile) $ heartbeat channels forkIO $ serveSocket context Rep (hbPort profile) $ heartbeat channels
forkIO $ serveSocket context Router (controlPort profile) $ control channels forkIO $ serveSocket context Router (controlPort profile) $ control channels
forkIO $ serveSocket context Router (shellPort profile) $ shell channels forkIO $ serveSocket context Router (shellPort profile) $ shell channels
forkIO $ serveSocket context Router (stdinPort profile) $ stdin channels
-- The context is reference counted in this thread only. Thus, the last -- The context is reference counted in this thread only. Thus, the last
-- serveSocket cannot be asynchronous, because otherwise context would -- serveSocket cannot be asynchronous, because otherwise context would
...@@ -65,6 +73,24 @@ serveProfile profile = do ...@@ -65,6 +73,24 @@ serveProfile profile = do
return channels return channels
serveStdin :: Profile -> IO ZeroMQStdin
serveStdin profile = do
reqChannel <- newChan
repChannel <- newChan
-- Create the context in a separate thread that never finishes. If
-- withContext or withSocket complete, the context or socket become invalid.
forkIO $ withContext $ \context ->
-- Serve on all sockets.
serveSocket context Router (stdinPort profile) $ \socket -> do
-- Read the request from the interface channel and send it.
readChan reqChannel >>= sendMessage socket
-- Receive a response and write it to the interface channel.
receiveMessage socket >>= writeChan repChannel
return $ StdinChannel reqChannel repChannel
-- | Serve on a given socket in a separate thread. Bind the socket in the -- | Serve on a given socket in a separate thread. Bind the socket in the
-- | given context and then loop the provided action, which should listen -- | given context and then loop the provided action, which should listen
-- | on the socket and respond to any events. -- | on the socket and respond to any events.
...@@ -120,11 +146,6 @@ iopub :: ZeroMQInterface -> Socket Pub -> IO () ...@@ -120,11 +146,6 @@ iopub :: ZeroMQInterface -> Socket Pub -> IO ()
iopub channels socket = iopub channels socket =
readChan (iopubChannel channels) >>= sendMessage socket readChan (iopubChannel channels) >>= sendMessage socket
stdin :: ZeroMQInterface -> Socket Router -> IO ()
stdin _ socket = do
void $ receive socket
return ()
-- | Receive and parse a message from a socket. -- | Receive and parse a message from a socket.
receiveMessage :: Receiver a => Socket a -> IO Message receiveMessage :: Receiver a => Socket a -> IO Message
receiveMessage socket = do receiveMessage socket = do
......
...@@ -24,6 +24,7 @@ import IHaskell.Eval.Completion (complete) ...@@ -24,6 +24,7 @@ import IHaskell.Eval.Completion (complete)
import IHaskell.Eval.Info import IHaskell.Eval.Info
import qualified Data.ByteString.Char8 as Chars import qualified Data.ByteString.Char8 as Chars
import IHaskell.IPython import IHaskell.IPython
import qualified IHaskell.Eval.Stdin as Stdin
import GHC hiding (extensions) import GHC hiding (extensions)
import Outputable (showSDoc, ppr) import Outputable (showSDoc, ppr)
...@@ -218,6 +219,9 @@ runKernel profileSrc initInfo = do ...@@ -218,6 +219,9 @@ runKernel profileSrc initInfo = do
-- Parse the profile file. -- Parse the profile file.
Just profile <- liftM decode . readFile . fpFromText $ pack profileSrc Just profile <- liftM decode . readFile . fpFromText $ pack profileSrc
-- Necessary for `getLine` and their ilk to work.
Stdin.recordKernelProfile profile
-- Serve on all sockets and ports defined in the profile. -- Serve on all sockets and ports defined in the profile.
interface <- serveProfile profile interface <- serveProfile profile
...@@ -289,7 +293,8 @@ replyTo :: ZeroMQInterface -> Message -> MessageHeader -> KernelState -> Interpr ...@@ -289,7 +293,8 @@ replyTo :: ZeroMQInterface -> Message -> MessageHeader -> KernelState -> Interpr
-- Reply to kernel info requests with a kernel info reply. No computation -- 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 -- 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). -- hard coded into the representation of that message type).
replyTo _ KernelInfoRequest{} replyHeader state = return (state, KernelInfoReply { header = replyHeader }) replyTo _ KernelInfoRequest{} replyHeader state =
return (state, KernelInfoReply { header = replyHeader })
-- Reply to a shutdown request by exiting the main thread. -- Reply to a shutdown request by exiting the main thread.
-- Before shutdown, reply to the request to let the frontend know shutdown -- Before shutdown, reply to the request to let the frontend know shutdown
...@@ -301,10 +306,13 @@ replyTo interface ShutdownRequest{restartPending = restartPending} replyHeader _ ...@@ -301,10 +306,13 @@ replyTo interface ShutdownRequest{restartPending = restartPending} replyHeader _
-- Reply to an execution request. The reply itself does not require -- Reply to an execution request. The reply itself does not require
-- computation, but this causes messages to be sent to the IOPub socket -- computation, but this causes messages to be sent to the IOPub socket
-- with the output of the code in the execution request. -- with the output of the code in the execution request.
replyTo interface ExecuteRequest{ getCode = code } replyHeader state = do replyTo interface req@ExecuteRequest{ getCode = code } replyHeader state = do
-- Convenience function to send a message to the IOPub socket. -- Convenience function to send a message to the IOPub socket.
let send msg = liftIO $ writeChan (iopubChannel interface) msg let send msg = liftIO $ writeChan (iopubChannel interface) msg
-- Log things so that we can use stdin.
liftIO $ Stdin.recordParentHeader $ header req
-- Notify the frontend that the kernel is busy computing. -- Notify the frontend that the kernel is busy computing.
-- All the headers are copies of the reply header with a different -- All the headers are copies of the reply header with a different
-- message type, because this preserves the session ID, parent header, -- message type, because this preserves the session ID, parent header,
......
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