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
@@ -50,6 +50,9 @@ import qualified Language.LSP.Protocol.Message as LSP
50
50
import Language.LSP.Protocol.Types
51
51
import qualified Language.LSP.VFS as VFS
52
52
53
+ import qualified Data.Text ()
54
+ import qualified Ide.Plugin.Cabal.CabalAdd as CabalAdd
55
+
53
56
data Log
54
57
= LogModificationTime NormalizedFilePath FileVersion
55
58
| LogShake Shake. Log
@@ -60,6 +63,7 @@ data Log
60
63
| LogFOI (HashMap NormalizedFilePath FileOfInterestStatus )
61
64
| LogCompletionContext Types. Context Position
62
65
| LogCompletions Types. Log
66
+ | LogCabalAdd CabalAdd. Log
63
67
deriving (Show )
64
68
65
69
instance Pretty Log where
@@ -83,6 +87,25 @@ instance Pretty Log where
83
87
<+> " for cursor position:"
84
88
<+> pretty position
85
89
LogCompletions logs -> pretty logs
90
+ LogCabalAdd logs -> pretty logs
91
+
92
+ -- | Some actions with cabal files originate from haskell files.
93
+ -- This descriptor allows to hook into the diagnostics of haskell source files, and
94
+ -- allows us to provide code actions and commands that interact with `.cabal` files.
95
+ haskellInteractionDescriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
96
+ haskellInteractionDescriptor recorder plId =
97
+ (defaultPluginDescriptor plId " Provides the cabal-add code action in haskell files" )
98
+ { pluginHandlers =
99
+ mconcat
100
+ [ mkPluginHandler LSP. SMethod_TextDocumentCodeAction cabalAddCodeAction
101
+ ]
102
+ , pluginCommands = [PluginCommand CabalAdd. cabalAddCommand " add a dependency to a cabal file" (CabalAdd. command cabalAddRecorder)]
103
+ , pluginRules = pure ()
104
+ , pluginNotificationHandlers = mempty
105
+ }
106
+ where
107
+ cabalAddRecorder = cmapWithPrio LogCabalAdd recorder
108
+
86
109
87
110
descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
88
111
descriptor recorder plId =
@@ -280,6 +303,32 @@ fieldSuggestCodeAction recorder ide _ (CodeActionParams _ _ (TextDocumentIdentif
280
303
pure $ FieldSuggest. fieldErrorAction uri fieldName completionTexts _range
281
304
282
305
306
+ cabalAddCodeAction :: PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
307
+ cabalAddCodeAction state plId (CodeActionParams _ _ (TextDocumentIdentifier uri) _ CodeActionContext {_diagnostics= diags}) = do
308
+ maxCompls <- fmap maxCompletions . liftIO $ runAction " cabal.cabal-add" state getClientConfigAction
309
+ let suggestions = take maxCompls $ concatMap CabalAdd. hiddenPackageSuggestion diags
310
+ case suggestions of
311
+ [] -> pure $ InL []
312
+ _ ->
313
+ case uriToFilePath uri of
314
+ Nothing -> pure $ InL []
315
+ Just haskellFilePath -> do
316
+ mbCabalFile <- liftIO $ CabalAdd. findResponsibleCabalFile haskellFilePath
317
+ case mbCabalFile of
318
+ Nothing -> pure $ InL []
319
+ Just cabalFilePath -> do
320
+ verTxtDocId <- lift $ pluginGetVersionedTextDoc $ TextDocumentIdentifier (filePathToUri cabalFilePath)
321
+ mbGPD <- liftIO $ runAction " cabal.cabal-add" state $ useWithStale ParseCabalFile $ toNormalizedFilePath cabalFilePath
322
+ case mbGPD of
323
+ Nothing -> pure $ InL []
324
+ Just (gpd, _) -> do
325
+ actions <- liftIO $ CabalAdd. addDependencySuggestCodeAction plId verTxtDocId
326
+ suggestions
327
+ haskellFilePath cabalFilePath
328
+ gpd
329
+ pure $ InL $ fmap InR actions
330
+
331
+
283
332
-- ----------------------------------------------------------------
284
333
-- Cabal file of Interest rules and global variable
285
334
-- ----------------------------------------------------------------
0 commit comments