Skip to content

Commit 077d587

Browse files
committed
address feedback
1 parent 1a069dc commit 077d587

File tree

3 files changed

+32
-32
lines changed

3 files changed

+32
-32
lines changed

ghcide/src/Development/IDE/Plugin/Completions.hs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -47,10 +47,9 @@ import GHC.Exts (fromList, toList)
4747
import Ide.Plugin.Config (Config)
4848
import Ide.Types
4949
import qualified Language.LSP.Server as LSP
50-
import qualified Language.LSP.VFS as VFS
5150
import Text.Fuzzy.Parallel (Scored (..))
5251

53-
import qualified GHC.LanguageExtensions as LangExt
52+
import qualified GHC.LanguageExtensions as LangExt
5453
import Language.LSP.Types
5554

5655
data Log = LogShake Shake.Log deriving Show
@@ -141,12 +140,14 @@ getCompletionsLSP ide plId
141140
exportsCompItems = foldMap (map (fromIdentInfo uri) . Set.toList) . Map.elems . getExportsMap $ exportsMap
142141
exportsCompls = mempty{anyQualCompls = exportsCompItems}
143142
let compls = (fst <$> localCompls) <> (fst <$> nonLocalCompls) <> Just exportsCompls <> Just lModules
144-
143+
145144
-- get HieAst if OverloadedRecordDot is enabled
146-
let uses_th_qq (ms_hspp_opts -> dflags) = xopt LangExt.OverloadedRecordDot dflags
145+
let uses_overloaded_record_dot (ms_hspp_opts . msrModSummary -> dflags) = xopt LangExt.OverloadedRecordDot dflags
147146
ms <- fmap fst <$> useWithStaleFast GetModSummaryWithoutTimestamps npath
148-
astres <- case ms of
149-
Just ms' -> if uses_th_qq . msrModSummary $ ms' then useWithStaleFast GetHieAst npath else return Nothing
147+
astres <- case ms of
148+
Just ms' -> if uses_overloaded_record_dot ms'
149+
then useWithStaleFast GetHieAst npath
150+
else return Nothing
150151
Nothing -> return Nothing
151152

152153
pure (opts, fmap (,pm,binds) compls, moduleExports, astres)
@@ -159,7 +160,7 @@ getCompletionsLSP ide plId
159160
(Just pfix', _) -> do
160161
let clientCaps = clientCapabilities $ shakeExtras ide
161162
config <- getCompletionsConfig plId
162-
163+
163164
allCompletions <- liftIO $ getCompletions plId ideOpts cci' parsedMod astres bindMap pfix' clientCaps config moduleExports
164165
pure $ InL (List $ orderedCompletions allCompletions)
165166
_ -> return (InL $ List [])

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

Lines changed: 19 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -14,14 +14,14 @@ module Development.IDE.Plugin.Completions.Logic (
1414
) where
1515

1616
import Control.Applicative
17-
import Data.Char (isUpper)
17+
import Data.Char (isAlphaNum, isUpper)
1818
import Data.Generics
1919
import Data.List.Extra as List hiding
2020
(stripPrefix)
2121
import qualified Data.Map as Map
2222

23-
import Data.Maybe (fromMaybe, isJust,
24-
mapMaybe, catMaybes)
23+
import Data.Maybe (catMaybes, fromMaybe,
24+
isJust, mapMaybe)
2525
import qualified Data.Text as T
2626
import qualified Text.Fuzzy.Parallel as Fuzzy
2727

@@ -31,7 +31,7 @@ import Data.Either (fromRight)
3131
import Data.Function (on)
3232
import Data.Functor
3333
import qualified Data.HashMap.Strict as HM
34-
import qualified Data.Map.Strict as M
34+
import qualified Data.Map.Strict as M
3535

3636
import qualified Data.HashSet as HashSet
3737
import Data.Monoid (First (..))
@@ -69,11 +69,10 @@ import qualified Language.LSP.VFS as VFS
6969
import Text.Fuzzy.Parallel (Scored (score),
7070
original)
7171

72-
import Development.IDE
73-
import Data.Coerce (coerce)
72+
import Data.Coerce (coerce)
73+
import Development.IDE
7474

75-
import Data.Char (isAlphaNum)
76-
import qualified Data.Rope.UTF16 as Rope
75+
import qualified Data.Rope.UTF16 as Rope
7776

7877
-- Chunk size used for parallelizing fuzzy matching
7978
chunkSize :: Int
@@ -610,14 +609,14 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
610609
lpos = lowerRange position'
611610
hpos = upperRange position'
612611
in getCContext lpos pm <|> getCContext hpos pm
613-
612+
614613
dotFieldSelectorToCompl :: T.Text -> (Bool, CompItem)
615614
dotFieldSelectorToCompl label = (True, CI CiVariable label (ImportedFrom T.empty) Nothing label Nothing emptySpanDoc False Nothing)
616615

617616
-- we need the hieast to be fresh
618617
-- not fresh, hasfield won't have a chance. it would to another larger change to ghc IfaceTyCon to contain record fields
619618
tst :: [(Bool, CompItem)]
620-
tst = case maybe_ast_res of
619+
tst = case maybe_ast_res of
621620
Just (HAR {hieAst = hieast, hieKind = HieFresh},_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) (theFunc HieFresh)
622621
_ -> []
623622

@@ -631,7 +630,7 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
631630
g :: Type -> [(Bool, CompItem)]
632631
g (TyConApp theTyCon _) = map dotFieldSelectorToCompl $ getSels theTyCon
633632
g _ = []
634-
633+
635634
nodeInfoH :: HieKind a -> HieAST a -> NodeInfo a
636635
nodeInfoH (HieFromDisk _) = nodeInfo'
637636
nodeInfoH HieFresh = nodeInfo
@@ -685,7 +684,7 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
685684
thisModName = Local $ nameSrcSpan name
686685

687686
compls
688-
| T.null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($Nothing) <$> anyQualCompls)
687+
| T.null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($ Nothing) <$> anyQualCompls)
689688
| not $ null tst = tst
690689
| otherwise = ((qual,) <$> Map.findWithDefault [] prefixScope (getQualCompls qualCompls))
691690
++ ((notQual,) . ($ Just prefixScope) <$> anyQualCompls)
@@ -947,28 +946,28 @@ mergeListsBy cmp all_lists = merge_lists all_lists
947946
getCompletionPrefix :: (Monad m) => Position -> VFS.VirtualFile -> m (Maybe PosPrefixInfo)
948947
getCompletionPrefix pos@(Position l c) (VFS.VirtualFile _ _ ropetext) =
949948
return $ Just $ fromMaybe (PosPrefixInfo "" "" "" pos) $ do -- Maybe monad
950-
let headMaybe [] = Nothing
949+
let headMaybe [] = Nothing
951950
headMaybe (x:_) = Just x
952-
lastMaybe [] = Nothing
953-
lastMaybe xs = Just $ last xs
951+
lastMaybe [] = Nothing
952+
lastMaybe [x] = Just x
953+
lastMaybe (_:xs) = lastMaybe xs
954954

