4
4
5
5
module Development.IDE.Plugin.Completions
6
6
( descriptor
7
- , ProduceCompletions (.. )
8
7
, LocalCompletions (.. )
9
8
, NonLocalCompletions (.. )
10
9
) where
11
10
import Language.Haskell.LSP.Types
12
11
import qualified Language.Haskell.LSP.Core as LSP
13
12
import qualified Language.Haskell.LSP.VFS as VFS
14
13
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
15
20
import Development.Shake.Classes
16
21
import Development.Shake
17
22
import GHC.Generics
@@ -22,36 +27,33 @@ import Development.IDE.Types.Location
22
27
import Development.IDE.Core.RuleTypes
23
28
import Development.IDE.Core.Shake
24
29
import Development.IDE.GHC.Compat
25
-
30
+ import Development.IDE.GHC.ExactPrint ( Annotated ( annsA ), GetAnnotatedParsedSource ( GetAnnotatedParsedSource ))
26
31
import 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
29
34
import Ide.Plugin.Config (Config (completionSnippetsOn ))
30
35
import Ide.PluginUtils (getClientConfig )
31
36
import Ide.Types
32
-
37
+ import TcRnDriver ( tcRnImportDecls )
33
38
#if defined(GHC_LIB)
34
39
import Development.IDE.Import.DependencyInformation
35
40
#endif
36
41
37
42
descriptor :: PluginId -> PluginDescriptor IdeState
38
43
descriptor plId = (defaultPluginDescriptor plId)
39
- { pluginRules = produceCompletions
40
- , pluginCompletionProvider = Just getCompletionsLSP
41
- }
44
+ { pluginRules = produceCompletions,
45
+ pluginCompletionProvider = Just (getCompletionsLSP plId),
46
+ pluginCommands = [extendImportCommand]
47
+ }
42
48
43
49
produceCompletions :: Rules ()
44
50
produceCompletions = 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)
50
51
define $ \ LocalCompletions file -> do
52
+ let uri = fromNormalizedUri $ normalizedFilePathToUri file
51
53
pm <- useWithStale GetParsedModule file
52
54
case pm of
53
55
Just (pm, _) -> do
54
- let cdata = localCompletionsForParsedModule pm
56
+ let cdata = localCompletionsForParsedModule uri pm
55
57
return ([] , Just cdata)
56
58
_ -> return ([] , Nothing )
57
59
define $ \ NonLocalCompletions file -> do
@@ -77,7 +79,8 @@ produceCompletions = do
77
79
res <- liftIO $ tcRnImportDecls env (dropListFromImportDecl <$> imps)
78
80
case res of
79
81
(_, 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
81
84
return ([] , Just cdata)
82
85
(_diag, _) ->
83
86
return ([] , Nothing )
@@ -94,16 +97,9 @@ dropListFromImportDecl iDecl = let
94
97
in f <$> iDecl
95
98
96
99
-- | Produce completions info for a file
97
- type instance RuleResult ProduceCompletions = CachedCompletions
98
100
type instance RuleResult LocalCompletions = CachedCompletions
99
101
type instance RuleResult NonLocalCompletions = CachedCompletions
100
102
101
- data ProduceCompletions = ProduceCompletions
102
- deriving (Eq , Show , Typeable , Generic )
103
- instance Hashable ProduceCompletions
104
- instance NFData ProduceCompletions
105
- instance Binary ProduceCompletions
106
-
107
103
data LocalCompletions = LocalCompletions
108
104
deriving (Eq , Show , Typeable , Generic )
109
105
instance Hashable LocalCompletions
@@ -115,13 +111,15 @@ data NonLocalCompletions = NonLocalCompletions
115
111
instance Hashable NonLocalCompletions
116
112
instance NFData NonLocalCompletions
117
113
instance Binary NonLocalCompletions
114
+
118
115
-- | Generate code actions.
119
116
getCompletionsLSP
120
- :: LSP. LspFuncs Config
117
+ :: PluginId
118
+ -> LSP. LspFuncs Config
121
119
-> IdeState
122
120
-> CompletionParams
123
121
-> IO (Either ResponseError CompletionResponseResult )
124
- getCompletionsLSP lsp ide
122
+ getCompletionsLSP plId lsp ide
125
123
CompletionParams {_textDocument= TextDocumentIdentifier uri
126
124
,_position= position
127
125
,_context= completionContext} = do
@@ -131,12 +129,13 @@ getCompletionsLSP lsp ide
131
129
let npath = toNormalizedFilePath' path
132
130
(ideOpts, compls) <- runIdeAction " Completion" (shakeExtras ide) $ do
133
131
opts <- liftIO $ getIdeOptionsIO $ shakeExtras ide
134
- compls <- useWithStaleFast ProduceCompletions npath
132
+ localCompls <- useWithStaleFast LocalCompletions npath
133
+ nonLocalCompls <- useWithStaleFast NonLocalCompletions npath
135
134
pm <- useWithStaleFast GetParsedModule npath
136
135
binds <- fromMaybe (mempty , zeroMapping) <$> useWithStaleFast GetBindings npath
137
- pure (opts, fmap (,pm,binds) compls )
136
+ pure (opts, fmap (,pm,binds) (( fst <$> localCompls) <> ( fst <$> nonLocalCompls)) )
138
137
case compls of
139
- Just (( cci', _) , parsedMod, bindMap) -> do
138
+ Just (cci', parsedMod, bindMap) -> do
140
139
pfix <- VFS. getCompletionPrefix position cnts
141
140
case (pfix, completionContext) of
142
141
(Just (VFS. PosPrefixInfo _ " " _ _), Just CompletionContext { _triggerCharacter = Just " ." })
@@ -145,8 +144,57 @@ getCompletionsLSP lsp ide
145
144
let clientCaps = clientCapabilities $ shakeExtras ide
146
145
config <- getClientConfig lsp
147
146
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
149
148
pure $ Completions (List allCompletions)
150
149
_ -> return (Completions $ List [] )
151
150
_ -> return (Completions $ List [] )
152
151
_ -> 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