Skip to content

Commit a1c852c

Browse files
dyniecfendor
authored andcommitted
Use context in code actions for cabal files
1 parent 56022a0 commit a1c852c

File tree

3 files changed

+102
-74
lines changed

3 files changed

+102
-74
lines changed

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal.hs

Lines changed: 64 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -18,14 +18,15 @@ import Data.Hashable
1818
import Data.HashMap.Strict (HashMap)
1919
import qualified Data.HashMap.Strict as HashMap
2020
import qualified Data.List.NonEmpty as NE
21+
import Data.Maybe (mapMaybe)
22+
import qualified Data.Text as T
2123
import qualified Data.Text.Encoding as Encoding
2224
import Data.Typeable
2325
import Development.IDE as D
2426
import Development.IDE.Core.Shake (restartShakeSession)
2527
import qualified Development.IDE.Core.Shake as Shake
2628
import Development.IDE.Graph (Key, alwaysRerun)
2729
import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
28-
import qualified Development.IDE.Plugin.Completions.Types as Ghcide
2930
import Development.IDE.Types.Shake (toKey)
3031
import qualified Distribution.Fields as Syntax
3132
import qualified Distribution.Parsec.Position as Syntax
@@ -88,7 +89,7 @@ descriptor recorder plId =
8889
mconcat
8990
[ mkPluginHandler LSP.SMethod_TextDocumentCodeAction licenseSuggestCodeAction
9091
, mkPluginHandler LSP.SMethod_TextDocumentCompletion $ completion recorder
91-
, mkPluginHandler LSP.SMethod_TextDocumentCodeAction fieldSuggestCodeAction
92+
, mkPluginHandler LSP.SMethod_TextDocumentCodeAction $ fieldSuggestCodeAction recorder
9293
]
9394
, pluginNotificationHandlers =
9495
mconcat
@@ -229,9 +230,37 @@ licenseSuggestCodeAction :: PluginMethodHandler IdeState 'LSP.Method_TextDocumen
229230
licenseSuggestCodeAction _ _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range CodeActionContext{_diagnostics=diags}) =
230231
pure $ InL $ diags >>= (fmap InR . LicenseSuggest.licenseErrorAction uri)
231232

232-
fieldSuggestCodeAction :: PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
233-
fieldSuggestCodeAction _ _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range CodeActionContext{_diagnostics=diags}) =
234-
pure $ InL $ diags >>= (fmap InR . FieldSuggest.fieldErrorAction uri)
233+
-- | CodeActions for correcting field names with typos in them.
234+
--
235+
-- Provides CodeActions that fix typos in field names, in both stanzas and top-level field names.
236+
-- The suggestions are computed based on the completion context, where we "move" a fake cursor
237+
-- to the end of the field name and trigger cabal file completions. The completions are then
238+
-- suggested to the user.
239+
fieldSuggestCodeAction :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
240+
fieldSuggestCodeAction recorder ide _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _ CodeActionContext{_diagnostics=diags}) = do
241+
vfileM <- lift (pluginGetVirtualFile $ toNormalizedUri uri)
242+
case (,) <$> vfileM <*> uriToFilePath' uri of
243+
Nothing -> pure $ InL []
244+
Just (vfile, path) -> do
245+
-- We decide on `useWithStale` here, since `useWithStaleFast` often leads to the wrong completions being suggested.
246+
-- In case it fails, we still will get some completion results instead of an error.
247+
mFields <- liftIO $ runAction "cabal-plugin.fields" ide $ useWithStale ParseCabalFields $ toNormalizedFilePath path
248+
case mFields of
249+
Nothing ->
250+
pure $ InL []
251+
Just (cabalFields, _) -> do
252+
let fields = mapMaybe FieldSuggest.fieldErrorName diags
253+
results <- forM fields (getSuggestion vfile path cabalFields)
254+
pure $ InL $ map InR $ concat results
255+
where
256+
getSuggestion vfile fp cabalFields (fieldName,Diagnostic{ _range=_range@(Range (Position lineNr col) _) }) = do
257+
let -- Compute where we would anticipate the cursor to be.
258+
fakeLspCursorPosition = Position lineNr (col + fromIntegral (T.length fieldName))
259+
lspPrefixInfo = Ghcide.getCompletionPrefix fakeLspCursorPosition vfile
260+
cabalPrefixInfo = Completions.getCabalPrefixInfo fp lspPrefixInfo
261+
completions <- liftIO $ computeCompletionsAt recorder ide cabalPrefixInfo fp cabalFields
262+
let completionTexts = fmap (^. JL.label) completions
263+
pure $ FieldSuggest.fieldErrorAction uri fieldName completionTexts _range
235264

