Commit 1019b37c authored by Andrew Gibiansky's avatar Andrew Gibiansky

Merge pull request #34 from edechter/tooltip

Added basic tooltip functionality. 
parents 341a5cd1 f8beae87
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
-- | Description : IPython configuration files are compiled-into IHaskell -- | 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 Data.String.Here
import ClassyPrelude import ClassyPrelude
...@@ -19,3 +19,6 @@ qtconsole = [template|config/ipython_qtconsole_config.py|] ...@@ -19,3 +19,6 @@ qtconsole = [template|config/ipython_qtconsole_config.py|]
customjs :: String customjs :: String
customjs = [template|config/custom.js|] customjs = [template|config/custom.js|]
tooltipjs :: String
tooltipjs = [template|deps/tooltip.js|]
...@@ -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
......
...@@ -97,6 +97,12 @@ writeConfigFilesTo profileDir ihaskellPath = do ...@@ -97,6 +97,12 @@ writeConfigFilesTo profileDir ihaskellPath = do
-- The custom directory many not exist, in which case we'll create it. -- The custom directory many not exist, in which case we'll create it.
mkdir_p (conf "static/custom/") mkdir_p (conf "static/custom/")
writeFile (conf "static/custom/custom.js") Config.customjs 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 where
conf filename = fromText $ profileDir ++ filename conf filename = fromText $ profileDir ++ filename
......
...@@ -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
...@@ -62,6 +62,14 @@ instance ToJSON Message where ...@@ -62,6 +62,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
...@@ -126,6 +130,8 @@ instance FromJSON MessageType where ...@@ -126,6 +130,8 @@ instance FromJSON MessageType where
"pyin" -> return InputMessage "pyin" -> return InputMessage
"complete_request" -> return CompleteRequestMessage "complete_request" -> return CompleteRequestMessage
"complete_reply" -> return CompleteReplyMessage "complete_reply" -> return CompleteReplyMessage
"object_info_request" -> return ObjectInfoRequestMessage
"object_info_reply" -> return ObjectInfoReplyMessage
_ -> fail ("Unknown message type: " ++ show s) _ -> fail ("Unknown message type: " ++ show s)
parseJSON _ = fail "Must be a string." parseJSON _ = fail "Must be a string."
...@@ -220,6 +226,19 @@ data Message ...@@ -220,6 +226,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
...@@ -252,4 +271,5 @@ replyType :: MessageType -> MessageType ...@@ -252,4 +271,5 @@ replyType :: MessageType -> MessageType
replyType KernelInfoRequestMessage = KernelInfoReplyMessage replyType KernelInfoRequestMessage = KernelInfoReplyMessage
replyType ExecuteRequestMessage = ExecuteReplyMessage replyType ExecuteRequestMessage = ExecuteReplyMessage
replyType CompleteRequestMessage = CompleteReplyMessage replyType CompleteRequestMessage = CompleteReplyMessage
replyType ObjectInfoRequestMessage = ObjectInfoReplyMessage
replyType messageType = error $ "No reply for message type " ++ show messageType replyType messageType = error $ "No reply for message type " ++ show messageType
{-# 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,23 @@ replyTo _ creq@CompleteRequest{} replyHeader state = trace (show creq) $ do ...@@ -162,4 +167,23 @@ replyTo _ creq@CompleteRequest{} replyHeader state = trace (show creq) $ do
cr <- makeCompletions replyHeader creq cr <- makeCompletions replyHeader creq
return (state, cr) 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
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)
// The following code was taken directively from the ipython repo at:
// ipython/ipython/master/IPython/html/static/notebook/js/tooltip.js
// commit: #4195
// ----------------------------------------------------------------------------
// ----------------------------------------------------------------------------
// Copyright (C) 2008-2011 The IPython Development Team
// Distributed under the terms of the BSD License. The full license is in
// the file COPYING, distributed as part of this software.
// ----------------------------------------------------------------------------
// ============================================================================
// Tooltip
// ============================================================================
// you can set the autocall time by setting `IPython.tooltip.time_before_tooltip` in ms
// you can configure the differents action of pressing tab several times in a row by
// setting/appending different fonction in the array
// IPython.tooltip.tabs_functions
// eg :
// IPython.tooltip.tabs_functions[4] = function (){console.log('this is the action of the 4th tab pressing')}
var IPython = (function (IPython) {
"use strict";
var utils = IPython.utils;
// tooltip constructor
var Tooltip = function () {
var that = this;
this.time_before_tooltip = 1200;
// handle to html
this.tooltip = \$('#tooltip');
this._hidden = true;
// variable for consecutive call
this._old_cell = null;
this._old_request = null;
this._consecutive_counter = 0;
// 'sticky ?'
this._sticky = false;
// display tooltip if the docstring is empty?
this._hide_if_no_docstring = false;
// contain the button in the upper right corner
this.buttons = \$('<div/>').addClass('tooltipbuttons');
// will contain the docstring
this.text = \$('<div/>').addClass('tooltiptext').addClass('smalltooltip');
// build the buttons menu on the upper right
// expand the tooltip to see more
var expandlink = \$('<a/>').attr('href', "#").addClass("ui-corner-all") //rounded corner
.attr('role', "button").attr('id', 'expanbutton').attr('title', 'Grow the tooltip vertically (press tab 2 times)').click(function () {
that.expand()
}).append(
\$('<span/>').text('Expand').addClass('ui-icon').addClass('ui-icon-plus'));
// open in pager
var morelink = \$('<a/>').attr('href', "#").attr('role', "button").addClass('ui-button').attr('title', 'show the current docstring in pager (press tab 4 times)');
var morespan = \$('<span/>').text('Open in Pager').addClass('ui-icon').addClass('ui-icon-arrowstop-l-n');
morelink.append(morespan);
morelink.click(function () {
that.showInPager(that._old_cell);
});
// close the tooltip
var closelink = \$('<a/>').attr('href', "#").attr('role', "button").addClass('ui-button');
var closespan = \$('<span/>').text('Close').addClass('ui-icon').addClass('ui-icon-close');
closelink.append(closespan);
closelink.click(function () {
that.remove_and_cancel_tooltip(true);
});
this._clocklink = \$('<a/>').attr('href', "#");
this._clocklink.attr('role', "button");
this._clocklink.addClass('ui-button');
this._clocklink.attr('title', 'Tootip is not dismissed while typing for 10 seconds');
var clockspan = \$('<span/>').text('Close');
clockspan.addClass('ui-icon');
clockspan.addClass('ui-icon-clock');
this._clocklink.append(clockspan);
this._clocklink.click(function () {
that.cancel_stick();
});
//construct the tooltip
// add in the reverse order you want them to appear
this.buttons.append(closelink);
this.buttons.append(expandlink);
this.buttons.append(morelink);
this.buttons.append(this._clocklink);
this._clocklink.hide();
// we need a phony element to make the small arrow
// of the tooltip in css
// we will move the arrow later
this.arrow = \$('<div/>').addClass('pretooltiparrow');
this.tooltip.append(this.buttons);
this.tooltip.append(this.arrow);
this.tooltip.append(this.text);
// function that will be called if you press tab 1, 2, 3... times in a row
this.tabs_functions = [function (cell, text) {
that._request_tooltip(cell, text);
}, function () {
that.expand();
}, function () {
that.stick();
}, function (cell) {
that.cancel_stick();
that.showInPager(cell);
}];
// call after all the tabs function above have bee call to clean their effects
// if necessary
this.reset_tabs_function = function (cell, text) {
this._old_cell = (cell) ? cell : null;
this._old_request = (text) ? text : null;
this._consecutive_counter = 0;
}
};
Tooltip.prototype.showInPager = function (cell) {
// reexecute last call in pager by appending ? to show back in pager
var that = this;
var empty = function () {};
cell.kernel.execute(
that.name + '?', {
'execute_reply': empty,
'output': empty,
'clear_output': empty,
'cell': cell
}, {
'silent': false,
'store_history': true
});
this.remove_and_cancel_tooltip();
}
// grow the tooltip verticaly
Tooltip.prototype.expand = function () {
this.text.removeClass('smalltooltip');
this.text.addClass('bigtooltip');
\$('#expanbutton').hide('slow');
}
// deal with all the logic of hiding the tooltip
// and reset it's status
Tooltip.prototype._hide = function () {
this.tooltip.fadeOut('fast');
\$('#expanbutton').show('slow');
this.text.removeClass('bigtooltip');
this.text.addClass('smalltooltip');
// keep scroll top to be sure to always see the first line
this.text.scrollTop(0);
this._hidden = true;
this.code_mirror = null;
}
Tooltip.prototype.remove_and_cancel_tooltip = function (force) {
// note that we don't handle closing directly inside the calltip
// as in the completer, because it is not focusable, so won't
// get the event.
if (this._sticky == false || force == true) {
this.cancel_stick();
this._hide();
}
this.cancel_pending();
this.reset_tabs_function();
}
// cancel autocall done after '(' for example.
Tooltip.prototype.cancel_pending = function () {
if (this._tooltip_timeout != null) {
clearTimeout(this._tooltip_timeout);
this._tooltip_timeout = null;
}
}
// will trigger tooltip after timeout
Tooltip.prototype.pending = function (cell, hide_if_no_docstring) {
var that = this;
this._tooltip_timeout = setTimeout(function () {
that.request(cell, hide_if_no_docstring)
}, that.time_before_tooltip);
}
Tooltip.prototype._request_tooltip = function (cell, func) {
// use internally just to make the request to the kernel
// Feel free to shorten this logic if you are better
// than me in regEx
// basicaly you shoul be able to get xxx.xxx.xxx from
// something(range(10), kwarg=smth) ; xxx.xxx.xxx( firstarg, rand(234,23), kwarg1=2,
// remove everything between matchin bracket (need to iterate)
var matchBracket = /\\([^\\(\\)]+\\)/g;
var endBracket = /\\([^\\(]*\$/g;
var oldfunc = func;
func = func.replace(matchBracket, "");
while (oldfunc != func) {
oldfunc = func;
func = func.replace(matchBracket, "");
}
// remove everything after last open bracket
func = func.replace(endBracket, "");
var re = /[a-z_][0-9a-z._!]+\$/gi; // casse insensitive
var that = this
var callbacks_v2 = function(data){
\$.proxy(that._show(data.content), that)
}
var callbacks = {
'object_info_reply': \$.proxy(this._show, this)
}
if(cell.kernel.object_info_request){
// we are on IPython 1.x and early 2.0 (before bidirectionnal js comm)
var msg_id = cell.kernel.object_info_request(re.exec(func), callbacks);
} else {
// we are after that, 2.0-dev late october and after
var msg_id = cell.kernel.object_info(re.exec(func), callbacks_v2);
}
}
// make an imediate completion request
Tooltip.prototype.request = function (cell, hide_if_no_docstring) {
// request(codecell)
// Deal with extracting the text from the cell and counting
// call in a row
this.cancel_pending();
var editor = cell.code_mirror;
var cursor = editor.getCursor();
var text = editor.getRange({
line: cursor.line,
ch: 0
}, cursor).trim();
this._hide_if_no_docstring = hide_if_no_docstring;
if(editor.somethingSelected()){
text = editor.getSelection();
}
// need a permanent handel to code_mirror for future auto recall
this.code_mirror = editor;
// now we treat the different number of keypress
// first if same cell, same text, increment counter by 1
if (this._old_cell == cell && this._old_request == text && this._hidden == false) {
this._consecutive_counter++;
} else {
// else reset
this.cancel_stick();
this.reset_tabs_function (cell, text);
}
// don't do anything if line beggin with '(' or is empty
if (text === "" || text === "(") {
return;
}
this.tabs_functions[this._consecutive_counter](cell, text);
// then if we are at the end of list function, reset
if (this._consecutive_counter == this.tabs_functions.length) this.reset_tabs_function (cell, text);
return;
}
// cancel the option of having the tooltip to stick
Tooltip.prototype.cancel_stick = function () {
clearTimeout(this._stick_timeout);
this._stick_timeout = null;
this._clocklink.hide('slow');
this._sticky = false;
}
// put the tooltip in a sicky state for 10 seconds
// it won't be removed by remove_and_cancell() unless you called with
// the first parameter set to true.
// remove_and_cancell_tooltip(true)
Tooltip.prototype.stick = function (time) {
time = (time != undefined) ? time : 10;
var that = this;
this._sticky = true;
this._clocklink.show('slow');
this._stick_timeout = setTimeout(function () {
that._sticky = false;
that._clocklink.hide('slow');
}, time * 1000);
}
// should be called with the kernel reply to actually show the tooltip
Tooltip.prototype._show = function (reply) {
// move the bubble if it is not hidden
// otherwise fade it
this.name = reply.name;
// do some math to have the tooltip arrow on more or less on left or right
// width of the editor
var w = \$(this.code_mirror.getScrollerElement()).width();
// ofset of the editor
var o = \$(this.code_mirror.getScrollerElement()).offset();
// whatever anchor/head order but arrow at mid x selection
var anchor = this.code_mirror.cursorCoords(false);
var head = this.code_mirror.cursorCoords(true);
var xinit = (head.left+anchor.left)/2;
var xinter = o.left + (xinit - o.left) / w * (w - 450);
var posarrowleft = xinit - xinter;
if (this._hidden == false) {
this.tooltip.animate({
'left': xinter - 30 + 'px',
'top': (head.bottom + 10) + 'px'
});
} else {
this.tooltip.css({
'left': xinter - 30 + 'px'
});
this.tooltip.css({
'top': (head.bottom + 10) + 'px'
});
}
this.arrow.animate({
'left': posarrowleft + 'px'
});
// build docstring
var defstring = reply.call_def;
if (defstring == null) {
defstring = reply.init_definition;
}
if (defstring == null) {
defstring = reply.definition;
}
var docstring = reply.call_docstring;
if (docstring == null) {
docstring = reply.init_docstring;
}
if (docstring == null) {
docstring = reply.docstring;
}
if (docstring == null) {
// For reals this time, no docstring
if (this._hide_if_no_docstring) {
return;
} else {
docstring = "<empty docstring>";
}
}
this.tooltip.fadeIn('fast');
this._hidden = false;
this.text.children().remove();
var pre = \$('<pre/>').html(utils.fixConsole(docstring));
if (defstring) {
var defstring_html = \$('<pre/>').html(utils.fixConsole(defstring));
this.text.append(defstring_html);
}
this.text.append(pre);
// keep scroll top to be sure to always see the first line
this.text.scrollTop(0);
}
IPython.Tooltip = Tooltip;
return IPython;
}(IPython));
\ No newline at end of file
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