Commit c53f70d8 authored by Andrew Gibiansky's avatar Andrew Gibiansky

Formatting ipython-kernel

parent 7ba7c4d1
This diff is collapsed.
-- | This module exports all the types and functions necessary to create an
-- IPython language kernel that supports the @ipython console@ and @ipython
-- notebook@ frontends.
module IHaskell.IPython.Kernel (
module X,
) where
-- | This module exports all the types and functions necessary to create an IPython language kernel
-- that supports the @ipython console@ and @ipython notebook@ frontends.
module IHaskell.IPython.Kernel (module X) where
import IHaskell.IPython.Types as X
import IHaskell.IPython.Message.Writer as X
import IHaskell.IPython.Message.Parser as X
import IHaskell.IPython.Message.UUID as X
import IHaskell.IPython.ZeroMQ as X
import IHaskell.IPython.Types as X
import IHaskell.IPython.Message.Writer as X
import IHaskell.IPython.Message.Parser as X
import IHaskell.IPython.Message.UUID as X
import IHaskell.IPython.ZeroMQ as X
{-# LANGUAGE OverloadedStrings #-}
-- | Description : Parsing messages received from IPython
--
-- This module is responsible for converting from low-level ByteStrings
-- obtained from the 0MQ sockets into Messages. The only exposed function is
-- `parseMessage`, which should only be used in the low-level 0MQ interface.
-- This module is responsible for converting from low-level ByteStrings obtained from the 0MQ
-- sockets into Messages. The only exposed function is `parseMessage`, which should only be used in
-- the low-level 0MQ interface.
module IHaskell.IPython.Message.Parser (parseMessage) where
import Data.Aeson ((.:), decode, Result(..), Object)
......@@ -17,9 +18,7 @@ import IHaskell.IPython.Types
type LByteString = Lazy.ByteString
----- External interface -----
-- | Parse a message from its ByteString components into a Message.
-- --- External interface ----- | Parse a message from its ByteString components into a Message.
parseMessage :: [ByteString] -- ^ The list of identifiers sent with the message.
-> ByteString -- ^ The header data.
-> ByteString -- ^ The parent header, which is just "{}" if there is no header.
......@@ -32,26 +31,25 @@ parseMessage idents headerData parentHeader metadata content =
messageWithoutHeader = parser messageType $ Lazy.fromStrict content
in messageWithoutHeader { header = header }
----- Module internals -----
-- | Parse a header from its ByteString components into a MessageHeader.
-- --- Module internals ----- | Parse a header from its ByteString components into a MessageHeader.
parseHeader :: [ByteString] -- ^ The list of identifiers.
-> ByteString -- ^ The header data.
-> ByteString -- ^ The parent header, or "{}" for Nothing.
-> ByteString -- ^ The metadata, or "{}" for an empty map.
-> MessageHeader -- The resulting message header.
parseHeader idents headerData parentHeader metadata =
MessageHeader { identifiers = idents
, parentHeader = parentResult
, metadata = metadataMap
, messageId = messageUUID
, sessionId = sessionUUID
, username = username
, msgType = messageType
}
MessageHeader
{ identifiers = idents
, parentHeader = parentResult
, metadata = metadataMap
, messageId = messageUUID
, sessionId = sessionUUID
, username = username
, msgType = messageType
}
where
-- Decode the header data and the parent header data into JSON objects.
-- If the parent header data is absent, just have Nothing instead.
-- Decode the header data and the parent header data into JSON objects. If the parent header data is
-- absent, just have Nothing instead.
Just result = decode $ Lazy.fromStrict headerData :: Maybe Object
parentResult = if parentHeader == "{}"
then Nothing
......@@ -71,27 +69,26 @@ noHeader :: MessageHeader
noHeader = error "No header created"
parser :: MessageType -- ^ The message type being parsed.
-> LByteString -> Message -- ^ The parser that converts the body into a message.
-- This message should have an undefined header.
-> LByteString -> Message -- ^ The parser that converts the body into a message. This message
-- should have an undefined header.
parser KernelInfoRequestMessage = kernelInfoRequestParser
parser ExecuteRequestMessage = executeRequestParser
parser CompleteRequestMessage = completeRequestParser
parser ExecuteRequestMessage = executeRequestParser
parser CompleteRequestMessage = completeRequestParser
parser ObjectInfoRequestMessage = objectInfoRequestParser
parser ShutdownRequestMessage = shutdownRequestParser
parser InputReplyMessage = inputReplyParser
parser CommOpenMessage = commOpenParser
parser CommDataMessage = commDataParser
parser CommCloseMessage = commCloseParser
parser HistoryRequestMessage = historyRequestParser
parser other = error $ "Unknown message type " ++ show other
-- | Parse a kernel info request.
-- A kernel info request has no auxiliary information, so ignore the body.
parser ShutdownRequestMessage = shutdownRequestParser
parser InputReplyMessage = inputReplyParser
parser CommOpenMessage = commOpenParser
parser CommDataMessage = commDataParser
parser CommCloseMessage = commCloseParser
parser HistoryRequestMessage = historyRequestParser
parser other = error $ "Unknown message type " ++ show other
-- | Parse a kernel info request. A kernel info request has no auxiliary information, so ignore the
-- body.
kernelInfoRequestParser :: LByteString -> Message
kernelInfoRequestParser _ = KernelInfoRequest { header = noHeader }
-- | Parse an execute request.
-- Fields used are:
-- | Parse an execute request. Fields used are:
-- 1. "code": the code to execute.
-- 2. "silent": whether to execute silently.
-- 3. "store_history": whether to include this in history.
......@@ -99,22 +96,23 @@ kernelInfoRequestParser _ = KernelInfoRequest { header = noHeader }
executeRequestParser :: LByteString -> Message
executeRequestParser content =
let parser obj = do
code <- obj .: "code"
silent <- obj .: "silent"
storeHistory <- obj .: "store_history"
allowStdin <- obj .: "allow_stdin"
code <- obj .: "code"
silent <- obj .: "silent"
storeHistory <- obj .: "store_history"
allowStdin <- obj .: "allow_stdin"
return (code, silent, storeHistory, allowStdin)
return (code, silent, storeHistory, allowStdin)
Just decoded = decode content
Success (code, silent, storeHistory, allowStdin) = parse parser decoded
in ExecuteRequest { header = noHeader
, getCode = code
, getSilent = silent
, getAllowStdin = allowStdin
, getStoreHistory = storeHistory
, getUserVariables = []
, getUserExpressions = []
}
in ExecuteRequest
{ header = noHeader
, getCode = code
, getSilent = silent
, getAllowStdin = allowStdin
, getStoreHistory = storeHistory
, getUserVariables = []
, getUserExpressions = []
}
requestParser parser content = parsed
where
......@@ -147,7 +145,6 @@ objectInfoRequestParser = requestParser $ \obj -> do
dlevel <- obj .: "detail_level"
return $ ObjectInfoRequest noHeader oname dlevel
shutdownRequestParser :: LByteString -> Message
shutdownRequestParser = requestParser $ \obj -> do
code <- obj .: "restart"
......
-- | Description : UUID generator and data structure
--
-- Generate, parse, and pretty print UUIDs for use with IPython.
module IHaskell.IPython.Message.UUID (
UUID,
random, randoms,
) where
module IHaskell.IPython.Message.UUID (UUID, random, randoms) where
import Control.Monad (mzero, replicateM)
import Control.Applicative ((<$>))
import Data.Text (pack)
import Data.Aeson
import Data.UUID.V4 (nextRandom)
-- We use an internal string representation because for the purposes of
-- IPython, it matters whether the letters are uppercase or lowercase and
-- whether the dashes are present in the correct locations. For the
-- purposes of new UUIDs, it does not matter, but IPython expects UUIDs
-- passed to kernels to be returned unchanged, so we cannot actually parse
-- them.
import Control.Monad (mzero, replicateM)
import Control.Applicative ((<$>))
import Data.Text (pack)
import Data.Aeson
import Data.UUID.V4 (nextRandom)
-- | A UUID (universally unique identifier).
data UUID = UUID String deriving (Show, Read, Eq, Ord)
data UUID =
-- We use an internal string representation because for the purposes of IPython, it
-- matters whether the letters are uppercase or lowercase and whether the dashes are
-- present in the correct locations. For the purposes of new UUIDs, it does not matter,
-- but IPython expects UUIDs passed to kernels to be returned unchanged, so we cannot
-- actually parse them.
UUID String
deriving (Show, Read, Eq, Ord)
-- | Generate a list of random UUIDs.
randoms :: Int -- ^ Number of UUIDs to generate.
......
{-# LANGUAGE OverloadedStrings #-}
-- | Description : @ToJSON@ for Messages
--
-- This module contains the @ToJSON@ instance for @Message@.
module IHaskell.IPython.Message.Writer (
ToJSON(..)
) where
module IHaskell.IPython.Message.Writer (ToJSON(..)) where
import Data.Aeson
import Data.Map (Map)
import Data.Text (Text, pack)
import Data.Monoid (mempty)
import Data.Aeson
import Data.Map (Map)
import Data.Text (Text, pack)
import Data.Monoid (mempty)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString as B
import Data.Text.Encoding
import Data.Text.Encoding
import IHaskell.IPython.Types
import IHaskell.IPython.Types
-- Convert message bodies into JSON.
instance ToJSON Message where
toJSON KernelInfoReply{ versionList = vers, language = language } = object [
"protocol_version" .= string "5.0", -- current protocol version, major and minor
"language_version" .= vers,
"language" .= language
]
toJSON ExecuteReply{ status = status, executionCounter = counter, pagerOutput = pager} = object [
"status" .= show status,
"execution_count" .= counter,
"payload" .=
if null pager
then []
else [object [
"source" .= string "page",
"text" .= pager
]],
"user_variables" .= emptyMap,
"user_expressions" .= emptyMap
]
toJSON PublishStatus{ executionState = executionState } = object [
"execution_state" .= executionState
]
toJSON PublishStream{ streamType = streamType, streamContent = content } = object [
"data" .= content,
"name" .= streamType
]
toJSON PublishDisplayData{ source = src, displayData = datas } = object [
"source" .= src,
"metadata" .= object [],
"data" .= object (map displayDataToJson datas)
]
toJSON PublishOutput{ executionCount = execCount, reprText = reprText } = object [
"data" .= object ["text/plain" .= reprText],
"execution_count" .= execCount,
"metadata" .= object []
]
toJSON PublishInput{ executionCount = execCount, inCode = code } = object [
"execution_count" .= execCount,
"code" .= code
]
toJSON (CompleteReply _ matches start end metadata status) = object [
"matches" .= matches,
"cursor_start" .= start,
"cursor_end" .= end,
"metadata" .= metadata,
"status" .= if status then string "ok" else "error"
]
toJSON o@ObjectInfoReply{} = object [
"oname" .= objectName o,
"found" .= objectFound o,
"ismagic" .= False,
"isalias" .= False,
"type_name" .= objectTypeString o,
"docstring" .= objectDocString o
]
toJSON ShutdownReply{restartPending = restart} = object [
"restart" .= restart
]
toJSON ClearOutput{wait = wait} = object [
"wait" .= wait
]
toJSON RequestInput{inputPrompt = prompt} = object [
"prompt" .= prompt
]
toJSON req@CommOpen{} = object [
"comm_id" .= commUuid req,
"target_name" .= commTargetName req,
"data" .= commData req
]
toJSON req@CommData{} = object [
"comm_id" .= commUuid req,
"data" .= commData req
]
toJSON req@CommClose{} = object [
"comm_id" .= commUuid req,
"data" .= commData req
]
toJSON req@HistoryReply{} = object [ "history" .= map tuplify (historyReply req) ]
where tuplify (HistoryReplyElement sess linum res) = (sess, linum, case res of
Left inp -> toJSON inp
Right (inp, out) -> toJSON out)
toJSON KernelInfoReply { versionList = vers, language = language } =
object ["protocol_version" .= string "5.0" -- current protocol version, major and minor
, "language_version" .= vers, "language" .= language]
toJSON ExecuteReply { status = status, executionCounter = counter, pagerOutput = pager } =
object
[ "status" .= show status
, "execution_count" .= counter
, "payload" .=
if null pager
then []
else [object ["source" .= string "page", "text" .= pager]]
, "user_variables" .= emptyMap
, "user_expressions" .= emptyMap
]
toJSON PublishStatus { executionState = executionState } =
object ["execution_state" .= executionState]
toJSON PublishStream { streamType = streamType, streamContent = content } =
object ["data" .= content, "name" .= streamType]
toJSON PublishDisplayData { source = src, displayData = datas } =
object
["source" .= src, "metadata" .=
object [], "data" .=
object (map displayDataToJson datas)]
toJSON PublishOutput { executionCount = execCount, reprText = reprText } =
object
["data" .=
object ["text/plain" .= reprText], "execution_count" .= execCount, "metadata" .=
object []]
toJSON PublishInput { executionCount = execCount, inCode = code } =
object ["execution_count" .= execCount, "code" .= code]
toJSON (CompleteReply _ matches start end metadata status) =
object
[ "matches" .= matches
, "cursor_start" .= start
, "cursor_end" .= end
, "metadata" .= metadata
, "status" .= if status
then string "ok"
else "error"
]
toJSON o@ObjectInfoReply{} =
object
[ "oname" .=
objectName o
, "found" .= objectFound o
, "ismagic" .= False
, "isalias" .= False
, "type_name" .= objectTypeString o
, "docstring" .= objectDocString o
]
toJSON ShutdownReply { restartPending = restart } =
object ["restart" .= restart]
toJSON ClearOutput { wait = wait } =
object ["wait" .= wait]
toJSON RequestInput { inputPrompt = prompt } =
object ["prompt" .= prompt]
toJSON req@CommOpen{} =
object ["comm_id" .= commUuid req, "target_name" .= commTargetName req, "data" .= commData req]
toJSON req@CommData{} =
object ["comm_id" .= commUuid req, "data" .= commData req]
toJSON req@CommClose{} =
object ["comm_id" .= commUuid req, "data" .= commData req]
toJSON req@HistoryReply{} =
object ["history" .= map tuplify (historyReply req)]
where
tuplify (HistoryReplyElement sess linum res) = (sess, linum, case res of
Left inp -> toJSON inp
Right (inp, out) -> toJSON out)
toJSON body = error $ "Do not know how to convert to JSON for message " ++ show body
-- | Print an execution state as "busy", "idle", or "starting".
instance ToJSON ExecutionState where
toJSON Busy = String "busy"
toJSON Idle = String "idle"
toJSON Starting = String "starting"
toJSON Busy = String "busy"
toJSON Idle = String "idle"
toJSON Starting = String "starting"
-- | Print a stream as "stdin" or "stdout" strings.
instance ToJSON StreamType where
toJSON Stdin = String "stdin"
toJSON Stdout = String "stdout"
toJSON Stdin = String "stdin"
toJSON Stdout = String "stdout"
-- | Convert a MIME type and value into a JSON dictionary pair.
displayDataToJson :: DisplayData -> (Text, Value)
displayDataToJson :: DisplayData -> (Text, Value)
displayDataToJson (DisplayData mimeType dataStr) =
pack (show mimeType) .= String dataStr
pack (show mimeType) .= String dataStr
----- Constants -----
emptyMap :: Map String String
emptyMap = mempty
......
{-# LANGUAGE OverloadedStrings, DoAndIfThenElse #-}
-- | This module provides a way in which the Haskell standard input may be
-- forwarded to the IPython frontend and thus allows the notebook to use
-- the standard input.
-- | This module provides a way in which the Haskell standard input may be forwarded to the IPython
-- frontend and thus allows the notebook to use the standard input.
--
-- This relies on the implementation of file handles in GHC, and is
-- generally unsafe and terrible. However, it is difficult to find another
-- way to do it, as file handles are generally meant to point to streams
-- and files, and not networked communication protocols.
-- This relies on the implementation of file handles in GHC, and is generally unsafe and terrible.
-- However, it is difficult to find another way to do it, as file handles are generally meant to
-- point to streams and files, and not networked communication protocols.
--
-- In order to use this module, it must first be initialized with two
-- things. First of all, in order to know how to communicate with the
-- IPython frontend, it must know the kernel profile used for
-- communication. For this, use @recordKernelProfile@ once the profile is
-- known. Both this and @recordParentHeader@ take a directory name where
-- they can store this data.
-- In order to use this module, it must first be initialized with two things. First of all, in order
-- to know how to communicate with the IPython frontend, it must know the kernel profile used for
-- communication. For this, use @recordKernelProfile@ once the profile is known. Both this and
-- @recordParentHeader@ take a directory name where they can store this data.
--
-- Finally, the module must know what @execute_request@ message is
-- currently being replied to (which will request the input). Thus, every
-- time the language kernel receives an @execute_request@ message, it
-- should inform this module via @recordParentHeader@, so that the module
-- may generate messages with an appropriate parent header set. If this is
-- not done, the IPython frontends will not recognize the target of the
-- communication.
-- Finally, the module must know what @execute_request@ message is currently being replied to (which
-- will request the input). Thus, every time the language kernel receives an @execute_request@
-- message, it should inform this module via @recordParentHeader@, so that the module may generate
-- messages with an appropriate parent header set. If this is not done, the IPython frontends will
-- not recognize the target of the communication.
--
-- Finally, in order to activate this module, @fixStdin@ must be called
-- once. It must be passed the same directory name as @recordParentHeader@
-- and @recordKernelProfile@. Note that if this is being used from within
-- the GHC API, @fixStdin@ /must/ be called from within the GHC session
-- not from the host code.
module IHaskell.IPython.Stdin (
fixStdin,
recordParentHeader,
recordKernelProfile
) where
-- Finally, in order to activate this module, @fixStdin@ must be called once. It must be passed the
-- same directory name as @recordParentHeader@ and @recordKernelProfile@. Note that if this is being
-- used from within the GHC API, @fixStdin@ /must/ be called from within the GHC session not from
-- the host code.
module IHaskell.IPython.Stdin (fixStdin, recordParentHeader, recordKernelProfile) where
import Control.Concurrent
import Control.Applicative ((<$>))
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 Control.Concurrent
import Control.Applicative ((<$>))
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.IPython.Types
import IHaskell.IPython.ZeroMQ
import IHaskell.IPython.Message.UUID as UUID
import IHaskell.IPython.Types
import IHaskell.IPython.ZeroMQ
import IHaskell.IPython.Message.UUID as UUID
stdinInterface :: MVar ZeroMQStdin
{-# NOINLINE stdinInterface #-}
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.
-- | 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 :: String -> IO ()
fixStdin dir = do
-- Initialize the stdin interface.
......@@ -78,17 +67,18 @@ stdinOnce dir = do
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 dir
hPutStr stdinInput $ line ++ "\n"
loop stdinInput oldStdin newStdin
then loop stdinInput oldStdin newStdin
else do
line <- getInputLine dir
hPutStr stdinInput $ line ++ "\n"
loop stdinInput oldStdin newStdin
-- | Get a line of input from the IPython frontend.
getInputLine :: String -> IO String
......@@ -98,15 +88,15 @@ getInputLine dir = do
-- Send a request for input.
uuid <- UUID.random
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 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
......
......@@ -44,10 +44,15 @@ except:
# Find all the source files
sources = []
for root, dirnames, filenames in os.walk("src"):
for filename in filenames:
if filename.endswith(".hs"):
sources.append(os.path.join(root, filename))
for source_dir in ["src", "ipython-kernel"]:
for root, dirnames, filenames in os.walk(source_dir):
# Skip cabal dist directories
if "dist" in root:
continue
for filename in filenames:
if filename.endswith(".hs"):
sources.append(os.path.join(root, filename))
hindent_outputs = {}
......
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