Commit 0e96a451 authored by Eyal Dechter's avatar Eyal Dechter

Add basic tooltip functionality and implement object_info_request and object_info_reply messages.

IPython has a tooltip feature which shows an info box under the cursor containing info about the current object. I have ported this to IHaskell. Basically, tooltip.js sends an object_info_request message to the kernel and the kernel responds with type information about the closest object.
parent adfa3af9
{-# LANGUAGE QuasiQuotes #-}
-- | Description : IPython configuration files are compiled-into IHaskell
module IHaskell.Config (ipython, notebook, console, qtconsole, customjs) where
module IHaskell.Config (ipython, notebook, console, qtconsole, customjs, tooltipjs) where
import Data.String.Here
import ClassyPrelude
......@@ -19,3 +19,6 @@ qtconsole = [template|config/ipython_qtconsole_config.py|]
customjs :: String
customjs = [template|config/custom.js|]
tooltipjs :: String
tooltipjs = [template|deps/tooltip.js|]
......@@ -97,6 +97,12 @@ writeConfigFilesTo profileDir ihaskellPath = do
-- The custom directory many not exist, in which case we'll create it.
mkdir_p (conf "static/custom/")
writeFile (conf "static/custom/custom.js") Config.customjs
-- The notebook/js directory many not exist, in which case we'll create it.
mkdir_p (conf "static/notebook/")
mkdir_p (conf "static/notebook/js")
writeFile (conf "static/notebook/js/tooltip.js") Config.tooltipjs
where
conf filename = fromText $ profileDir ++ filename
......
......@@ -75,7 +75,7 @@ parser :: MessageType -- ^ The message type being parsed.
parser KernelInfoRequestMessage = kernelInfoRequestParser
parser ExecuteRequestMessage = executeRequestParser
parser CompleteRequestMessage = completeRequestParser
parser ObjectInfoRequestMessage = objectInfoRequestParser
parser ObjectInfoRequestMessage = objectInfoRequestParser
parser other = error $ "Unknown message type " ++ show other
-- | Parse a kernel info request.
......
......@@ -130,6 +130,8 @@ instance FromJSON MessageType where
"pyin" -> return InputMessage
"complete_request" -> return CompleteRequestMessage
"complete_reply" -> return CompleteReplyMessage
"object_info_request" -> return ObjectInfoRequestMessage
"object_info_reply" -> return ObjectInfoReplyMessage
_ -> fail ("Unknown message type: " ++ show s)
parseJSON _ = fail "Must be a string."
......@@ -269,4 +271,5 @@ replyType :: MessageType -> MessageType
replyType KernelInfoRequestMessage = KernelInfoReplyMessage
replyType ExecuteRequestMessage = ExecuteReplyMessage
replyType CompleteRequestMessage = CompleteReplyMessage
replyType ObjectInfoRequestMessage = ObjectInfoReplyMessage
replyType messageType = error $ "No reply for message type " ++ show messageType
......@@ -167,6 +167,8 @@ replyTo _ creq@CompleteRequest{} replyHeader state = trace (show creq) $ do
cr <- makeCompletions replyHeader creq
return (state, cr)
-- | 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
dflags <- getSessionDynFlags
maybeDocs <- flip gcatch (\(e::SomeException) -> return Nothing) $ do
......
This diff is collapsed.
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