4
4
{-# LANGUAGE OverloadedStrings #-}
5
5
{-# LANGUAGE TypeFamilies #-}
6
6
7
- module Ide.Plugin.Cabal (descriptor , Log (.. )) where
7
+ module Ide.Plugin.Cabal (descriptor , haskellInteractionDescriptor , Log (.. )) where
8
8
9
9
import Control.Concurrent.Strict
10
10
import Control.DeepSeq
@@ -17,12 +17,14 @@ import qualified Data.ByteString as BS
17
17
import Data.Hashable
18
18
import Data.HashMap.Strict (HashMap )
19
19
import qualified Data.HashMap.Strict as HashMap
20
+ import Data.List (find )
20
21
import qualified Data.List.NonEmpty as NE
21
22
import qualified Data.Maybe as Maybe
22
23
import qualified Data.Text as T
23
24
import qualified Data.Text.Encoding as Encoding
24
25
import Data.Typeable
25
26
import Development.IDE as D
27
+ import Development.IDE.Core.PluginUtils
26
28
import Development.IDE.Core.Shake (restartShakeSession )
27
29
import qualified Development.IDE.Core.Shake as Shake
28
30
import Development.IDE.Graph (Key , alwaysRerun )
@@ -31,6 +33,7 @@ import Development.IDE.Types.Shake (toKey)
31
33
import qualified Distribution.Fields as Syntax
32
34
import qualified Distribution.Parsec.Position as Syntax
33
35
import GHC.Generics
36
+ import Ide.Plugin.Cabal.Completion.CabalFields as CabalFields
34
37
import qualified Ide.Plugin.Cabal.Completion.Completer.Types as CompleterTypes
35
38
import qualified Ide.Plugin.Cabal.Completion.Completions as Completions
36
39
import Ide.Plugin.Cabal.Completion.Types (ParseCabalCommonSections (ParseCabalCommonSections ),
@@ -43,12 +46,16 @@ import qualified Ide.Plugin.Cabal.LicenseSuggest as LicenseSuggest
43
46
import Ide.Plugin.Cabal.Orphans ()
44
47
import Ide.Plugin.Cabal.Outline
45
48
import qualified Ide.Plugin.Cabal.Parse as Parse
49
+ import Ide.Plugin.Error
46
50
import Ide.Types
47
51
import qualified Language.LSP.Protocol.Lens as JL
48
52
import qualified Language.LSP.Protocol.Message as LSP
49
53
import Language.LSP.Protocol.Types
50
54
import qualified Language.LSP.VFS as VFS
51
55
56
+ import qualified Data.Text ()
57
+ import qualified Ide.Plugin.Cabal.CabalAdd as CabalAdd
58
+
52
59
data Log
53
60
= LogModificationTime NormalizedFilePath FileVersion
54
61
| LogShake Shake. Log
@@ -59,6 +66,7 @@ data Log
59
66
| LogFOI (HashMap NormalizedFilePath FileOfInterestStatus )
60
67
| LogCompletionContext Types. Context Position
61
68
| LogCompletions Types. Log
69
+ | LogCabalAdd CabalAdd. Log
62
70
deriving (Show )
63
71
64
72
instance Pretty Log where
@@ -82,6 +90,25 @@ instance Pretty Log where
82
90
<+> " for cursor position:"
83
91
<+> pretty position
84
92
LogCompletions logs -> pretty logs
93
+ LogCabalAdd logs -> pretty logs
94
+
95
+ -- | Some actions with cabal files originate from haskell files.
96
+ -- This descriptor allows to hook into the diagnostics of haskell source files, and
97
+ -- allows us to provide code actions and commands that interact with `.cabal` files.
98
+ haskellInteractionDescriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
99
+ haskellInteractionDescriptor recorder plId =
100
+ (defaultPluginDescriptor plId " Provides the cabal-add code action in haskell files" )
101
+ { pluginHandlers =
102
+ mconcat
103
+ [ mkPluginHandler LSP. SMethod_TextDocumentCodeAction cabalAddCodeAction
104
+ ]
105
+ , pluginCommands = [PluginCommand CabalAdd. cabalAddCommand " add a dependency to a cabal file" (CabalAdd. command cabalAddRecorder)]
106
+ , pluginRules = pure ()
107
+ , pluginNotificationHandlers = mempty
108
+ }
109
+ where
110
+ cabalAddRecorder = cmapWithPrio LogCabalAdd recorder
111
+
85
112
86
113
descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
87
114
descriptor recorder plId =
@@ -93,6 +120,7 @@ descriptor recorder plId =
93
120
, mkPluginHandler LSP. SMethod_TextDocumentCompletion $ completion recorder
94
121
, mkPluginHandler LSP. SMethod_TextDocumentDocumentSymbol moduleOutline
95
122
, mkPluginHandler LSP. SMethod_TextDocumentCodeAction $ fieldSuggestCodeAction recorder
123
+ , mkPluginHandler LSP. SMethod_TextDocumentDefinition gotoDefinition
96
124
]
97
125
, pluginNotificationHandlers =
98
126
mconcat
@@ -277,6 +305,59 @@ fieldSuggestCodeAction recorder ide _ (CodeActionParams _ _ (TextDocumentIdentif
277
305
let completionTexts = fmap (^. JL. label) completions
278
306
pure $ FieldSuggest. fieldErrorAction uri fieldName completionTexts _range
279
307
308
+ -- | CodeActions for going to definitions.
309
+ --
310
+ -- Provides a CodeAction for going to a definition when clicking on an identifier.
311
+ -- The definition is found by traversing the sections and comparing their name to
312
+ -- the clicked identifier.
313
+ --
314
+ -- TODO: Support more definitions than sections.
315
+ gotoDefinition :: PluginMethodHandler IdeState LSP. Method_TextDocumentDefinition
316
+ gotoDefinition ideState _ msgParam = do
317
+ nfp <- getNormalizedFilePathE uri
318
+ cabalFields <- runActionE " cabal-plugin.commonSections" ideState $ useE ParseCabalFields nfp
319
+ case CabalFields. findTextWord cursor cabalFields of
320
+ Nothing ->
321
+ pure $ InR $ InR Null
322
+ Just cursorText -> do
323
+ commonSections <- runActionE " cabal-plugin.commonSections" ideState $ useE ParseCabalCommonSections nfp
324
+ case find (isSectionArgName cursorText) commonSections of
325
+ Nothing ->
326
+ pure $ InR $ InR Null
327
+ Just commonSection -> do
328
+ pure $ InL $ Definition $ InL $ Location uri $ CabalFields. getFieldLSPRange commonSection
329
+ where
330
+ cursor = Types. lspPositionToCabalPosition (msgParam ^. JL. position)
331
+ uri = msgParam ^. JL. textDocument . JL. uri
332
+ isSectionArgName name (Syntax. Section _ sectionArgName _) = name == CabalFields. onelineSectionArgs sectionArgName
333
+ isSectionArgName _ _ = False
334
+
335
+ cabalAddCodeAction :: PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
336
+ cabalAddCodeAction state plId (CodeActionParams _ _ (TextDocumentIdentifier uri) _ CodeActionContext {_diagnostics= diags}) = do
337
+ maxCompls <- fmap maxCompletions . liftIO $ runAction " cabal.cabal-add" state getClientConfigAction
338
+ let suggestions = take maxCompls $ concatMap CabalAdd. hiddenPackageSuggestion diags
339
+ case suggestions of
340
+ [] -> pure $ InL []
341
+ _ ->
342
+ case uriToFilePath uri of
343
+ Nothing -> pure $ InL []
344
+ Just haskellFilePath -> do
345
+ mbCabalFile <- liftIO $ CabalAdd. findResponsibleCabalFile haskellFilePath
346
+ case mbCabalFile of
347
+ Nothing -> pure $ InL []
348
+ Just cabalFilePath -> do
349
+ verTxtDocId <- lift $ pluginGetVersionedTextDoc $ TextDocumentIdentifier (filePathToUri cabalFilePath)
350
+ mbGPD <- liftIO $ runAction " cabal.cabal-add" state $ useWithStale ParseCabalFile $ toNormalizedFilePath cabalFilePath
351
+ case mbGPD of
352
+ Nothing -> pure $ InL []
353
+ Just (gpd, _) -> do
354
+ actions <- liftIO $ CabalAdd. addDependencySuggestCodeAction plId verTxtDocId
355
+ suggestions
356
+ haskellFilePath cabalFilePath
357
+ gpd
358
+ pure $ InL $ fmap InR actions
359
+
360
+
280
361
-- ----------------------------------------------------------------
281
362
-- Cabal file of Interest rules and global variable
282
363
-- ----------------------------------------------------------------
0 commit comments