Commit f708b881 authored by Andrew Gibiansky's avatar Andrew Gibiansky

Made completion code a bit nicer. Removed dups.

parent d72c9c5b
...@@ -47,7 +47,7 @@ ...@@ -47,7 +47,7 @@
"collapsed": false, "collapsed": false,
"input": [ "input": [
"import Control.Applicative\n", "import Control.Applicative\n",
"\n", "print\n",
"print $ (+) <$> Just 3 <*> Just 10" "print $ (+) <$> Just 3 <*> Just 10"
], ],
"language": "python", "language": "python",
......
{-# LANGUAGE PatternGuards #-}
{- | Description : generates tab-completion options {- | Description : generates tab-completion options
context-insensitive completion for what is probably context-insensitive completion for what is probably
...@@ -18,51 +17,54 @@ ...@@ -18,51 +17,54 @@
module IHaskell.Completion (makeCompletions) where module IHaskell.Completion (makeCompletions) where
import Prelude import Prelude
import Data.List import Data.List (find, isPrefixOf, nub)
import IHaskell.Types
import GhcMonad(liftIO, GhcMonad)
import qualified GHC import qualified GHC
import GhcMonad(liftIO)
import Outputable (showPpr) import Outputable (showPpr)
import Data.Char import Data.Char
import Data.ByteString.UTF8 import Data.ByteString.UTF8 hiding (drop)
import Data.List.Split import Data.List.Split
import Data.List.Split.Internals import Data.List.Split.Internals
import Data.Aeson
import IHaskell.Message.Writer
import qualified Data.ByteString.Lazy as L
import Data.Maybe import Data.Maybe
makeCompletions import IHaskell.Types
:: GHC.GhcMonad m => MessageHeader -> Message -> m Message
makeCompletions replyHeader (CompleteRequest hdr code line pos) = do import Control.Applicative ((<$>))
ns <- GHC.getRdrNamesInScope makeCompletions :: GHC.GhcMonad m => MessageHeader -> Message -> m Message
fs <- GHC.getProgramDynFlags makeCompletions replyHeader (CompleteRequest _ _ line pos) = do
names <- GHC.getRdrNamesInScope
flags <- GHC.getProgramDynFlags
let candidate = getWordAt (toString line) pos let maybeCand = getWordAt (toString line) pos
opts | Just cand <- candidate = filter (cand `isPrefixOf`) $ map (showPpr fs) ns options =
| otherwise = [] case maybeCand of
matched_text = fromString $ fromMaybe "" candidate Nothing -> []
Just candidate -> nub $ filter (candidate `isPrefixOf`) $ map (showPpr flags) names
matched_text = fromString $ fromMaybe "" maybeCand
return $ CompleteReply replyHeader (map fromString opts) matched_text line True return $ CompleteReply replyHeader (map fromString options) matched_text line True
-- maybe there are better ways to be sure we're getting only -- | Get the word under a given cursor location.
-- the whole word under the cursor...
getWordAt :: String -> Int -> Maybe String getWordAt :: String -> Int -> Maybe String
getWordAt xs n = getWordAt xs n = map fst <$> find (elem n . map snd) (split splitter $ zip xs [1 .. ])
fmap (map fst) $ where
find (any (== n) . map snd) $ splitter = defaultSplitter {
split (defaultSplitter{ -- Split using only the characters, which are the first elements of
delimiter = Delimiter [ isDelim . fst ], -- the (char, index) tuple
condensePolicy = Condense }) delimiter = Delimiter [isDelim . fst],
(zip xs [1 .. ]) -- Condense multiple delimiters into one
condensePolicy = Condense
}
isDelim char =
case drop (max 0 (n - 1)) xs of
x:_ -> (char `elem` neverIdent) || if isSymbol x
then isAlpha char
else isSymbol char
_ -> char `elem` neverIdent
where isDelim | x:_ <- Data.List.drop (max 0 (n-1)) xs = \s -> -- These are never part of an identifier, except for the dot.
(s `elem` neverIdent) -- Qualified names are tricky!
|| if isSymbol x then isAlpha s neverIdent = " \t(),{}[]\\'\"`."
else isSymbol s
| otherwise = \s -> s `elem` neverIdent
-- these (and others?) are never part of an identifier
-- except for the dot (qualified names are tricky)
neverIdent = " \t(),{}[]\\'\"`."
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