Commit a2553fa5 authored by Adam Vogt's avatar Adam Vogt

generate completions on the ghc-side, doesn't get interpreted correctly yet

see note in Completion.hs
parent 3700cbb3
......@@ -70,6 +70,8 @@ executable IHaskell
ghc ==7.6.*,
ghc-paths ==0.1.*,
random ==1.0.*,
split,
utf8-string,
strict ==0.3.*,
shelly ==1.3.*,
text ==0.11.*
{-# LANGUAGE PatternGuards #-}
{- | very approximate completion. Seems to generate what is required by
<http://ipython.org/ipython-doc/dev/development/messaging.html#complete>,
but for whatever reason nothing gets added when the liftIO below prints
stuff like:
> {"status":"ok","text":"import Data hea","matches":["head"]}
When the cursor is after the hea, and you press tab.
-}
module IHaskell.Completion (makeCompletions) where
import Prelude
import Data.List
import IHaskell.Types
import GhcMonad(liftIO)
import qualified GHC
import Outputable (showPpr)
import Data.Char
import Data.ByteString.UTF8
import Data.List.Split
import Data.List.Split.Internals
import Data.Aeson
import IHaskell.Message.Writer
import qualified Data.ByteString.Lazy as L
makeCompletions replyHeader (CompleteRequest hdr code line pos) = do
ns <- GHC.getRdrNamesInScope
fs <- GHC.getProgramDynFlags
let candidate = getWordAt (toString line) pos
opts | Just cand <- candidate = filter (cand `isPrefixOf`) $ map (showPpr fs) ns
| otherwise = []
let reply = CompleteReply replyHeader (map fromString opts) line True
liftIO (L.putStrLn $ encode $ toJSON reply)
return reply
-- there are better ways to accomplish this
getWordAt :: String -> Int -> Maybe String
getWordAt xs n =
fmap (map fst) $
find (any (== n) . map snd) $
split (defaultSplitter{
delimiter = Delimiter [ (==) ' ' . fst ],
condensePolicy = Condense })
(zip xs [1 .. ])
......@@ -12,6 +12,7 @@ import qualified IHaskell.Message.UUID as UUID
import IHaskell.Eval.Evaluate
import qualified Data.ByteString.Char8 as Chars
import IHaskell.IPython
import IHaskell.Completion (makeCompletions)
data KernelState = KernelState
{ getExecutionCounter :: Int
......@@ -147,7 +148,8 @@ replyTo interface ExecuteRequest{ getCode = code } replyHeader state = do
})
replyTo _ cr@CompleteRequest{} replyHeader state = trace (show cr) $ do
return (state, CompleteReply replyHeader [] "" True)
replyTo _ creq@CompleteRequest{} replyHeader state = trace (show creq) $ do
cr <- makeCompletions replyHeader creq
return (state, cr)
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