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
@@ -53,6 +53,9 @@ import qualified Language.LSP.Protocol.Message as LSP
53
53
import Language.LSP.Protocol.Types
54
54
import qualified Language.LSP.VFS as VFS
55
55
56
+ import qualified Data.Text ()
57
+ import qualified Ide.Plugin.Cabal.CabalAdd as CabalAdd
58
+
56
59
data Log
57
60
= LogModificationTime NormalizedFilePath FileVersion
58
61
| LogShake Shake. Log
@@ -63,6 +66,7 @@ data Log
63
66
| LogFOI (HashMap NormalizedFilePath FileOfInterestStatus )
64
67
| LogCompletionContext Types. Context Position
65
68
| LogCompletions Types. Log
69
+ | LogCabalAdd CabalAdd. Log
66
70
deriving (Show )
67
71
68
72
instance Pretty Log where
@@ -86,6 +90,25 @@ instance Pretty Log where
86
90
<+> " for cursor position:"
87
91
<+> pretty position
88
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
+
89
112
90
113
descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
91
114
descriptor recorder plId =
@@ -309,6 +332,32 @@ gotoDefinition ideState _ msgParam = do
309
332
isSectionArgName name (Syntax. Section _ sectionArgName _) = name == CabalFields. onelineSectionArgs sectionArgName
310
333
isSectionArgName _ _ = False
311
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
+
312
361
-- ----------------------------------------------------------------
313
362
-- Cabal file of Interest rules and global variable
314
363
-- ----------------------------------------------------------------
0 commit comments