955955
curLine <- headMaybe $ T.lines $ Rope.toText
956956
$ fst $ Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) ropetext
957957
let beforePos = T.take (fromIntegral c) curLine
958958
curWord <-
959-
if | T.null beforePos -> Just ""
959+
if | T.null beforePos -> Just ""
960960
| T.last beforePos == ' ' -> Just "" -- don't count abc as the curword in 'abc '
961-
| otherwise -> lastMaybe (T.words beforePos)
961+
| otherwise -> lastMaybe (T.words beforePos)
962962

963963
let parts = T.split (=='.')
964964
$ T.takeWhileEnd (\x -> isAlphaNum x || x `elem` ("._'"::String)) curWord
965965
case reverse parts of
966966
[] -> Nothing
967967
(x:xs) -> do
968-
let modParts = dropWhile (\_ -> False)
969-
$ reverse $ filter (not .T.null) xs
968+
let modParts = reverse $ filter (not .T.null) xs
970969
modName = T.intercalate "." modParts
971970
return $ PosPrefixInfo { fullLine = curLine, prefixScope = modName, prefixText = x, cursorPos = pos }
972971

973972
completionPrefixPos :: PosPrefixInfo -> Position
974-
completionPrefixPos PosPrefixInfo { cursorPos = Position ln co, prefixText = str} = Position ln (co - (fromInteger . toInteger . T.length $ str) - 1)
973+
completionPrefixPos PosPrefixInfo { cursorPos = Position ln co, prefixText = str} = Position ln (co - (fromInteger . toInteger . T.length $ str) - 1)

ghcide/src/Development/IDE/Plugin/Completions/Types.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -139,10 +139,10 @@ instance Semigroup CachedCompletions where
139139
CC (a<>a') (b<>b') (c<>c') (d<>d') (e<>e')
140140

141141

142-
-- moved here from Language.LSP.VHS
142+
-- moved here from Language.LSP.VFS
143143
-- | Describes the line at the current cursor position
144144
data PosPrefixInfo = PosPrefixInfo
145-
{ fullLine :: !T.Text
145+
{ fullLine :: !T.Text
146146
-- ^ The full contents of the line the cursor is at
147147

148148
, prefixScope :: !T.Text
@@ -152,10 +152,10 @@ data PosPrefixInfo = PosPrefixInfo
152152
-- If OverloadedRecordDot is enabled, "Shape.rect.width" will be
153153
-- "Shape.rect"
154154

155-
, prefixText :: !T.Text
155+
, prefixText :: !T.Text
156156
-- ^ The word right before the cursor position, after removing the module part.
157157
-- For example if the user has typed "Data.Maybe.from",
158158
-- then this property will be "from"
159-
, cursorPos :: !J.Position
159+
, cursorPos :: !J.Position
160160
-- ^ The cursor position
161-
} deriving (Show,Eq)
161+
} deriving (Show,Eq)

0 commit comments

Comments
 (0)