diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index 6fc3489353..53126af81f 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -173,6 +173,7 @@ library Development.IDE.Types.Shake Development.IDE.Plugin Development.IDE.Plugin.Completions + Development.IDE.Plugin.Completions.Types Development.IDE.Plugin.CodeAction Development.IDE.Plugin.CodeAction.ExactPrint Development.IDE.Plugin.HLS @@ -204,7 +205,6 @@ library Development.IDE.Plugin.CodeAction.Rules Development.IDE.Plugin.CodeAction.RuleTypes Development.IDE.Plugin.Completions.Logic - Development.IDE.Plugin.Completions.Types Development.IDE.Plugin.HLS.Formatter Development.IDE.Types.Action ghc-options: -Wall -Wno-name-shadowing -Wincomplete-uni-patterns diff --git a/ghcide/src/Development/IDE/GHC/Compat.hs b/ghcide/src/Development/IDE/GHC/Compat.hs index dcb4e4db94..f7571a1593 100644 --- a/ghcide/src/Development/IDE/GHC/Compat.hs +++ b/ghcide/src/Development/IDE/GHC/Compat.hs @@ -60,7 +60,7 @@ module Development.IDE.GHC.Compat( module Compat.HieTypes, module Compat.HieUtils, dropForAll - ) where + ,isQualifiedImport) where #if MIN_GHC_API_VERSION(8,10,0) import LinkerTypes @@ -300,3 +300,12 @@ pattern FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res} #else pattern FunTy arg res <- TyCoRep.FunTy arg res #endif + +isQualifiedImport :: ImportDecl a -> Bool +#if MIN_GHC_API_VERSION(8,10,0) +isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False +isQualifiedImport ImportDecl{} = True +#else +isQualifiedImport ImportDecl{ideclQualified} = ideclQualified +#endif +isQualifiedImport _ = False diff --git a/ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs b/ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs index 49114c70d0..762ba294c6 100644 --- a/ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs +++ b/ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs @@ -6,6 +6,7 @@ module Development.IDE.Plugin.CodeAction.ExactPrint ( Rewrite (..), rewriteToEdit, + rewriteToWEdit, transferAnn, -- * Utilities @@ -40,6 +41,8 @@ import Retrie.GHC (rdrNameOcc, unpackFS, mkRealSrcSpan, realSrcSpanEnd) import Development.IDE.Spans.Common import Development.IDE.GHC.Error import Safe (lastMay) +import Data.Generics (listify) +import GHC.Exts (IsList (fromList)) ------------------------------------------------------------------------------ @@ -56,7 +59,7 @@ data Rewrite where ------------------------------------------------------------------------------ --- | Convert a 'Rewrite' into a 'WorkspaceEdit'. +-- | Convert a 'Rewrite' into a list of '[TextEdit]'. rewriteToEdit :: DynFlags -> Anns -> @@ -71,6 +74,16 @@ rewriteToEdit dflags anns (Rewrite dst f) = do ] pure editMap +-- | Convert a 'Rewrite' into a 'WorkspaceEdit' +rewriteToWEdit :: DynFlags -> Uri -> Anns -> Rewrite -> Either String WorkspaceEdit +rewriteToWEdit dflags uri anns r = do + edits <- rewriteToEdit dflags anns r + return $ + WorkspaceEdit + { _changes = Just (fromList [(uri, List edits)]) + , _documentChanges = Nothing + } + ------------------------------------------------------------------------------ -- | Fix the parentheses around a type context @@ -200,17 +213,25 @@ extendImportTopLevel df idnetifier (L l it@ImportDecl {..}) src <- uniqueSrcSpanT top <- uniqueSrcSpanT rdr <- liftParseAST df idnetifier + + let alreadyImported = + showNameWithoutUniques (occName (unLoc rdr)) `elem` + map (showNameWithoutUniques @OccName) (listify (const True) lies) + when alreadyImported $ + lift (Left $ idnetifier <> " already imported") + let lie = L src $ IEName rdr x = L top $ IEVar noExtField lie - when hasSibling $ - addTrailingCommaT (last lies) - addSimpleAnnT x (DP (0, if hasSibling then 1 else 0)) [] - addSimpleAnnT rdr dp00 $ unqalDP $ hasParen idnetifier - -- Parens are attachted to `lies`, so if `lies` was empty previously, - -- we need change the ann key from `[]` to `:` to keep parens and other anns. - unless hasSibling $ - transferAnn (L l' lies) (L l' [x]) id - return $ L l it {ideclHiding = Just (hide, L l' $ lies ++ [x])} + if x `elem` lies then lift (Left $ idnetifier <> " already imported") else do + when hasSibling $ + addTrailingCommaT (last lies) + addSimpleAnnT x (DP (0, if hasSibling then 1 else 0)) [] + addSimpleAnnT rdr dp00 $ unqalDP $ hasParen idnetifier + -- Parens are attachted to `lies`, so if `lies` was empty previously, + -- we need change the ann key from `[]` to `:` to keep parens and other anns. + unless hasSibling $ + transferAnn (L l' lies) (L l' [x]) id + return $ L l it {ideclHiding = Just (hide, L l' $ lies ++ [x])} extendImportTopLevel _ _ _ = lift $ Left "Unable to extend the import list" -- | Add an identifier with its parent to import list @@ -244,6 +265,13 @@ extendImportViaParent df parent child (L l it@ImportDecl {..}) do srcChild <- uniqueSrcSpanT childRdr <- liftParseAST df child + + let alreadyImported = + showNameWithoutUniques(occName (unLoc childRdr)) `elem` + map (showNameWithoutUniques @OccName) (listify (const True) lies') + when alreadyImported $ + lift (Left $ child <> " already included in " <> parent <> " imports") + when hasSibling $ addTrailingCommaT (last lies') let childLIE = L srcChild $ IEName childRdr diff --git a/ghcide/src/Development/IDE/Plugin/Completions.hs b/ghcide/src/Development/IDE/Plugin/Completions.hs index 4c146c580f..052bb58c11 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions.hs @@ -4,7 +4,6 @@ module Development.IDE.Plugin.Completions ( descriptor - , ProduceCompletions(..) , LocalCompletions(..) , NonLocalCompletions(..) ) where @@ -12,6 +11,12 @@ import Language.Haskell.LSP.Types import qualified Language.Haskell.LSP.Core as LSP import qualified Language.Haskell.LSP.VFS as VFS +import Control.Monad +import Control.Monad.Trans.Maybe +import Data.Aeson +import Data.List (find) +import Data.Maybe +import qualified Data.Text as T import Development.Shake.Classes import Development.Shake import GHC.Generics @@ -22,36 +27,33 @@ import Development.IDE.Types.Location import Development.IDE.Core.RuleTypes import Development.IDE.Core.Shake import Development.IDE.GHC.Compat - +import Development.IDE.GHC.ExactPrint (Annotated (annsA), GetAnnotatedParsedSource (GetAnnotatedParsedSource)) import Development.IDE.GHC.Util -import TcRnDriver (tcRnImportDecls) -import Data.Maybe +import Development.IDE.Plugin.CodeAction.ExactPrint +import Development.IDE.Plugin.Completions.Types import Ide.Plugin.Config (Config (completionSnippetsOn)) import Ide.PluginUtils (getClientConfig) import Ide.Types - +import TcRnDriver (tcRnImportDecls) #if defined(GHC_LIB) import Development.IDE.Import.DependencyInformation #endif descriptor :: PluginId -> PluginDescriptor IdeState descriptor plId = (defaultPluginDescriptor plId) - { pluginRules = produceCompletions - , pluginCompletionProvider = Just getCompletionsLSP - } + { pluginRules = produceCompletions, + pluginCompletionProvider = Just (getCompletionsLSP plId), + pluginCommands = [extendImportCommand] + } produceCompletions :: Rules () produceCompletions = do - define $ \ProduceCompletions file -> do - local <- useWithStale LocalCompletions file - nonLocal <- useWithStale NonLocalCompletions file - let extract = fmap fst - return ([], extract local <> extract nonLocal) define $ \LocalCompletions file -> do + let uri = fromNormalizedUri $ normalizedFilePathToUri file pm <- useWithStale GetParsedModule file case pm of Just (pm, _) -> do - let cdata = localCompletionsForParsedModule pm + let cdata = localCompletionsForParsedModule uri pm return ([], Just cdata) _ -> return ([], Nothing) define $ \NonLocalCompletions file -> do @@ -77,7 +79,8 @@ produceCompletions = do res <- liftIO $ tcRnImportDecls env (dropListFromImportDecl <$> imps) case res of (_, Just rdrEnv) -> do - cdata <- liftIO $ cacheDataProducer env (ms_mod ms) rdrEnv imps parsedDeps + let uri = fromNormalizedUri $ normalizedFilePathToUri file + cdata <- liftIO $ cacheDataProducer uri env (ms_mod ms) rdrEnv imps parsedDeps return ([], Just cdata) (_diag, _) -> return ([], Nothing) @@ -94,16 +97,9 @@ dropListFromImportDecl iDecl = let in f <$> iDecl -- | Produce completions info for a file -type instance RuleResult ProduceCompletions = CachedCompletions type instance RuleResult LocalCompletions = CachedCompletions type instance RuleResult NonLocalCompletions = CachedCompletions -data ProduceCompletions = ProduceCompletions - deriving (Eq, Show, Typeable, Generic) -instance Hashable ProduceCompletions -instance NFData ProduceCompletions -instance Binary ProduceCompletions - data LocalCompletions = LocalCompletions deriving (Eq, Show, Typeable, Generic) instance Hashable LocalCompletions @@ -115,13 +111,15 @@ data NonLocalCompletions = NonLocalCompletions instance Hashable NonLocalCompletions instance NFData NonLocalCompletions instance Binary NonLocalCompletions + -- | Generate code actions. getCompletionsLSP - :: LSP.LspFuncs Config + :: PluginId + -> LSP.LspFuncs Config -> IdeState -> CompletionParams -> IO (Either ResponseError CompletionResponseResult) -getCompletionsLSP lsp ide +getCompletionsLSP plId lsp ide CompletionParams{_textDocument=TextDocumentIdentifier uri ,_position=position ,_context=completionContext} = do @@ -131,12 +129,13 @@ getCompletionsLSP lsp ide let npath = toNormalizedFilePath' path (ideOpts, compls) <- runIdeAction "Completion" (shakeExtras ide) $ do opts <- liftIO $ getIdeOptionsIO $ shakeExtras ide - compls <- useWithStaleFast ProduceCompletions npath + localCompls <- useWithStaleFast LocalCompletions npath + nonLocalCompls <- useWithStaleFast NonLocalCompletions npath pm <- useWithStaleFast GetParsedModule npath binds <- fromMaybe (mempty, zeroMapping) <$> useWithStaleFast GetBindings npath - pure (opts, fmap (,pm,binds) compls ) + pure (opts, fmap (,pm,binds) ((fst <$> localCompls) <> (fst <$> nonLocalCompls))) case compls of - Just ((cci', _), parsedMod, bindMap) -> do + Just (cci', parsedMod, bindMap) -> do pfix <- VFS.getCompletionPrefix position cnts case (pfix, completionContext) of (Just (VFS.PosPrefixInfo _ "" _ _), Just CompletionContext { _triggerCharacter = Just "."}) @@ -145,8 +144,57 @@ getCompletionsLSP lsp ide let clientCaps = clientCapabilities $ shakeExtras ide config <- getClientConfig lsp let snippets = WithSnippets . completionSnippetsOn $ config - allCompletions <- getCompletions ideOpts cci' parsedMod bindMap pfix' clientCaps snippets + allCompletions <- getCompletions plId ideOpts cci' parsedMod bindMap pfix' clientCaps snippets pure $ Completions (List allCompletions) _ -> return (Completions $ List []) _ -> return (Completions $ List []) _ -> return (Completions $ List []) + +---------------------------------------------------------------------------------------------------- + +extendImportCommand :: PluginCommand IdeState +extendImportCommand = + PluginCommand (CommandId extendImportCommandId) "additional edits for a completion" extendImportHandler + +extendImportHandler :: CommandFunction IdeState ExtendImport +extendImportHandler _lsp ideState edit = do + res <- runMaybeT $ extendImportHandler' ideState edit + return (Right Null, res) + +extendImportHandler' :: IdeState -> ExtendImport -> MaybeT IO (ServerMethod, ApplyWorkspaceEditParams) +extendImportHandler' ideState ExtendImport {..} + | Just fp <- uriToFilePath doc, + nfp <- toNormalizedFilePath' fp = + do + (ms, ps, imps) <- MaybeT $ + runAction "extend import" ideState $ + runMaybeT $ do + -- We want accurate edits, so do not use stale data here + (ms, imps) <- MaybeT $ use GetModSummaryWithoutTimestamps nfp + ps <- MaybeT $ use GetAnnotatedParsedSource nfp + return (ms, ps, imps) + let df = ms_hspp_opts ms + wantedModule = mkModuleName (T.unpack importName) + wantedQual = mkModuleName . T.unpack <$> importQual + imp <- liftMaybe $ find (isWantedModule wantedModule wantedQual) imps + wedit <- + liftEither $ + rewriteToWEdit df doc (annsA ps) $ + extendImport (T.unpack <$> thingParent) (T.unpack newThing) imp + return (WorkspaceApplyEdit, ApplyWorkspaceEditParams wedit) + | otherwise = + mzero + +isWantedModule :: ModuleName -> Maybe ModuleName -> GenLocated l (ImportDecl pass) -> Bool +isWantedModule wantedModule Nothing (L _ it@ImportDecl{ideclName, ideclHiding = Just (False, _)}) = + not (isQualifiedImport it) && unLoc ideclName == wantedModule +isWantedModule wantedModule (Just qual) (L _ ImportDecl{ideclAs, ideclName, ideclHiding = Just (False, _)}) = + unLoc ideclName == wantedModule && (wantedModule == qual || (unLoc <$> ideclAs) == Just qual) +isWantedModule _ _ _ = False + +liftMaybe :: Monad m => Maybe a -> MaybeT m a +liftMaybe a = MaybeT $ pure a + +liftEither :: Monad m => Either e a -> MaybeT m a +liftEither (Left _) = mzero +liftEither (Right x) = return x diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs index 97ab78896e..7591903d03 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE CPP #-} {-# LANGUAGE GADTs#-} @@ -13,12 +14,12 @@ module Development.IDE.Plugin.Completions.Logic ( ) where import Control.Applicative -import Data.Char (isAlphaNum, isUpper) +import Data.Char (isUpper) import Data.Generics import Data.List.Extra as List hiding (stripPrefix) import qualified Data.Map as Map -import Data.Maybe (listToMaybe, fromMaybe, mapMaybe) +import Data.Maybe (fromMaybe, isJust, listToMaybe, mapMaybe) import qualified Data.Text as T import qualified Text.Fuzzy as Fuzzy @@ -53,7 +54,11 @@ import GhcPlugins ( flLabel, unpackFS) import Data.Either (fromRight) -import Ide.Types(WithSnippets(..)) +import Data.Aeson (ToJSON (toJSON)) +import Data.Functor +import Ide.PluginUtils (mkLspCommand) +import Ide.Types (CommandId (..), PluginId, WithSnippets (..)) +import Control.Monad -- From haskell-ide-engine/hie-plugin-api/Haskell/Ide/Engine/Context.hs @@ -153,9 +158,23 @@ showModName = T.pack . moduleNameString -- Nothing Nothing Nothing Nothing (Just insertText) (Just Snippet) -- Nothing Nothing Nothing Nothing Nothing -mkCompl :: IdeOptions -> CompItem -> CompletionItem -mkCompl IdeOptions{..} CI{compKind,insertText, importedFrom,typeText,label,docs, additionalTextEdits} = - CompletionItem {_label = label, +mkCompl :: PluginId -> IdeOptions -> CompItem -> IO CompletionItem +mkCompl + pId + IdeOptions {..} + CI + { compKind, + isInfix, + insertText, + importedFrom, + typeText, + label, + docs, + additionalTextEdits + } = do + mbCommand <- mkAdditionalEditsCommand pId `traverse` additionalTextEdits + let ci = CompletionItem + {_label = label, _kind = kind, _tags = Nothing, _detail = (colon <>) <$> typeText, @@ -167,10 +186,11 @@ mkCompl IdeOptions{..} CI{compKind,insertText, importedFrom,typeText,label,docs, _insertText = Just insertText, _insertTextFormat = Just Snippet, _textEdit = Nothing, - _additionalTextEdits = List <$> additionalTextEdits, + _additionalTextEdits = Nothing, _commitCharacters = Nothing, - _command = Nothing, + _command = mbCommand, _xdata = Nothing} + return $ removeSnippetsWhen (isJust isInfix) ci where kind = Just compKind docs' = imported : spanDocToMarkdown docs @@ -182,8 +202,12 @@ mkCompl IdeOptions{..} CI{compKind,insertText, importedFrom,typeText,label,docs, MarkupContent MkMarkdown $ T.intercalate sectionSeparator docs' -mkNameCompItem :: Name -> ModuleName -> Maybe Type -> Maybe Backtick -> SpanDoc -> Maybe (LImportDecl GhcPs) -> CompItem -mkNameCompItem origName origMod thingType isInfix docs !imp = CI{..} +mkAdditionalEditsCommand :: PluginId -> ExtendImport -> IO Command +mkAdditionalEditsCommand pId edits = + mkLspCommand pId (CommandId extendImportCommandId) "extend import" (Just [toJSON edits]) + +mkNameCompItem :: Uri -> Maybe T.Text -> Name -> ModuleName -> Maybe Type -> Maybe Backtick -> SpanDoc -> Maybe (LImportDecl GhcPs) -> CompItem +mkNameCompItem doc thingParent origName origMod thingType isInfix docs !imp = CI {..} where compKind = occNameToComKind typeText $ occName origName importedFrom = Right $ showModName origMod @@ -199,7 +223,15 @@ mkNameCompItem origName origMod thingType isInfix docs !imp = CI{..} typeText | Just t <- thingType = Just . stripForall $ showGhc t | otherwise = Nothing - additionalTextEdits = imp >>= extendImportList (showGhc origName) + additionalTextEdits = + imp <&> \x -> + ExtendImport + { doc, + thingParent, + importName = showModName $ unLoc $ ideclName $ unLoc x, + importQual = getImportQual x, + newThing = showNameWithoutUniques origName + } stripForall :: T.Text -> T.Text stripForall t @@ -261,33 +293,13 @@ mkPragmaCompl label insertText = Nothing Nothing Nothing Nothing Nothing (Just insertText) (Just Snippet) Nothing Nothing Nothing Nothing Nothing -extendImportList :: T.Text -> LImportDecl GhcPs -> Maybe [TextEdit] -extendImportList name lDecl = let - f (Just range) ImportDecl {ideclHiding} = case ideclHiding of - Just (False, x) - | Set.notMember name (Set.fromList [T.pack (show y) | y <- unLoc x]) - -> let - start_pos = _end range - new_start_pos = start_pos {_character = _character start_pos - 1} - -- use to same start_pos to handle situation where we do not have latest edits due to caching of Rules - new_range = Range new_start_pos new_start_pos - -- we cannot wrap mapM_ inside (mapM_) but we need to wrap (<$) - alpha = T.all isAlphaNum $ T.filter (\c -> c /= '_') name - result = if alpha then name <> ", " - else "(" <> name <> "), " - in Just [TextEdit new_range result] - | otherwise -> Nothing - _ -> Nothing -- hiding import list and no list - f _ _ = Nothing - src_span = srcSpanToRange . getLoc $ lDecl - in f src_span . unLoc $ lDecl - - -cacheDataProducer :: HscEnv -> Module -> GlobalRdrEnv -> [LImportDecl GhcPs] -> [ParsedModule] -> IO CachedCompletions -cacheDataProducer packageState curMod rdrEnv limports deps = do +cacheDataProducer :: Uri -> HscEnv -> Module -> GlobalRdrEnv -> [LImportDecl GhcPs] -> [ParsedModule] -> IO CachedCompletions +cacheDataProducer uri packageState curMod rdrEnv limports deps = do let dflags = hsc_dflags packageState curModName = moduleName curMod + importMap = Map.fromList [ (getLoc imp, imp) | imp <- limports ] + iDeclToModName :: ImportDecl name -> ModuleName iDeclToModName = unLoc . ideclName @@ -312,11 +324,12 @@ cacheDataProducer packageState curMod rdrEnv limports deps = do getCompls = foldMapM getComplsForOne getComplsForOne :: GlobalRdrElt -> IO ([CompItem],QualCompls) - getComplsForOne (GRE n _ True _) = - (, mempty) <$> toCompItem curMod curModName n Nothing - getComplsForOne (GRE n _ False prov) = + getComplsForOne (GRE n par True _) = + (, mempty) <$> toCompItem par curMod curModName n Nothing + getComplsForOne (GRE n par False prov) = flip foldMapM (map is_decl prov) $ \spec -> do - compItem <- toCompItem curMod (is_mod spec) n Nothing + let originalImportDecl = Map.lookup (is_dloc spec) importMap + compItem <- toCompItem par curMod (is_mod spec) n originalImportDecl let unqual | is_qual spec = [] | otherwise = compItem @@ -327,25 +340,27 @@ cacheDataProducer packageState curMod rdrEnv limports deps = do origMod = showModName (is_mod spec) return (unqual,QualCompls qual) - toCompItem :: Module -> ModuleName -> Name -> Maybe (LImportDecl GhcPs) -> IO [CompItem] - toCompItem m mn n imp' = do + toCompItem :: Parent -> Module -> ModuleName -> Name -> Maybe (LImportDecl GhcPs) -> IO [CompItem] + toCompItem par m mn n imp' = do docs <- getDocumentationTryGhc packageState curMod deps n - ty <- catchSrcErrors (hsc_dflags packageState) "completion" $ do - name' <- lookupName packageState m n - return $ name' >>= safeTyThingType - -- use the same pass to also capture any Record snippets that we can collect - record_ty <- catchSrcErrors (hsc_dflags packageState) "record-completion" $ do + let mbParent = case par of + NoParent -> Nothing + ParentIs n -> Just (showNameWithoutUniques n) + FldParent n _ -> Just (showNameWithoutUniques n) + tys <- catchSrcErrors (hsc_dflags packageState) "completion" $ do name' <- lookupName packageState m n - return $ name' >>= safeTyThingForRecord + return ( name' >>= safeTyThingType + , guard (isJust mbParent) >> name' >>= safeTyThingForRecord + ) + let (ty, record_ty) = fromRight (Nothing, Nothing) tys - let recordCompls = case fromRight Nothing record_ty of - Just (ctxStr, flds) -> case flds of - [] -> [] - _ -> [mkRecordSnippetCompItem ctxStr flds (ppr mn) docs imp'] - Nothing -> [] + let recordCompls = case record_ty of + Just (ctxStr, flds) | not (null flds) -> + [mkRecordSnippetCompItem uri mbParent ctxStr flds (ppr mn) docs imp'] + _ -> [] - return $ mkNameCompItem n mn (fromRight Nothing ty) Nothing docs imp' - : recordCompls + return $ mkNameCompItem uri mbParent n mn ty Nothing docs imp' + : recordCompls (unquals,quals) <- getCompls rdrElts @@ -358,8 +373,8 @@ cacheDataProducer packageState curMod rdrEnv limports deps = do -- | Produces completions from the top level declarations of a module. -localCompletionsForParsedModule :: ParsedModule -> CachedCompletions -localCompletionsForParsedModule pm@ParsedModule{pm_parsed_source = L _ HsModule{hsmodDecls, hsmodName}} = +localCompletionsForParsedModule :: Uri -> ParsedModule -> CachedCompletions +localCompletionsForParsedModule uri pm@ParsedModule{pm_parsed_source = L _ HsModule{hsmodDecls, hsmodName}} = CC { allModNamesAsNS = mempty , unqualCompls = compls , qualCompls = mempty @@ -394,7 +409,7 @@ localCompletionsForParsedModule pm@ParsedModule{pm_parsed_source = L _ HsModule{ | id <- listify (\(_ :: Located(IdP GhcPs)) -> True) x , let cl = occNameToComKind Nothing (rdrNameOcc $ unLoc id)] -- here we only have to look at the outermost type - recordCompls = findRecordCompl pm thisModName x + recordCompls = findRecordCompl uri pm thisModName x in -- the constructors and snippets will be duplicated here giving the user 2 choices. generalCompls ++ recordCompls @@ -414,10 +429,11 @@ localCompletionsForParsedModule pm@ParsedModule{pm_parsed_source = L _ HsModule{ thisModName = ppr hsmodName -findRecordCompl :: ParsedModule -> T.Text -> TyClDecl GhcPs -> [CompItem] -findRecordCompl pmod mn DataDecl {tcdLName, tcdDataDefn} = result +findRecordCompl :: Uri -> ParsedModule -> T.Text -> TyClDecl GhcPs -> [CompItem] +findRecordCompl uri pmod mn DataDecl {tcdLName, tcdDataDefn} = result where - result = [mkRecordSnippetCompItem (showGhc . unLoc $ con_name) field_labels mn doc Nothing + result = [mkRecordSnippetCompItem uri (Just $ showNameWithoutUniques $ unLoc tcdLName) + (showGhc . unLoc $ con_name) field_labels mn doc Nothing | ConDeclH98{..} <- unLoc <$> dd_cons tcdDataDefn , Just con_details <- [getFlds con_args] , let field_names = mapMaybe extract con_details @@ -438,24 +454,32 @@ findRecordCompl pmod mn DataDecl {tcdLName, tcdDataDefn} = result | otherwise = Nothing -- XConDeclField extract _ = Nothing -findRecordCompl _ _ _ = [] +findRecordCompl _ _ _ _ = [] ppr :: Outputable a => a -> T.Text ppr = T.pack . prettyPrint toggleSnippets :: ClientCapabilities -> WithSnippets -> CompletionItem -> CompletionItem -toggleSnippets ClientCapabilities { _textDocument } (WithSnippets with) x - | with && supported = x - | otherwise = x { _insertTextFormat = Just PlainText - , _insertText = Nothing - } +toggleSnippets ClientCapabilities {_textDocument} (WithSnippets with) = + removeSnippetsWhen (not $ with && supported) where supported = Just True == (_textDocument >>= _completion >>= _completionItem >>= _snippetSupport) +removeSnippetsWhen :: Bool -> CompletionItem -> CompletionItem +removeSnippetsWhen condition x = + if condition + then + x + { _insertTextFormat = Just PlainText, + _insertText = Nothing + } + else x + -- | Returns the cached completions for the given module and position. getCompletions - :: IdeOptions + :: PluginId + -> IdeOptions -> CachedCompletions -> Maybe (ParsedModule, PositionMapping) -> (Bindings, PositionMapping) @@ -463,7 +487,7 @@ getCompletions -> ClientCapabilities -> WithSnippets -> IO [CompletionItem] -getCompletions ideOpts CC { allModNamesAsNS, unqualCompls, qualCompls, importableModules} +getCompletions plId ideOpts CC {allModNamesAsNS, unqualCompls, qualCompls, importableModules} maybe_parsed (localBindings, bmapping) prefixInfo caps withSnippets = do let VFS.PosPrefixInfo { fullLine, prefixModule, prefixText } = prefixInfo enteredQual = if T.null prefixModule then "" else prefixModule <> "." @@ -550,25 +574,23 @@ getCompletions ideOpts CC { allModNamesAsNS, unqualCompls, qualCompls, importabl | s == c = ss | otherwise = s:ss - result - | "import " `T.isPrefixOf` fullLine - = filtImportCompls - -- we leave this condition here to avoid duplications and return empty list - -- since HLS implements this completion (#haskell-language-server/pull/662) - | "{-# language" `T.isPrefixOf` T.toLower fullLine - = [] - | "{-# options_ghc" `T.isPrefixOf` T.toLower fullLine - = filtOptsCompls (map (T.pack . stripLeading '-') $ flagsForCompletion False) - | "{-# " `T.isPrefixOf` fullLine - = filtPragmaCompls (pragmaSuffix fullLine) - | otherwise - = let uniqueFiltCompls = nubOrdOn insertText filtCompls - in filtModNameCompls - ++ filtKeywordCompls - ++ map ( toggleSnippets caps withSnippets - . mkCompl ideOpts . stripAutoGenerated - ) uniqueFiltCompls - return result + if + | "import " `T.isPrefixOf` fullLine + -> return filtImportCompls + -- we leave this condition here to avoid duplications and return empty list + -- since HLS implements this completion (#haskell-language-server/pull/662) + | "{-# language" `T.isPrefixOf` T.toLower fullLine + -> return [] + | "{-# options_ghc" `T.isPrefixOf` T.toLower fullLine + -> return $ filtOptsCompls (map (T.pack . stripLeading '-') $ flagsForCompletion False) + | "{-# " `T.isPrefixOf` fullLine + -> return $ filtPragmaCompls (pragmaSuffix fullLine) + | otherwise -> do + let uniqueFiltCompls = nubOrdOn insertText filtCompls + compls <- mapM (mkCompl plId ideOpts . stripAutoGenerated) uniqueFiltCompls + return $ filtModNameCompls + ++ filtKeywordCompls + ++ map ( toggleSnippets caps withSnippets) compls -- --------------------------------------------------------------------- @@ -615,7 +637,7 @@ isUsedAsInfix line prefixMod prefixText pos openingBacktick :: T.Text -> T.Text -> T.Text -> Position -> Bool openingBacktick line prefixModule prefixText Position { _character } - | backtickIndex < 0 = False + | backtickIndex < 0 || backtickIndex > T.length line = False | otherwise = (line `T.index` backtickIndex) == '`' where backtickIndex :: Int @@ -704,8 +726,8 @@ safeTyThingForRecord (AConLike dc) = Just (ctxStr, field_names) safeTyThingForRecord _ = Nothing -mkRecordSnippetCompItem :: T.Text -> [T.Text] -> T.Text -> SpanDoc -> Maybe (LImportDecl GhcPs) -> CompItem -mkRecordSnippetCompItem ctxStr compl mn docs imp = r +mkRecordSnippetCompItem :: Uri -> Maybe T.Text -> T.Text -> [T.Text] -> T.Text -> SpanDoc -> Maybe (LImportDecl GhcPs) -> CompItem +mkRecordSnippetCompItem uri parent ctxStr compl mn docs imp = r where r = CI { compKind = CiSnippet @@ -716,7 +738,14 @@ mkRecordSnippetCompItem ctxStr compl mn docs imp = r , isInfix = Nothing , docs = docs , isTypeCompl = False - , additionalTextEdits = imp >>= extendImportList ctxStr + , additionalTextEdits = imp <&> \x -> + ExtendImport + { doc = uri, + thingParent = parent, + importName = showModName $ unLoc $ ideclName $ unLoc x, + importQual = getImportQual x, + newThing = ctxStr + } } placeholder_pairs = zip compl ([1..]::[Int]) @@ -724,3 +753,8 @@ mkRecordSnippetCompItem ctxStr compl mn docs imp = r snippet = T.intercalate (T.pack ", ") snippet_parts buildSnippet = ctxStr <> " {" <> snippet <> "}" importedFrom = Right mn + +getImportQual :: LImportDecl GhcPs -> Maybe T.Text +getImportQual (L _ imp) + | isQualifiedImport imp = Just $ T.pack $ moduleNameString $ maybe (unLoc $ ideclName imp) unLoc (ideclAs imp) + | otherwise = Nothing diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Types.hs b/ghcide/src/Development/IDE/Plugin/Completions/Types.hs index c928b54338..528ab1baf2 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Types.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Types.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} module Development.IDE.Plugin.Completions.Types ( module Development.IDE.Plugin.Completions.Types ) where @@ -8,13 +10,27 @@ import qualified Data.Text as T import SrcLoc import Development.IDE.Spans.Common -import Language.Haskell.LSP.Types (TextEdit, CompletionItemKind) - --- From haskell-ide-engine/src/Haskell/Ide/Engine/LSP/Completions.hs +import Data.Aeson (FromJSON, ToJSON) +import Data.Text (Text) +import GHC.Generics (Generic) +import Language.Haskell.LSP.Types (CompletionItemKind, Uri) data Backtick = Surrounded | LeftSide deriving (Eq, Ord, Show) +extendImportCommandId :: Text +extendImportCommandId = "extendImport" + +data ExtendImport = ExtendImport + { doc :: !Uri, + newThing :: !T.Text, + thingParent :: !(Maybe T.Text), + importName :: !T.Text, + importQual :: !(Maybe T.Text) + } + deriving (Eq, Show, Generic) + deriving anyclass (FromJSON, ToJSON) + data CompItem = CI { compKind :: CompletionItemKind , insertText :: T.Text -- ^ Snippet for the completion @@ -25,7 +41,7 @@ data CompItem = CI -- in the context of an infix notation. , docs :: SpanDoc -- ^ Available documentation. , isTypeCompl :: Bool - , additionalTextEdits :: Maybe [TextEdit] + , additionalTextEdits :: Maybe ExtendImport } deriving (Eq, Show) diff --git a/ghcide/test/exe/Main.hs b/ghcide/test/exe/Main.hs index 6d6b9538db..d856ec2c5c 100644 --- a/ghcide/test/exe/Main.hs +++ b/ghcide/test/exe/Main.hs @@ -30,6 +30,7 @@ import Development.IDE.Core.Shake (Q(..)) import Development.IDE.GHC.Util import qualified Data.Text as T import Data.Typeable +import Development.IDE.Plugin.Completions.Types (extendImportCommandId) import Development.IDE.Plugin.TypeLenses (typeLensCommandId) import Development.IDE.Spans.Common import Development.IDE.Test @@ -42,7 +43,7 @@ import Development.IDE.Test flushMessages, standardizeQuotes, waitForAction, - Cursor ) + Cursor, expectMessages ) import Development.IDE.Test.Runfiles import qualified Development.IDE.Types.Diagnostics as Diagnostics import Development.IDE.Types.Location @@ -156,7 +157,7 @@ initializeResponseTests = withResource acquire release tests where , chk "NO doc link" _documentLinkProvider Nothing , chk "NO color" _colorProvider (Just $ ColorOptionsStatic False) , chk "NO folding range" _foldingRangeProvider (Just $ FoldingRangeOptionsStatic False) - , che " execute command" _executeCommandProvider [blockCommandId, typeLensCommandId] + , che " execute command" _executeCommandProvider [blockCommandId, extendImportCommandId, typeLensCommandId] , chk " workspace" _workspace (Just $ WorkspaceOptions (Just WorkspaceFolderOptions{_supported = Just True, _changeNotifications = Just ( WorkspaceFolderChangeNotificationsBool True )})) , chk "NO experimental" _experimental Nothing ] where @@ -3409,6 +3410,35 @@ completionTest name src pos expected = testSessionWait name $ do when expectedDocs $ assertBool ("Missing docs: " <> T.unpack _label) (isJust _documentation) +completionCommandTest :: + String -> + [T.Text] -> + Position -> + T.Text -> + [T.Text] -> + TestTree +completionCommandTest name src pos wanted expected = testSession name $ do + docId <- createDoc "A.hs" "haskell" (T.unlines src) + _ <- waitForDiagnostics + compls <- getCompletions docId pos + let wantedC = find ( \case + CompletionItem {_insertText = Just x} -> wanted `T.isPrefixOf` x + _ -> False + ) compls + case wantedC of + Nothing -> + liftIO $ assertFailure $ "Cannot find expected completion in: " <> show [_label | CompletionItem {_label} <- compls] + Just CompletionItem {..} -> do + c <- assertJust "Expected a command" _command + executeCommand c + if src /= expected + then do + modifiedCode <- getDocumentEdit docId + liftIO $ modifiedCode @?= T.unlines expected + else do + expectMessages @ApplyWorkspaceEditRequest 1 $ \edit -> + liftIO $ assertFailure $ "Expected no edit but got: " <> show edit + topLevelCompletionTests :: [TestTree] topLevelCompletionTests = [ completionTest @@ -3557,46 +3587,104 @@ nonLocalCompletionTests = ] (Position 3 6) [], - expectFailBecause "Auto import completion snippets were disabled in v0.6.0.2" $ - testGroup "auto import snippets" - [ completionTest + testGroup "auto import snippets" + [ completionCommandTest "show imports not in list - simple" ["{-# LANGUAGE NoImplicitPrelude #-}", "module A where", "import Control.Monad (msum)", "f = joi"] (Position 3 6) - [("join", CiFunction, "join ${1:m (m a)}", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 2, _character = 26}, _end = Position {_line = 2, _character = 26}}, _newText = "join, "}]))] - , completionTest + "join" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad (msum, join)", "f = joi"] + , completionCommandTest "show imports not in list - multi-line" ["{-# LANGUAGE NoImplicitPrelude #-}", "module A where", "import Control.Monad (\n msum)", "f = joi"] (Position 4 6) - [("join", CiFunction, "join ${1:m (m a)}", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 3, _character = 8}, _end = Position {_line = 3, _character = 8}}, _newText = "join, "}]))] - , completionTest + "join" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad (\n msum, join)", "f = joi"] + , completionCommandTest "show imports not in list - names with _" ["{-# LANGUAGE NoImplicitPrelude #-}", - "module A where", "import qualified Control.Monad as M (msum)", "f = M.mapM_"] + "module A where", "import Control.Monad as M (msum)", "f = M.mapM_"] (Position 3 11) - [("mapM_", CiFunction, "mapM_ ${1:a -> m b} ${2:t a}", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 2, _character = 41}, _end = Position {_line = 2, _character = 41}}, _newText = "mapM_, "}]))] - , completionTest + "mapM_" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad as M (msum, mapM_)", "f = M.mapM_"] + , completionCommandTest "show imports not in list - initial empty list" ["{-# LANGUAGE NoImplicitPrelude #-}", - "module A where", "import qualified Control.Monad as M ()", "f = M.joi"] + "module A where", "import Control.Monad as M ()", "f = M.joi"] (Position 3 10) - [("join", CiFunction, "join ${1:m (m a)}", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 2, _character = 37}, _end = Position {_line = 2, _character = 37}}, _newText = "join, "}]))] - , completionTest - "record snippet on import" - ["module A where", "import Text.Printf (FormatParse(FormatParse))", "FormatParse"] - (Position 2 10) - [("FormatParse", CiStruct, "FormatParse ", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 1, _character = 44}, _end = Position {_line = 1, _character = 44}}, _newText = "FormatParse, "}])), - ("FormatParse", CiConstructor, "FormatParse ${1:String} ${2:Char} ${3:String}", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 1, _character = 44}, _end = Position {_line = 1, _character = 44}}, _newText = "FormatParse, "}])), - ("FormatParse", CiSnippet, "FormatParse {fpModifiers=${1:_fpModifiers}, fpChar=${2:_fpChar}, fpRest=${3:_fpRest}}", False, False, - Just (List [TextEdit {_range = Range {_start = Position {_line = 1, _character = 44}, _end = Position {_line = 1, _character = 44}}, _newText = "FormatParse, "}])) + "join" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad as M (join)", "f = M.joi"] + , testGroup "qualified imports" + [ completionCommandTest + "single" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad ()", "f = Control.Monad.joi"] + (Position 3 22) + "join" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad (join)", "f = Control.Monad.joi"] + , completionCommandTest + "as" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad as M ()", "f = M.joi"] + (Position 3 10) + "join" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad as M (join)", "f = M.joi"] + , completionCommandTest + "multiple" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad as M ()", "import Control.Monad as N ()", "f = N.joi"] + (Position 4 10) + "join" + ["{-# LANGUAGE NoImplicitPrelude #-}", + "module A where", "import Control.Monad as M ()", "import Control.Monad as N (join)", "f = N.joi"] + ] + , testGroup "Data constructor" + [ completionCommandTest + "not imported" + ["module A where", "import Text.Printf ()", "ZeroPad"] + (Position 2 4) + "ZeroPad" + ["module A where", "import Text.Printf (FormatAdjustment (ZeroPad))", "ZeroPad"] + , completionCommandTest + "parent imported" + ["module A where", "import Text.Printf (FormatAdjustment)", "ZeroPad"] + (Position 2 4) + "ZeroPad" + ["module A where", "import Text.Printf (FormatAdjustment (ZeroPad))", "ZeroPad"] + , completionCommandTest + "already imported" + ["module A where", "import Text.Printf (FormatAdjustment (ZeroPad))", "ZeroPad"] + (Position 2 4) + "ZeroPad" + ["module A where", "import Text.Printf (FormatAdjustment (ZeroPad))", "ZeroPad"] + ] + , testGroup "Record completion" + [ completionCommandTest + "not imported" + ["module A where", "import Text.Printf ()", "FormatParse"] + (Position 2 10) + "FormatParse {" + ["module A where", "import Text.Printf (FormatParse (FormatParse))", "FormatParse"] + , completionCommandTest + "parent imported" + ["module A where", "import Text.Printf (FormatParse)", "FormatParse"] + (Position 2 10) + "FormatParse {" + ["module A where", "import Text.Printf (FormatParse (FormatParse))", "FormatParse"] + , completionCommandTest + "already imported" + ["module A where", "import Text.Printf (FormatParse (FormatParse))", "FormatParse"] + (Position 2 10) + "FormatParse {" + ["module A where", "import Text.Printf (FormatParse (FormatParse))", "FormatParse"] ] ], -- we need this test to make sure the ghcide completions module does not return completions for language pragmas. this functionality is turned on in hls diff --git a/ghcide/test/src/Development/IDE/Test.hs b/ghcide/test/src/Development/IDE/Test.hs index 7c4d446572..b473105543 100644 --- a/ghcide/test/src/Development/IDE/Test.hs +++ b/ghcide/test/src/Development/IDE/Test.hs @@ -11,6 +11,7 @@ module Development.IDE.Test , expectDiagnostics , expectDiagnosticsWithTags , expectNoMoreDiagnostics + , expectMessages , expectCurrentDiagnostics , checkDiagnosticsForDoc , canonicalizeUri @@ -35,6 +36,8 @@ import Test.Tasty.HUnit import System.Directory (canonicalizePath) import Data.Maybe (fromJust) import Development.IDE.Plugin.Test (WaitForIdeRuleResult, TestRequest(WaitForIdeRule)) +import Data.Aeson (FromJSON) +import Data.Typeable (Typeable) -- | (0-based line number, 0-based column number) @@ -66,7 +69,18 @@ requireDiagnostic actuals expected@(severity, cursor, expectedMsg, expectedTag) -- |wait for @timeout@ seconds and report an assertion failure -- if any diagnostic messages arrive in that period expectNoMoreDiagnostics :: Seconds -> Session () -expectNoMoreDiagnostics timeout = do +expectNoMoreDiagnostics timeout = + expectMessages @PublishDiagnosticsNotification timeout $ \diagsNot -> do + let fileUri = diagsNot ^. params . uri + actual = diagsNot ^. params . diagnostics + liftIO $ + assertFailure $ + "Got unexpected diagnostics for " <> show fileUri + <> " got " + <> show actual + +expectMessages :: (FromJSON msg, Typeable msg) => Seconds -> (msg -> Session ()) -> Session () +expectMessages timeout handle = do -- Give any further diagnostic messages time to arrive. liftIO $ sleep timeout -- Send a dummy message to provoke a response from the server. @@ -75,14 +89,7 @@ expectNoMoreDiagnostics timeout = do void $ sendRequest (CustomClientMethod "non-existent-method") () handleMessages where - handleMessages = handleDiagnostic <|> handleCustomMethodResponse <|> ignoreOthers - handleDiagnostic = do - diagsNot <- LspTest.message :: Session PublishDiagnosticsNotification - let fileUri = diagsNot ^. params . uri - actual = diagsNot ^. params . diagnostics - liftIO $ assertFailure $ - "Got unexpected diagnostics for " <> show fileUri <> - " got " <> show actual + handleMessages = (LspTest.message >>= handle) <|> handleCustomMethodResponse <|> ignoreOthers ignoreOthers = void anyMessage >> handleMessages handleCustomMethodResponse :: Session () diff --git a/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs b/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs index 4bc87b47d2..41a733a5ad 100644 --- a/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs +++ b/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs @@ -248,15 +248,6 @@ runIde state = runAction "importLens" state -------------------------------------------------------------------------------- -isQualifiedImport :: ImportDecl a -> Bool -#if MIN_GHC_API_VERSION(8,10,0) -isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False -isQualifiedImport ImportDecl{} = True -#else -isQualifiedImport ImportDecl{ideclQualified} = ideclQualified -#endif -isQualifiedImport _ = False - within :: Range -> SrcSpan -> Bool within (Range start end) span = isInsideSrcSpan start span || isInsideSrcSpan end span diff --git a/test/functional/Completion.hs b/test/functional/Completion.hs index 641b38bbc5..bd8ed721f4 100644 --- a/test/functional/Completion.hs +++ b/test/functional/Completion.hs @@ -286,8 +286,8 @@ snippetTests = testGroup "snippets" [ liftIO $ do item ^. label @?= "filter" item ^. kind @?= Just CiFunction - item ^. insertTextFormat @?= Just Snippet - item ^. insertText @?= Just "filter ${1:a -> Bool} ${2:[a]}" + item ^. insertTextFormat @?= Just PlainText + item ^. insertText @?= Nothing , testCase "work for infix functions in backticks" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do doc <- openDoc "Completion.hs" "haskell" @@ -300,8 +300,8 @@ snippetTests = testGroup "snippets" [ liftIO $ do item ^. label @?= "filter" item ^. kind @?= Just CiFunction - item ^. insertTextFormat @?= Just Snippet - item ^. insertText @?= Just "filter ${1:a -> Bool} ${2:[a]}" + item ^. insertTextFormat @?= Just PlainText + item ^. insertText @?= Nothing , testCase "work for qualified infix functions" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do doc <- openDoc "Completion.hs" "haskell" @@ -314,8 +314,8 @@ snippetTests = testGroup "snippets" [ liftIO $ do item ^. label @?= "intersperse" item ^. kind @?= Just CiFunction - item ^. insertTextFormat @?= Just Snippet - item ^. insertText @?= Just "intersperse ${1:a} ${2:[a]}" + item ^. insertTextFormat @?= Just PlainText + item ^. insertText @?= Nothing , testCase "work for qualified infix functions in backticks" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do doc <- openDoc "Completion.hs" "haskell" @@ -328,8 +328,8 @@ snippetTests = testGroup "snippets" [ liftIO $ do item ^. label @?= "intersperse" item ^. kind @?= Just CiFunction - item ^. insertTextFormat @?= Just Snippet - item ^. insertText @?= Just "intersperse ${1:a} ${2:[a]}" + item ^. insertTextFormat @?= Just PlainText + item ^. insertText @?= Nothing , testCase "respects lsp configuration" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do doc <- openDoc "Completion.hs" "haskell"