Commit fc177677 authored by Eyal Dechter's avatar Eyal Dechter

Added ObjectReplyInfoRequest and ObjectReplyInfoReply messages.

parent 26c22a77
...@@ -24,6 +24,7 @@ import InteractiveEval ...@@ -24,6 +24,7 @@ import InteractiveEval
import HscTypes import HscTypes
import GhcMonad (liftIO) import GhcMonad (liftIO)
import GHC hiding (Stmt) import GHC hiding (Stmt)
import GHC (exprType)
import GHC.Paths import GHC.Paths
import Exception hiding (evaluate) import Exception hiding (evaluate)
...@@ -61,8 +62,11 @@ write x = when debug $ liftIO $ hPutStrLn stderr x ...@@ -61,8 +62,11 @@ write x = when debug $ liftIO $ hPutStrLn stderr x
type LineNumber = Int type LineNumber = Int
type ColumnNumber = Int type ColumnNumber = Int
type Interpreter = Ghc type Interpreter = Ghc
data DirectiveType
= GetType String
deriving Show
data Command data Command
= Directive String = Directive DirectiveType
| Import String | Import String
| Declaration String | Declaration String
| Statement String | Statement String
...@@ -114,6 +118,7 @@ joinDisplays displays = ...@@ -114,6 +118,7 @@ joinDisplays displays =
0 -> other 0 -> other
_ -> joinedPlains : other _ -> joinedPlains : other
parseCommands :: String -- ^ Code containing commands. parseCommands :: String -- ^ Code containing commands.
-> [Command] -- ^ Commands contained in code string. -> [Command] -- ^ Commands contained in code string.
parseCommands code = concatMap makeCommands pieces parseCommands code = concatMap makeCommands pieces
...@@ -129,6 +134,7 @@ parseCommands code = concatMap makeCommands pieces ...@@ -129,6 +134,7 @@ parseCommands code = concatMap makeCommands pieces
makePieces [] = [] makePieces [] = []
makePieces (first:rest) makePieces (first:rest)
| isDirective first = first : makePieces rest | isDirective first = first : makePieces rest
| isImport first = first : makePieces rest
| otherwise = unlines (first:take endOfBlock rest) : makePieces (drop endOfBlock rest) | otherwise = unlines (first:take endOfBlock rest) : makePieces (drop endOfBlock rest)
where where
endOfBlock = fromMaybe (length rest) $ findIndex (\x -> indentLevel x <= indentLevel first) rest endOfBlock = fromMaybe (length rest) $ findIndex (\x -> indentLevel x <= indentLevel first) rest
...@@ -137,6 +143,7 @@ parseCommands code = concatMap makeCommands pieces ...@@ -137,6 +143,7 @@ parseCommands code = concatMap makeCommands pieces
pieces = trace (show $ makePieces $ lines code ) $ makePieces $ lines code pieces = trace (show $ makePieces $ lines code ) $ makePieces $ lines code
makeCommands lines makeCommands lines
| isDirective lines = [createDirective lines] | isDirective lines = [createDirective lines]
| isImport lines = [Import $ strip lines]
| otherwise = case (parseDecl lines, parseStmts lines) of | otherwise = case (parseDecl lines, parseStmts lines) of
(ParseOk declaration, _) -> [Declaration $ prettyPrint declaration] (ParseOk declaration, _) -> [Declaration $ prettyPrint declaration]
(ParseFailed {}, Right stmts) -> map (Statement . prettyPrint) $ init stmts (ParseFailed {}, Right stmts) -> map (Statement . prettyPrint) $ init stmts
...@@ -147,12 +154,12 @@ parseCommands code = concatMap makeCommands pieces ...@@ -147,12 +154,12 @@ parseCommands code = concatMap makeCommands pieces
(_, Left (lineNumber, colNumber,errMsg)) -> [ParseError lineNumber colNumber errMsg] (_, Left (lineNumber, colNumber,errMsg)) -> [ParseError lineNumber colNumber errMsg]
isDeclaration line = any (`isInfixOf` line) ["type", "newtype", "data", "instance", "class"] isDeclaration line = any (`isInfixOf` line) ["type", "newtype", "data", "instance", "class"]
isDirective line = startswith [directiveChar] stripped || startswith "import" stripped isDirective line = startswith [directiveChar] (strip line)
where stripped = strip line isImport line = startswith "import" (strip line)
createDirective line =
case strip line of createDirective line = case strip line of
':':_ -> Directive $ strip line ':':'t':' ':expr -> Directive (GetType expr)
_ -> Import $ strip line other -> ParseError 0 0 $ "Unknown command: " ++ other ++ "."
evalCommand :: Command -> Interpreter [DisplayData] evalCommand :: Command -> Interpreter [DisplayData]
evalCommand (Import importStr) = do evalCommand (Import importStr) = do
...@@ -162,9 +169,18 @@ evalCommand (Import importStr) = do ...@@ -162,9 +169,18 @@ evalCommand (Import importStr) = do
setContext $ IIDecl importDecl : context setContext $ IIDecl importDecl : context
return [] return []
evalCommand (Directive directive) = do evalCommand (Directive (GetType expr))
write $ "Directive: " ++ directive = ghandle handler
return [Display MimeHtml $ printf "<span style='font-weight: bold; color: green;'>%s</span>" directive] $ do result <- exprType expr
dflags <- getSessionDynFlags
return [Display MimeHtml
$ printf "<span style='font-weight: bold; color: green;'>%s</span>"
$ showSDocUnqual dflags $ ppr result]
where
handler :: SomeException -> Interpreter [DisplayData]
handler exception = do
write $ concat ["BreakCom: ", show exception]
return [Display MimeHtml $ makeError $ show exception]
evalCommand (Statement stmt) = do evalCommand (Statement stmt) = do
write $ "Statement: " ++ stmt write $ "Statement: " ++ stmt
......
...@@ -75,6 +75,7 @@ parser :: MessageType -- ^ The message type being parsed. ...@@ -75,6 +75,7 @@ parser :: MessageType -- ^ The message type being parsed.
parser KernelInfoRequestMessage = kernelInfoRequestParser parser KernelInfoRequestMessage = kernelInfoRequestParser
parser ExecuteRequestMessage = executeRequestParser parser ExecuteRequestMessage = executeRequestParser
parser CompleteRequestMessage = completeRequestParser parser CompleteRequestMessage = completeRequestParser
parser ObjectInfoRequestMessage = objectInfoRequestParser
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.
...@@ -120,3 +121,14 @@ completeRequestParser content = parsed ...@@ -120,3 +121,14 @@ completeRequestParser content = parsed
Just decoded = decode content Just decoded = decode content
objectInfoRequestParser :: LByteString -> Message
objectInfoRequestParser content = parsed
where
Success parsed = flip parse decoded $ \obj -> do
oname <- obj .: "oname"
dlevel <- obj .: "detail_level"
return $ ObjectInfoRequest noHeader oname dlevel
Just decoded = decode content
...@@ -61,6 +61,14 @@ instance ToJSON Message where ...@@ -61,6 +61,14 @@ instance ToJSON Message where
"text" .= t, "text" .= t,
"status" .= if s then "ok" :: String else "error" "status" .= if s then "ok" :: String else "error"
] ]
toJSON o@ObjectInfoReply{} = object [
"oname" .= objectName o,
"found" .= objectFound o,
"ismagic" .= False,
"isalias" .= False,
"type_name" .= objectTypeString o,
"docstring" .= objectDocString o
]
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
......
...@@ -99,6 +99,8 @@ data MessageType = KernelInfoReplyMessage ...@@ -99,6 +99,8 @@ data MessageType = KernelInfoReplyMessage
| InputMessage | InputMessage
| CompleteRequestMessage | CompleteRequestMessage
| CompleteReplyMessage | CompleteReplyMessage
| ObjectInfoRequestMessage
| ObjectInfoReplyMessage
instance Show MessageType where instance Show MessageType where
show KernelInfoReplyMessage = "kernel_info_reply" show KernelInfoReplyMessage = "kernel_info_reply"
...@@ -112,6 +114,8 @@ instance Show MessageType where ...@@ -112,6 +114,8 @@ instance Show MessageType where
show InputMessage = "pyin" show InputMessage = "pyin"
show CompleteRequestMessage = "complete_request" show CompleteRequestMessage = "complete_request"
show CompleteReplyMessage = "complete_reply" show CompleteReplyMessage = "complete_reply"
show ObjectInfoRequestMessage = "object_info_request"
show ObjectInfoReplyMessage = "object_info_reply"
instance FromJSON MessageType where instance FromJSON MessageType where
parseJSON (String s) = case s of parseJSON (String s) = case s of
...@@ -219,6 +223,19 @@ data Message ...@@ -219,6 +223,19 @@ data Message
# in other messages. # in other messages.
'status' : 'ok' 'status' : 'ok'
} -} } -}
| ObjectInfoRequest {
header :: MessageHeader,
objectName :: ByteString, -- ^ name of object to be searched for
detailLevel :: Int -- ^ level of detail desired. default (0)
-- is equivalent to typing foo?, (1) is foo?? (don't know yet what this means for haskell)
}
| ObjectInfoReply {
header :: MessageHeader,
objectName :: ByteString,
objectFound :: Bool, -- ^ was the object found?
objectTypeString :: ByteString, -- ^ type info string
objectDocString :: ByteString
}
deriving Show deriving Show
......
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | Description : Argument parsing and basic messaging loop, using Haskell -- | Description : Argument parsing and basic messaging loop, using Haskell
-- Chans to communicate with the ZeroMQ sockets. -- Chans to communicate with the ZeroMQ sockets.
module Main where module Main where
...@@ -18,6 +19,10 @@ import qualified Data.ByteString.Char8 as Chars ...@@ -18,6 +19,10 @@ import qualified Data.ByteString.Char8 as Chars
import IHaskell.IPython import IHaskell.IPython
import IHaskell.Completion (makeCompletions) import IHaskell.Completion (makeCompletions)
import GHC
import Exception (ghandle, gcatch)
import Outputable (showSDoc, ppr)
data KernelState = KernelState data KernelState = KernelState
{ getExecutionCounter :: Int { getExecutionCounter :: Int
} }
...@@ -162,4 +167,21 @@ replyTo _ creq@CompleteRequest{} replyHeader state = trace (show creq) $ do ...@@ -162,4 +167,21 @@ replyTo _ creq@CompleteRequest{} replyHeader state = trace (show creq) $ do
cr <- makeCompletions replyHeader creq cr <- makeCompletions replyHeader creq
return (state, cr) return (state, cr)
replyTo _ ObjectInfoRequest{objectName=oname} replyHeader state = do
dflags <- getSessionDynFlags
maybeDocs <- flip gcatch (\(e::SomeException) -> return Nothing) $ do
result <- exprType . Chars.unpack $ oname
let docs = (showSDoc dflags) . ppr $ result
return (Just docs)
let docs = maybe "" id maybeDocs
let reply = ObjectInfoReply {
header = replyHeader,
objectName = oname,
objectFound = if isNothing maybeDocs then False else True,
objectTypeString = Chars.pack docs,
objectDocString = Chars.pack docs
}
return (state, reply)
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