44
55module Development.IDE.Plugin.Completions
66 ( descriptor
7- , ProduceCompletions (.. )
87 , LocalCompletions (.. )
98 , NonLocalCompletions (.. )
109 ) where
1110import Language.Haskell.LSP.Types
1211import qualified Language.Haskell.LSP.Core as LSP
1312import qualified Language.Haskell.LSP.VFS as VFS
1413
14+ import Control.Monad
15+ import Control.Monad.Trans.Maybe
16+ import Data.Aeson
17+ import Data.List (find )
18+ import Data.Maybe
19+ import qualified Data.Text as T
1520import Development.Shake.Classes
1621import Development.Shake
1722import GHC.Generics
@@ -22,36 +27,33 @@ import Development.IDE.Types.Location
2227import Development.IDE.Core.RuleTypes
2328import Development.IDE.Core.Shake
2429import Development.IDE.GHC.Compat
25-
30+ import Development.IDE.GHC.ExactPrint ( Annotated ( annsA ), GetAnnotatedParsedSource ( GetAnnotatedParsedSource ))
2631import Development.IDE.GHC.Util
27- import TcRnDriver ( tcRnImportDecls )
28- import Data.Maybe
32+ import Development.IDE.Plugin.CodeAction.ExactPrint
33+ import Development.IDE.Plugin.Completions.Types
2934import Ide.Plugin.Config (Config (completionSnippetsOn ))
3035import Ide.PluginUtils (getClientConfig )
3136import Ide.Types
32-
37+ import TcRnDriver ( tcRnImportDecls )
3338#if defined(GHC_LIB)
3439import Development.IDE.Import.DependencyInformation
3540#endif
3641
3742descriptor :: PluginId -> PluginDescriptor IdeState
3843descriptor plId = (defaultPluginDescriptor plId)
39- { pluginRules = produceCompletions
40- , pluginCompletionProvider = Just getCompletionsLSP
41- }
44+ { pluginRules = produceCompletions,
45+ pluginCompletionProvider = Just (getCompletionsLSP plId),
46+ pluginCommands = [extendImportCommand]
47+ }
4248
4349produceCompletions :: Rules ()
4450produceCompletions = do
45- define $ \ ProduceCompletions file -> do
46- local <- useWithStale LocalCompletions file
47- nonLocal <- useWithStale NonLocalCompletions file
48- let extract = fmap fst
49- return ([] , extract local <> extract nonLocal)
5051 define $ \ LocalCompletions file -> do
52+ let uri = fromNormalizedUri $ normalizedFilePathToUri file
5153 pm <- useWithStale GetParsedModule file
5254 case pm of
5355 Just (pm, _) -> do
54- let cdata = localCompletionsForParsedModule pm
56+ let cdata = localCompletionsForParsedModule uri pm
5557 return ([] , Just cdata)
5658 _ -> return ([] , Nothing )
5759 define $ \ NonLocalCompletions file -> do
@@ -77,7 +79,8 @@ produceCompletions = do
7779 res <- liftIO $ tcRnImportDecls env (dropListFromImportDecl <$> imps)
7880 case res of
7981 (_, Just rdrEnv) -> do
80- cdata <- liftIO $ cacheDataProducer env (ms_mod ms) rdrEnv imps parsedDeps
82+ let uri = fromNormalizedUri $ normalizedFilePathToUri file
83+ cdata <- liftIO $ cacheDataProducer uri env (ms_mod ms) rdrEnv imps parsedDeps
8184 return ([] , Just cdata)
8285 (_diag, _) ->
8386 return ([] , Nothing )
@@ -94,16 +97,9 @@ dropListFromImportDecl iDecl = let
9497 in f <$> iDecl
9598
9699-- | Produce completions info for a file
97- type instance RuleResult ProduceCompletions = CachedCompletions
98100type instance RuleResult LocalCompletions = CachedCompletions
99101type instance RuleResult NonLocalCompletions = CachedCompletions
100102
101- data ProduceCompletions = ProduceCompletions
102- deriving (Eq , Show , Typeable , Generic )
103- instance Hashable ProduceCompletions
104- instance NFData ProduceCompletions
105- instance Binary ProduceCompletions
106-
107103data LocalCompletions = LocalCompletions
108104 deriving (Eq , Show , Typeable , Generic )
109105instance Hashable LocalCompletions
@@ -115,13 +111,15 @@ data NonLocalCompletions = NonLocalCompletions
115111instance Hashable NonLocalCompletions
116112instance NFData NonLocalCompletions
117113instance Binary NonLocalCompletions
114+
118115-- | Generate code actions.
119116getCompletionsLSP
120- :: LSP. LspFuncs Config
117+ :: PluginId
118+ -> LSP. LspFuncs Config
121119 -> IdeState
122120 -> CompletionParams
123121 -> IO (Either ResponseError CompletionResponseResult )
124- getCompletionsLSP lsp ide
122+ getCompletionsLSP plId lsp ide
125123 CompletionParams {_textDocument= TextDocumentIdentifier uri
126124 ,_position= position
127125 ,_context= completionContext} = do
@@ -131,12 +129,13 @@ getCompletionsLSP lsp ide
131129 let npath = toNormalizedFilePath' path
132130 (ideOpts, compls) <- runIdeAction " Completion" (shakeExtras ide) $ do
133131 opts <- liftIO $ getIdeOptionsIO $ shakeExtras ide
134- compls <- useWithStaleFast ProduceCompletions npath
132+ localCompls <- useWithStaleFast LocalCompletions npath
133+ nonLocalCompls <- useWithStaleFast NonLocalCompletions npath
135134 pm <- useWithStaleFast GetParsedModule npath
136135 binds <- fromMaybe (mempty , zeroMapping) <$> useWithStaleFast GetBindings npath
137- pure (opts, fmap (,pm,binds) compls )
136+ pure (opts, fmap (,pm,binds) (( fst <$> localCompls) <> ( fst <$> nonLocalCompls)) )
138137 case compls of
139- Just (( cci', _) , parsedMod, bindMap) -> do
138+ Just (cci', parsedMod, bindMap) -> do
140139 pfix <- VFS. getCompletionPrefix position cnts
141140 case (pfix, completionContext) of
142141 (Just (VFS. PosPrefixInfo _ " " _ _), Just CompletionContext { _triggerCharacter = Just " ." })
@@ -145,8 +144,57 @@ getCompletionsLSP lsp ide
145144 let clientCaps = clientCapabilities $ shakeExtras ide
146145 config <- getClientConfig lsp
147146 let snippets = WithSnippets . completionSnippetsOn $ config
148- allCompletions <- getCompletions ideOpts cci' parsedMod bindMap pfix' clientCaps snippets
147+ allCompletions <- getCompletions plId ideOpts cci' parsedMod bindMap pfix' clientCaps snippets
149148 pure $ Completions (List allCompletions)
150149 _ -> return (Completions $ List [] )
151150 _ -> return (Completions $ List [] )
152151 _ -> return (Completions $ List [] )
152+
153+ ----------------------------------------------------------------------------------------------------
154+
155+ extendImportCommand :: PluginCommand IdeState
156+ extendImportCommand =
157+ PluginCommand (CommandId extendImportCommandId) " additional edits for a completion" extendImportHandler
158+
159+ extendImportHandler :: CommandFunction IdeState ExtendImport
160+ extendImportHandler _lsp ideState edit = do
161+ res <- runMaybeT $ extendImportHandler' ideState edit
162+ return (Right Null , res)
163+
164+ extendImportHandler' :: IdeState -> ExtendImport -> MaybeT IO (ServerMethod , ApplyWorkspaceEditParams )
165+ extendImportHandler' ideState ExtendImport {.. }
166+ | Just fp <- uriToFilePath doc,
167+ nfp <- toNormalizedFilePath' fp =
168+ do
169+ (ms, ps, imps) <- MaybeT $
170+ runAction " extend import" ideState $
171+ runMaybeT $ do
172+ -- We want accurate edits, so do not use stale data here
173+ (ms, imps) <- MaybeT $ use GetModSummaryWithoutTimestamps nfp
174+ ps <- MaybeT $ use GetAnnotatedParsedSource nfp
175+ return (ms, ps, imps)
176+ let df = ms_hspp_opts ms
177+ wantedModule = mkModuleName (T. unpack importName)
178+ wantedQual = mkModuleName . T. unpack <$> importQual
179+ imp <- liftMaybe $ find (isWantedModule wantedModule wantedQual) imps
180+ wedit <-
181+ liftEither $
182+ rewriteToWEdit df doc (annsA ps) $
183+ extendImport (T. unpack <$> thingParent) (T. unpack newThing) imp
184+ return (WorkspaceApplyEdit , ApplyWorkspaceEditParams wedit)
185+ | otherwise =
186+ mzero
187+
188+ isWantedModule :: ModuleName -> Maybe ModuleName -> GenLocated l (ImportDecl pass ) -> Bool
189+ isWantedModule wantedModule Nothing (L _ it@ ImportDecl {ideclName, ideclHiding = Just (False , _)}) =
190+ not (isQualifiedImport it) && unLoc ideclName == wantedModule
191+ isWantedModule wantedModule (Just qual) (L _ ImportDecl {ideclAs, ideclName, ideclHiding = Just (False , _)}) =
192+ unLoc ideclName == wantedModule && (wantedModule == qual || (unLoc <$> ideclAs) == Just qual)
193+ isWantedModule _ _ _ = False
194+
195+ liftMaybe :: Monad m => Maybe a -> MaybeT m a
196+ liftMaybe a = MaybeT $ pure a
197+
198+ liftEither :: Monad m => Either e a -> MaybeT m a
199+ liftEither (Left _) = mzero
200+ liftEither (Right x) = return x
0 commit comments