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

updated

parent b7070c77
...@@ -36,7 +36,8 @@ ...@@ -36,7 +36,8 @@
"cell_type": "code", "cell_type": "code",
"collapsed": false, "collapsed": false,
"input": [ "input": [
"import Control.Monad.Identity" "import Control.Monad.Identity\n",
"lkajsdflkj "
], ],
"language": "python", "language": "python",
"metadata": {}, "metadata": {},
......
...@@ -129,6 +129,7 @@ activateParsingExtensions (Directive SetDynFlag flags) = ...@@ -129,6 +129,7 @@ activateParsingExtensions (Directive SetDynFlag flags) =
case stripPrefix "-X" flags of case stripPrefix "-X" flags of
Just ext -> void $ setExtension ext Just ext -> void $ setExtension ext
Nothing -> return () Nothing -> return ()
activateParsingExtensions _ = return ()
-- | Parse a single chunk of code, as indicated by the layout of the code. -- | Parse a single chunk of code, as indicated by the layout of the code.
parseCodeChunk :: GhcMonad m => String -> LineNumber -> m CodeBlock parseCodeChunk :: GhcMonad m => String -> LineNumber -> m CodeBlock
......
...@@ -2,29 +2,35 @@ ...@@ -2,29 +2,35 @@
-- | 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
import ClassyPrelude hiding (liftIO)
import Prelude (last, read) -- Prelude imports.
import Control.Concurrent.Chan import ClassyPrelude hiding (liftIO)
import Control.Concurrent (threadDelay) import Prelude (last, read)
import Data.Aeson
import Text.Printf -- Standard library imports.
import System.Exit (exitSuccess) import Control.Concurrent (threadDelay)
import System.Directory import Control.Concurrent.Chan
import Data.Aeson
import qualified Data.Map as Map import Data.String.Utils (strip)
import System.Directory
import IHaskell.Types import System.Exit (exitSuccess)
import IPython.ZeroMQ import Text.Printf
import qualified IPython.Message.UUID as UUID import qualified Data.Map as Map
import IHaskell.Eval.Evaluate
import IHaskell.Eval.Completion (complete) -- IHaskell imports.
import IHaskell.Eval.Info import IHaskell.Eval.Completion (complete)
import qualified Data.ByteString.Char8 as Chars import IHaskell.Eval.Evaluate
import IHaskell.IPython import IHaskell.Eval.Info
import qualified IPython.Stdin as Stdin import IHaskell.Flags
import IHaskell.Flags import IHaskell.IPython
import IHaskell.Types
import GHC hiding (extensions, language) import IPython.ZeroMQ
import qualified Data.ByteString.Char8 as Chars
import qualified IPython.Message.UUID as UUID
import qualified IPython.Stdin as Stdin
-- GHC API imports.
import GHC hiding (extensions, language)
import Outputable (showSDoc, ppr) import Outputable (showSDoc, ppr)
-- | Compute the GHC API version number using the dist/build/autogen/cabal_macros.h -- | Compute the GHC API version number using the dist/build/autogen/cabal_macros.h
...@@ -304,23 +310,23 @@ replyTo interface req@ExecuteRequest{ getCode = code } replyHeader state = do ...@@ -304,23 +310,23 @@ replyTo interface req@ExecuteRequest{ getCode = code } replyHeader state = do
replyTo _ req@CompleteRequest{} replyHeader state = do replyTo _ req@CompleteRequest{} replyHeader state = do
(matchedText, completions) <- complete (Chars.unpack $ getCodeLine req) (getCursorPos req) (matchedText, completions) <- complete (Chars.unpack $ getCodeLine req) (getCursorPos req)
let reply = CompleteReply replyHeader (map Chars.pack completions) (Chars.pack matchedText) (getCodeLine req) True let reply = CompleteReply replyHeader (map Chars.pack completions) (Chars.pack matchedText) (getCodeLine req) True
return (state, reply) return (state, reply)
-- | Reply to the object_info_request message. Given an object name, return -- | Reply to the object_info_request message. Given an object name, return
-- | the associated type calculated by GHC. -- | the associated type calculated by GHC.
replyTo _ ObjectInfoRequest{objectName=oname} replyHeader state = do replyTo _ ObjectInfoRequest{objectName=oname} replyHeader state = do
docs <- info $ Chars.unpack oname docs <- info $ Chars.unpack oname
let reply = ObjectInfoReply { let reply = ObjectInfoReply {
header = replyHeader, header = replyHeader,
objectName = oname, objectName = oname,
objectFound = docs == "", objectFound = strip docs /= "",
objectTypeString = Chars.pack docs, objectTypeString = Chars.pack docs,
objectDocString = Chars.pack docs objectDocString = Chars.pack docs
} }
return (state, reply) 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