236265
-- ----------------------------------------------------------------
237266
-- Cabal file of Interest rules and global variable
@@ -314,7 +343,7 @@ deleteFileOfInterest recorder state f = do
314343

315344
completion :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCompletion
316345
completion recorder ide _ complParams = do
317-
let (TextDocumentIdentifier uri) = complParams ^. JL.textDocument
346+
let TextDocumentIdentifier uri = complParams ^. JL.textDocument
318347
position = complParams ^. JL.position
319348
mVf <- lift $ pluginGetVirtualFile $ toNormalizedUri uri
320349
case (,) <$> mVf <*> uriToFilePath' uri of
@@ -326,36 +355,35 @@ completion recorder ide _ complParams = do
326355
Nothing ->
327356
pure . InR $ InR Null
328357
Just (fields, _) -> do
329-
let pref = Ghcide.getCompletionPrefix position cnts
330-
let res = produceCompletions pref path fields
358+
let lspPrefInfo = Ghcide.getCompletionPrefix position cnts
359+
cabalPrefInfo = Completions.getCabalPrefixInfo path lspPrefInfo
360+
let res = computeCompletionsAt recorder ide cabalPrefInfo path fields
331361
liftIO $ fmap InL res
332362
Nothing -> pure . InR $ InR Null
333-
where
334-
completerRecorder = cmapWithPrio LogCompletions recorder
335-
336-
produceCompletions :: Ghcide.PosPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
337-
produceCompletions prefix fp fields = do
338-
runMaybeT (context fields) >>= \case
339-
Nothing -> pure []
340-
Just ctx -> do
341-
logWith recorder Debug $ LogCompletionContext ctx pos
342-
let completer = Completions.contextToCompleter ctx
343-
let completerData = CompleterTypes.CompleterData
344-
{ getLatestGPD = do
345-
-- We decide on useWithStaleFast here, since we mostly care about the file's meta information,
346-
-- thus, a quick response gives us the desired result most of the time.
347-
-- The `withStale` option is very important here, since we often call this rule with invalid cabal files.
348-
mGPD <- runIdeAction "cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast ParseCabalFile $ toNormalizedFilePath fp
349-
pure $ fmap fst mGPD
350-
, cabalPrefixInfo = prefInfo
351-
, stanzaName =
352-
case fst ctx of
353-
Types.Stanza _ name -> name
354-
_ -> Nothing
355-
}
356-
completions <- completer completerRecorder completerData
357-
pure completions
358-
where
359-
pos = Ghcide.cursorPos prefix
363+
364+
computeCompletionsAt :: Recorder (WithPriority Log) -> IdeState -> Types.CabalPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
365+
computeCompletionsAt recorder ide prefInfo fp fields = do
366+
runMaybeT (context fields) >>= \case
367+
Nothing -> pure []
368+
Just ctx -> do
369+
logWith recorder Debug $ LogCompletionContext ctx pos
370+
let completer = Completions.contextToCompleter ctx
371+
let completerData = CompleterTypes.CompleterData
372+
{ getLatestGPD = do
373+
-- We decide on useWithStaleFast here, since we mostly care about the file's meta information,
374+
-- thus, a quick response gives us the desired result most of the time.
375+
-- The `withStale` option is very important here, since we often call this rule with invalid cabal files.
376+
mGPD <- runAction "cabal-plugin.modulesCompleter.gpd" ide $ useWithStale ParseCabalFile $ toNormalizedFilePath fp
377+
pure $ fmap fst mGPD
378+
, cabalPrefixInfo = prefInfo
379+
, stanzaName =
380+
case fst ctx of
381+
Types.Stanza _ name -> name
382+
_ -> Nothing
383+
}
384+
completions <- completer completerRecorder completerData
385+
pure completions
386+
where
387+
pos = Types.completionCursorPosition prefInfo
360388
context fields = Completions.getContext completerRecorder prefInfo fields
361-
prefInfo = Completions.getCabalPrefixInfo fp prefix
389+
completerRecorder = cmapWithPrio LogCompletions recorder

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/FieldSuggest.hs

