@@ -12,59 +12,42 @@ import Control.DeepSeq
12
12
import Control.Lens ((^.) )
13
13
import Control.Monad.Extra
14
14
import Control.Monad.IO.Class
15
- import Control.Monad.Trans.Class (lift )
16
15
import Control.Monad.Trans.Maybe (runMaybeT )
17
16
import qualified Data.ByteString as BS
18
17
import Data.Hashable
19
- import Data.HashMap.Strict (HashMap ,
20
- toList )
18
+ import Data.HashMap.Strict (HashMap )
19
+ -- toList)
21
20
import qualified Data.HashMap.Strict as HashMap
22
- import qualified Data.List as List
23
21
import qualified Data.List.NonEmpty as NE
24
- import qualified Data.Maybe as Maybe
25
22
import Data.Proxy
26
23
import qualified Data.Text ()
27
- import qualified Data.Text as T
28
24
import qualified Data.Text.Encoding as Encoding
29
25
import Data.Text.Utf16.Rope.Mixed as Rope
30
26
import Development.IDE as D
31
- import Development.IDE.Core.FileStore (getVersionedTextDoc )
32
- import Development.IDE.Core.PluginUtils
33
27
import Development.IDE.Core.Shake (restartShakeSession )
34
28
import qualified Development.IDE.Core.Shake as Shake
35
29
import Development.IDE.Graph (Key ,
36
30
alwaysRerun )
37
- import Development.IDE.LSP.HoverDefinition (foundHover )
38
31
import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
39
32
import Development.IDE.Types.Shake (toKey )
40
- import qualified Distribution.CabalSpecVersion as Cabal
41
33
import qualified Distribution.Fields as Syntax
42
- import Distribution.Package (Dependency )
43
- import Distribution.PackageDescription (allBuildDepends ,
44
- depPkgName ,
45
- unPackageName )
46
- import Distribution.PackageDescription.Configuration (flattenPackageDescription )
47
- import Distribution.Parsec.Error
34
+ -- import Distribution.PackageDescription (allBuildDepends,
35
+ -- depPkgName,
36
+ -- unPackageName)
48
37
import qualified Distribution.Parsec.Position as Syntax
49
38
import GHC.Generics
50
- import Ide.Plugin.Cabal.Completion.CabalFields as CabalFields
51
39
import qualified Ide.Plugin.Cabal.Completion.Completer.Types as CompleterTypes
52
- import qualified Ide.Plugin.Cabal.Completion.Data as Data
53
40
import qualified Ide.Plugin.Cabal.Completion.Types as CTypes
54
41
import Ide.Plugin.Cabal.Orphans ()
55
42
import qualified Ide.Plugin.CabalProject.Completion.Completions as Completions
56
43
import Ide.Plugin.CabalProject.Diagnostics as Diagnostics
57
44
import Ide.Plugin.CabalProject.Parse as Parse
58
45
import Ide.Plugin.CabalProject.Types as Types
59
- import Ide.Plugin.Error
60
46
import Ide.Types
61
47
import qualified Language.LSP.Protocol.Lens as JL
62
48
import qualified Language.LSP.Protocol.Message as LSP
63
49
import Language.LSP.Protocol.Types
64
50
import qualified Language.LSP.VFS as VFS
65
- import System.FilePath (takeFileName )
66
- import Text.Regex.TDFA
67
-
68
51
69
52
data Log
70
53
= LogModificationTime NormalizedFilePath FileVersion
@@ -103,7 +86,7 @@ instance Pretty Log where
103
86
descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
104
87
descriptor recorder plId =
105
88
(defaultCabalProjectPluginDescriptor plId " Provides a variety of IDE features in cabal.project files" )
106
- { pluginRules = cabalRules recorder plId
89
+ { pluginRules = cabalProjectRules recorder plId
107
90
, pluginHandlers =
108
91
mconcat
109
92
[
@@ -115,25 +98,25 @@ descriptor recorder plId =
115
98
\ ide vfs _ (DidOpenTextDocumentParams TextDocumentItem {_uri, _version}) -> liftIO $ do
116
99
whenUriFile _uri $ \ file -> do
117
100
log' Debug $ LogDocOpened _uri
118
- restartCabalShakeSession (shakeExtras ide) vfs file " (opened)" $
101
+ restartCabalProjectShakeSession (shakeExtras ide) vfs file " (opened)" $
119
102
addFileOfInterest recorder ide file Modified {firstOpen = True }
120
103
, mkPluginNotificationHandler LSP. SMethod_TextDocumentDidChange $
121
104
\ ide vfs _ (DidChangeTextDocumentParams VersionedTextDocumentIdentifier {_uri} _) -> liftIO $ do
122
105
whenUriFile _uri $ \ file-> do
123
106
log' Debug $ LogDocModified _uri
124
- restartCabalShakeSession (shakeExtras ide) vfs file " (changed)" $
107
+ restartCabalProjectShakeSession (shakeExtras ide) vfs file " (changed)" $
125
108
addFileOfInterest recorder ide file Modified {firstOpen = False }
126
109
, mkPluginNotificationHandler LSP. SMethod_TextDocumentDidSave $
127
110
\ ide vfs _ (DidSaveTextDocumentParams TextDocumentIdentifier {_uri} _) -> liftIO $ do
128
111
whenUriFile _uri $ \ file -> do
129
112
log' Debug $ LogDocSaved _uri
130
- restartCabalShakeSession (shakeExtras ide) vfs file " (saved)" $
113
+ restartCabalProjectShakeSession (shakeExtras ide) vfs file " (saved)" $
131
114
addFileOfInterest recorder ide file OnDisk
132
115
, mkPluginNotificationHandler LSP. SMethod_TextDocumentDidClose $
133
116
\ ide vfs _ (DidCloseTextDocumentParams TextDocumentIdentifier {_uri}) -> liftIO $ do
134
117
whenUriFile _uri $ \ file -> do
135
118
log' Debug $ LogDocClosed _uri
136
- restartCabalShakeSession (shakeExtras ide) vfs file " (closed)" $
119
+ restartCabalProjectShakeSession (shakeExtras ide) vfs file " (closed)" $
137
120
deleteFileOfInterest recorder ide file
138
121
]
139
122
, pluginConfigDescriptor = defaultConfigDescriptor
@@ -146,7 +129,7 @@ descriptor recorder plId =
146
129
whenUriFile :: Uri -> (NormalizedFilePath -> IO () ) -> IO ()
147
130
whenUriFile uri act = whenJust (uriToFilePath uri) $ act . toNormalizedFilePath'
148
131
149
- {- | Helper function to restart the shake session, specifically for modifying . cabal files.
132
+ {- | Helper function to restart the shake session, specifically for modifying cabal.project files.
150
133
No special logic, just group up a bunch of functions you need for the base
151
134
Notification Handlers.
152
135
@@ -155,28 +138,28 @@ needs to be re-parsed. That's what we do when we record the dirty key that our p
155
138
rule depends on.
156
139
Then we restart the shake session, so that changes to our virtual files are actually picked up.
157
140
-}
158
- restartCabalShakeSession :: ShakeExtras -> VFS. VFS -> NormalizedFilePath -> String -> IO [Key ] -> IO ()
159
- restartCabalShakeSession shakeExtras vfs file actionMsg actionBetweenSession = do
141
+ restartCabalProjectShakeSession :: ShakeExtras -> VFS. VFS -> NormalizedFilePath -> String -> IO [Key ] -> IO ()
142
+ restartCabalProjectShakeSession shakeExtras vfs file actionMsg actionBetweenSession = do
160
143
restartShakeSession shakeExtras (VFSModified vfs) (fromNormalizedFilePath file ++ " " ++ actionMsg) [] $ do
161
144
keys <- actionBetweenSession
162
145
return (toKey GetModificationTime file: keys)
163
146
164
147
165
- cabalRules :: Recorder (WithPriority Log ) -> PluginId -> Rules ()
166
- cabalRules recorder plId = do
167
- -- Make sure we initialise the cabal files-of-interest.
148
+ cabalProjectRules :: Recorder (WithPriority Log ) -> PluginId -> Rules ()
149
+ cabalProjectRules recorder plId = do
150
+ -- Make sure we initialise the cabal.project files-of-interest.
168
151
ofInterestRules recorder
169
- -- Rule to produce diagnostics for cabal files.
152
+ -- Rule to produce diagnostics for cabal.project files.
170
153
define (cmapWithPrio LogShake recorder) $ \ ParseCabalProjectFields file -> do
171
154
config <- getPluginConfigAction plId
172
155
if not (plcGlobalOn config && plcDiagnosticsOn config)
173
156
then pure ([] , Nothing )
174
157
else do
175
158
-- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
176
159
-- we rerun this rule because this rule *depends* on GetModificationTime.
177
- (t, mCabalSource ) <- use_ GetFileContents file
160
+ (t, mCabalProjectSource ) <- use_ GetFileContents file
178
161
log' Debug $ LogModificationTime file t
179
- contents <- case mCabalSource of
162
+ contents <- case mCabalProjectSource of
180
163
Just sources ->
181
164
pure $ Encoding. encodeUtf8 $ Rope. toText sources
182
165
Nothing -> do
@@ -195,10 +178,10 @@ cabalRules recorder plId = do
195
178
else do
196
179
-- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
197
180
-- we rerun this rule because this rule *depends* on GetModificationTime.
198
- (t, mCabalSource ) <- use_ GetFileContents file
181
+ (t, mCabalProjectSource ) <- use_ GetFileContents file
199
182
log' Debug $ LogModificationTime file t
200
183
201
- contents <- case mCabalSource of
184
+ contents <- case mCabalProjectSource of
202
185
Just sources ->
203
186
pure $ Encoding. encodeUtf8 $ Rope. toText sources
204
187
Nothing ->
@@ -216,96 +199,96 @@ cabalRules recorder plId = do
216
199
pure (warnDiags, Just projCfg)
217
200
218
201
action $ do
219
- -- Run the cabal kick. This code always runs when 'shakeRestart' is run.
202
+ -- Run the cabal.project kick. This code always runs when 'shakeRestart' is run.
220
203
-- Must be careful to not impede the performance too much. Crucial to
221
204
-- a snappy IDE experience.
222
205
kick
223
206
where
224
207
log' = logWith recorder
225
208
226
- {- | This is the kick function for the cabal plugin.
209
+ {- | This is the kick function for the cabal project plugin.
227
210
We run this action, whenever we shake session us run/restarted, which triggers
228
- actions to produce diagnostics for cabal files.
211
+ actions to produce diagnostics for cabal.project files.
229
212
230
213
It is paramount that this kick-function can be run quickly, since it is a blocking
231
214
function invocation.
232
215
-}
233
216
kick :: Action ()
234
217
kick = do
235
- files <- HashMap. keys <$> getCabalFilesOfInterestUntracked
218
+ files <- HashMap. keys <$> getCabalProjectFilesOfInterestUntracked
236
219
-- let keys = map Types.ParseCabalProjectFile files
237
220
Shake. runWithSignal (Proxy @ " kick/start/cabal-project" ) (Proxy @ " kick/done/cabal-project" ) files Types. ParseCabalProjectFile
238
221
239
222
240
223
-- ----------------------------------------------------------------
241
- -- Cabal file of Interest rules and global variable
224
+ -- Cabal.project file of Interest rules and global variable
242
225
-- ----------------------------------------------------------------
243
226
244
- {- | Cabal files that are currently open in the lsp-client.
227
+ {- | Cabal.project files that are currently open in the lsp-client.
245
228
Specific actions happen when these files are saved, closed or modified,
246
229
such as generating diagnostics, re-parsing, etc...
247
230
248
231
We need to store the open files to parse them again if we restart the shake session.
249
232
Restarting of the shake session happens whenever these files are modified.
250
233
-}
251
- newtype OfInterestCabalVar = OfInterestCabalVar (Var (HashMap NormalizedFilePath FileOfInterestStatus ))
234
+ newtype OfInterestCabalProjectVar = OfInterestCabalProjectVar (Var (HashMap NormalizedFilePath FileOfInterestStatus ))
252
235
253
- instance Shake. IsIdeGlobal OfInterestCabalVar
236
+ instance Shake. IsIdeGlobal OfInterestCabalProjectVar
254
237
255
- data IsCabalFileOfInterest = IsCabalFileOfInterest
238
+ data IsCabalProjectFileOfInterest = IsCabalProjectFileOfInterest
256
239
deriving (Eq , Show , Generic )
257
- instance Hashable IsCabalFileOfInterest
258
- instance NFData IsCabalFileOfInterest
240
+ instance Hashable IsCabalProjectFileOfInterest
241
+ instance NFData IsCabalProjectFileOfInterest
259
242
260
- type instance RuleResult IsCabalFileOfInterest = CabalFileOfInterestResult
243
+ type instance RuleResult IsCabalProjectFileOfInterest = CabalProjectFileOfInterestResult
261
244
262
- data CabalFileOfInterestResult = NotCabalFOI | IsCabalFOI FileOfInterestStatus
245
+ data CabalProjectFileOfInterestResult = NotCabalProjectFOI | IsCabalProjectFOI FileOfInterestStatus
263
246
deriving (Eq , Show , Generic )
264
- instance Hashable CabalFileOfInterestResult
265
- instance NFData CabalFileOfInterestResult
247
+ instance Hashable CabalProjectFileOfInterestResult
248
+ instance NFData CabalProjectFileOfInterestResult
266
249
267
250
{- | The rule that initialises the files of interest state.
268
251
269
252
Needs to be run on start-up.
270
253
-}
271
254
ofInterestRules :: Recorder (WithPriority Log ) -> Rules ()
272
255
ofInterestRules recorder = do
273
- Shake. addIdeGlobal . OfInterestCabalVar =<< liftIO (newVar HashMap. empty)
274
- Shake. defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \ IsCabalFileOfInterest f -> do
256
+ Shake. addIdeGlobal . OfInterestCabalProjectVar =<< liftIO (newVar HashMap. empty)
257
+ Shake. defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \ IsCabalProjectFileOfInterest f -> do
275
258
alwaysRerun
276
- filesOfInterest <- getCabalFilesOfInterestUntracked
277
- let foi = maybe NotCabalFOI IsCabalFOI $ f `HashMap.lookup` filesOfInterest
259
+ filesOfInterest <- getCabalProjectFilesOfInterestUntracked
260
+ let foi = maybe NotCabalProjectFOI IsCabalProjectFOI $ f `HashMap.lookup` filesOfInterest
278
261
fp = summarize foi
279
262
res = (Just fp, Just foi)
280
263
return res
281
264
where
282
- summarize NotCabalFOI = BS. singleton 0
283
- summarize (IsCabalFOI OnDisk ) = BS. singleton 1
284
- summarize (IsCabalFOI (Modified False )) = BS. singleton 2
285
- summarize (IsCabalFOI (Modified True )) = BS. singleton 3
286
-
287
- getCabalFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus )
288
- getCabalFilesOfInterestUntracked = do
289
- OfInterestCabalVar var <- Shake. getIdeGlobalAction
265
+ summarize NotCabalProjectFOI = BS. singleton 0
266
+ summarize (IsCabalProjectFOI OnDisk ) = BS. singleton 1
267
+ summarize (IsCabalProjectFOI (Modified False )) = BS. singleton 2
268
+ summarize (IsCabalProjectFOI (Modified True )) = BS. singleton 3
269
+
270
+ getCabalProjectFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus )
271
+ getCabalProjectFilesOfInterestUntracked = do
272
+ OfInterestCabalProjectVar var <- Shake. getIdeGlobalAction
290
273
liftIO $ readVar var
291
274
292
275
addFileOfInterest :: Recorder (WithPriority Log ) -> IdeState -> NormalizedFilePath -> FileOfInterestStatus -> IO [Key ]
293
276
addFileOfInterest recorder state f v = do
294
- OfInterestCabalVar var <- Shake. getIdeGlobalState state
277
+ OfInterestCabalProjectVar var <- Shake. getIdeGlobalState state
295
278
(prev, files) <- modifyVar var $ \ dict -> do
296
279
let (prev, new) = HashMap. alterF (,Just v) f dict
297
280
pure (new, (prev, new))
298
281
if prev /= Just v
299
282
then do
300
283
log' Debug $ LogFOI files
301
- return [toKey IsCabalFileOfInterest f]
284
+ return [toKey IsCabalProjectFileOfInterest f]
302
285
else return []
303
286
where
304
287
log' = logWith recorder
305
288
306
289
deleteFileOfInterest :: Recorder (WithPriority Log ) -> IdeState -> NormalizedFilePath -> IO [Key ]
307
290
deleteFileOfInterest recorder state f = do
308
- OfInterestCabalVar var <- Shake. getIdeGlobalState state
291
+ OfInterestCabalProjectVar var <- Shake. getIdeGlobalState state
309
292
files <- modifyVar' var $ HashMap. delete f
310
293
log' Debug $ LogFOI files
311
294
return [toKey IsFileOfInterest f]
@@ -329,20 +312,22 @@ completion recorder ide _ complParams = do
329
312
pure . InR $ InR Null
330
313
Just (fields, _) -> do
331
314
let lspPrefInfo = Ghcide. getCompletionPrefixFromRope position cnts
332
- cabalPrefInfo = Completions. getCabalPrefixInfo path lspPrefInfo
333
- let res = computeCompletionsAt recorder ide cabalPrefInfo path fields
315
+ cabalProjectPrefInfo = Completions. getCabalPrefixInfo path lspPrefInfo
316
+ let res = computeCompletionsAt recorder ide cabalProjectPrefInfo path fields
334
317
liftIO $ fmap InL res
335
318
Nothing -> pure . InR $ InR Null
336
319
337
320
computeCompletionsAt :: Recorder (WithPriority Log ) -> IdeState -> CTypes. CabalPrefixInfo -> FilePath -> [Syntax. Field Syntax. Position ] -> IO [CompletionItem ]
338
- computeCompletionsAt recorder ide prefInfo fp fields = do
321
+ computeCompletionsAt recorder _ prefInfo _ fields = do
339
322
runMaybeT (context fields) >>= \ case
340
323
Nothing -> pure []
341
324
Just ctx -> do
342
325
logWith recorder Debug $ LogCompletionContext ctx pos
343
326
let completer = Completions. contextToCompleter ctx
344
327
let completerData = CompleterTypes. CompleterData
345
328
{
329
+ getLatestGPD = pure Nothing ,
330
+ getCabalCommonSections = pure Nothing ,
346
331
cabalPrefixInfo = prefInfo
347
332
, stanzaName =
348
333
case fst ctx of
0 commit comments