Commit 258a07d3 authored by Andrew Gibiansky's avatar Andrew Gibiansky

updated

parent b7070c77
......@@ -36,7 +36,8 @@
"cell_type": "code",
"collapsed": false,
"input": [
"import Control.Monad.Identity"
"import Control.Monad.Identity\n",
"lkajsdflkj "
],
"language": "python",
"metadata": {},
......
......@@ -129,6 +129,7 @@ activateParsingExtensions (Directive SetDynFlag flags) =
case stripPrefix "-X" flags of
Just ext -> void $ setExtension ext
Nothing -> return ()
activateParsingExtensions _ = return ()
-- | Parse a single chunk of code, as indicated by the layout of the code.
parseCodeChunk :: GhcMonad m => String -> LineNumber -> m CodeBlock
......
......@@ -2,28 +2,34 @@
-- | Description : Argument parsing and basic messaging loop, using Haskell
-- Chans to communicate with the ZeroMQ sockets.
module Main where
-- Prelude imports.
import ClassyPrelude hiding (liftIO)
import Prelude (last, read)
import Control.Concurrent.Chan
-- Standard library imports.
import Control.Concurrent (threadDelay)
import Control.Concurrent.Chan
import Data.Aeson
import Text.Printf
import System.Exit (exitSuccess)
import Data.String.Utils (strip)
import System.Directory
import System.Exit (exitSuccess)
import Text.Printf
import qualified Data.Map as Map
import IHaskell.Types
import IPython.ZeroMQ
import qualified IPython.Message.UUID as UUID
import IHaskell.Eval.Evaluate
-- IHaskell imports.
import IHaskell.Eval.Completion (complete)
import IHaskell.Eval.Evaluate
import IHaskell.Eval.Info
import qualified Data.ByteString.Char8 as Chars
import IHaskell.Flags
import IHaskell.IPython
import IHaskell.Types
import IPython.ZeroMQ
import qualified Data.ByteString.Char8 as Chars
import qualified IPython.Message.UUID as UUID
import qualified IPython.Stdin as Stdin
import IHaskell.Flags
-- GHC API imports.
import GHC hiding (extensions, language)
import Outputable (showSDoc, ppr)
......@@ -316,7 +322,7 @@ replyTo _ ObjectInfoRequest{objectName=oname} replyHeader state = do
let reply = ObjectInfoReply {
header = replyHeader,
objectName = oname,
objectFound = docs == "",
objectFound = strip docs /= "",
objectTypeString = Chars.pack docs,
objectDocString = Chars.pack docs
}
......
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