Lines changed: 37 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -3,65 +3,65 @@
33
{-# LANGUAGE FlexibleContexts #-}
44
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE OverloadedStrings #-}
6+
67
module Ide.Plugin.Cabal.FieldSuggest
7-
( fieldErrorSuggestion
8-
, fieldErrorAction
9-
-- * Re-exports
10-
, T.Text
11-
, Diagnostic(..)
12-
)
8+
( fieldErrorName,
9+
fieldErrorAction,
10+
-- * Re-exports
11+
T.Text,
12+
Diagnostic (..),
13+
)
1314
where
1415

1516
import qualified Data.Map.Strict as Map
1617
import qualified Data.Text as T
17-
import Language.LSP.Protocol.Types (CodeAction (CodeAction),
18+
import Language.LSP.Protocol.Types (CodeAction (..),
1819
CodeActionKind (..),
19-
Diagnostic (..),
20-
Position (Position),
21-
Range (Range),
22-
TextEdit (TextEdit), Uri,
23-
WorkspaceEdit (WorkspaceEdit))
20+
Diagnostic (..), Position (..),
21+
Range (..), TextEdit (..), Uri,
22+
WorkspaceEdit (..))
2423
import Text.Regex.TDFA
2524

26-
-- | Given a diagnostic returned by 'Ide.Plugin.Cabal.Diag.errorDiagnostic',
27-
-- if it represents an "Unknown field"-error along
28-
-- with a incorrect field, then return a 'CodeAction' for replacing the
29-
-- the incorrect field with the suggestion.
30-
-- It should be context sensitive, but for now it isn't
25+
-- | Generate all code action for given file, error field in position and suggestions
3126
fieldErrorAction
3227
:: Uri
3328
-- ^ File for which the diagnostic was generated
34-
-> Diagnostic
35-
-- ^ Output of 'Ide.Plugin.Cabal.Diag.errorDiagnostic'
36-
-> [CodeAction]
37-
fieldErrorAction uri diag =
38-
mkCodeAction <$> fieldErrorSuggestion diag
29+
-> T.Text
30+
-- ^ Original field
31+
-> [T.Text]
32+
-- ^ Suggestions
33+
-> Range
34+
-- ^ Location of diagnostic
35+
-> [CodeAction]
36+
fieldErrorAction uri original suggestions range =
37+
fmap mkCodeAction suggestions
3938
where
40-
mkCodeAction (original, suggestion) =
39+
mkCodeAction suggestion =
4140
let
4241
-- Range returned by cabal here represents fragment from start of
4342
-- offending identifier to end of line, we modify it to the end of identifier
44-
adjustRange (Range rangeFrom@(Position line col) _) =
45-
Range rangeFrom (Position line (col + fromIntegral (T.length original)))
46-
title = "Replace with " <> suggestion
47-
tedit = [TextEdit (adjustRange $ _range diag) suggestion]
43+
adjustRange (Range rangeFrom@(Position lineNr col) _) =
44+
Range rangeFrom (Position lineNr (col + fromIntegral (T.length original)))
45+
title = "Replace with " <> suggestion'
46+
tedit = [TextEdit (adjustRange range ) suggestion']
4847
edit = WorkspaceEdit (Just $ Map.singleton uri tedit) Nothing Nothing
4948
in CodeAction title (Just CodeActionKind_QuickFix) (Just []) Nothing Nothing (Just edit) Nothing Nothing
49+
where
50+
-- dropping colon from the end of suggestion
51+
suggestion' = T.dropEnd 1 suggestion
5052

5153
-- | Given a diagnostic returned by 'Ide.Plugin.Cabal.Diag.errorDiagnostic',
5254
-- if it represents an "Unknown field"- error with incorrect identifier
53-
-- then return the suggestion (for now placeholder "name")
54-
-- along with the incorrect identifier.
55-
--
56-
fieldErrorSuggestion
57-
:: Diagnostic
55+
-- then return the incorrect identifier together with original diagnostics.
56+
fieldErrorName ::
57+
Diagnostic ->
5858
-- ^ Output of 'Ide.Plugin.Cabal.Diag.errorDiagnostic'
59-
-> [(T.Text, T.Text)]
60-
-- ^ (Original (incorrect) license identifier, suggested replacement)
61-
fieldErrorSuggestion diag =
59+
Maybe (T.Text, Diagnostic)
60+
-- ^ Original (incorrect) field name with the suggested replacement
61+
fieldErrorName diag =
6262
mSuggestion (_message diag) >>= \case
63-
[original] -> [(original, "name")]
64-
_ -> []
63+
[original] -> Just (original, diag)
64+
_ -> Nothing
6565
where
6666
regex :: T.Text
6767
regex = "Unknown field: \"(.*)\""

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/LicenseSuggest.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ licenseErrorSuggestion ::
7272
T.Text
7373
-- ^ Output of 'Ide.Plugin.Cabal.Diag.errorDiagnostic'
7474
-> [(T.Text, T.Text)]
75-
-- ^ (Original (incorrect) license identifier, suggested replacement)
75+
-- ^ Original (incorrect) license identifier with the suggested replacement
7676
licenseErrorSuggestion msg =
7777
(getMatch <$> msg =~~ regex) >>= \case
7878
[original] ->

0 commit comments

Comments
 (0)