Skip to content

Commit b0e9815

Browse files
dyniecVeryMilkyJoe
authored andcommitted
Use context in code actions for cabal files
1 parent 881bcc8 commit b0e9815

File tree

2 files changed

+100
-76
lines changed

2 files changed

+100
-76
lines changed

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

+63-39
Original file line numberDiff line numberDiff line change
@@ -19,14 +19,14 @@ import Data.HashMap.Strict (HashMap)
1919
import qualified Data.HashMap.Strict as HashMap
2020
import qualified Data.List.NonEmpty as NE
2121
import qualified Data.Maybe as Maybe
22+
import qualified Data.Text as T
2223
import qualified Data.Text.Encoding as Encoding
2324
import Data.Typeable
2425
import Development.IDE as D
2526
import Development.IDE.Core.Shake (restartShakeSession)
2627
import qualified Development.IDE.Core.Shake as Shake
2728
import Development.IDE.Graph (Key, alwaysRerun)
2829
import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
29-
import qualified Development.IDE.Plugin.Completions.Types as Ghcide
3030
import Development.IDE.Types.Shake (toKey)
3131
import qualified Distribution.Fields as Syntax
3232
import qualified Distribution.Parsec.Position as Syntax
@@ -90,7 +90,7 @@ descriptor recorder plId =
9090
mconcat
9191
[ mkPluginHandler LSP.SMethod_TextDocumentCodeAction licenseSuggestCodeAction
9292
, mkPluginHandler LSP.SMethod_TextDocumentCompletion $ completion recorder
93-
, mkPluginHandler LSP.SMethod_TextDocumentCodeAction fieldSuggestCodeAction
93+
, mkPluginHandler LSP.SMethod_TextDocumentCodeAction $ fieldSuggestCodeAction recorder
9494
]
9595
, pluginNotificationHandlers =
9696
mconcat
@@ -240,9 +240,37 @@ licenseSuggestCodeAction ideState _ (CodeActionParams _ _ (TextDocumentIdentifie
240240
maxCompls <- fmap maxCompletions . liftIO $ runAction "cabal-plugin.suggestLicense" ideState getClientConfigAction
241241
pure $ InL $ diags >>= (fmap InR . LicenseSuggest.licenseErrorAction maxCompls uri)
242242

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

247275
-- ----------------------------------------------------------------
248276
-- Cabal file of Interest rules and global variable
@@ -325,7 +353,7 @@ deleteFileOfInterest recorder state f = do
325353

326354
completion :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCompletion
327355
completion recorder ide _ complParams = do
328-
let (TextDocumentIdentifier uri) = complParams ^. JL.textDocument
356+
let TextDocumentIdentifier uri = complParams ^. JL.textDocument
329357
position = complParams ^. JL.position
330358
mVf <- lift $ pluginGetVirtualFile $ toNormalizedUri uri
331359
case (,) <$> mVf <*> uriToFilePath' uri of
@@ -337,39 +365,35 @@ completion recorder ide _ complParams = do
337365
Nothing ->
338366
pure . InR $ InR Null
339367
Just (fields, _) -> do
340-
let pref = Ghcide.getCompletionPrefix position cnts
341-
let res = produceCompletions pref path fields
368+
let lspPrefInfo = Ghcide.getCompletionPrefix position cnts
369+
cabalPrefInfo = Completions.getCabalPrefixInfo path lspPrefInfo
370+
let res = computeCompletionsAt recorder ide cabalPrefInfo path fields
342371
liftIO $ fmap InL res
343372
Nothing -> pure . InR $ InR Null
344-
where
345-
completerRecorder = cmapWithPrio LogCompletions recorder
346-
347-
produceCompletions :: Ghcide.PosPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
348-
produceCompletions prefix fp fields = do
349-
runMaybeT (context fields) >>= \case
350-
Nothing -> pure []
351-
Just ctx -> do
352-
logWith recorder Debug $ LogCompletionContext ctx pos
353-
let completer = Completions.contextToCompleter ctx
354-
let completerData = CompleterTypes.CompleterData
355-
{ getLatestGPD = do
356-
-- We decide on useWithStaleFast here, since we mostly care about the file's meta information,
357-
-- thus, a quick response gives us the desired result most of the time.
358-
-- The `withStale` option is very important here, since we often call this rule with invalid cabal files.
359-
mGPD <- runIdeAction "cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast ParseCabalFile $ toNormalizedFilePath fp
360-
pure $ fmap fst mGPD
361-
, getCabalCommonSections = do
362-
mSections <- runIdeAction "cabal-plugin.modulesCompleter.commonsections" (shakeExtras ide) $ useWithStaleFast ParseCabalCommonSections $ toNormalizedFilePath fp
363-
pure $ fmap fst mSections
364-
, cabalPrefixInfo = prefInfo
365-
, stanzaName =
366-
case fst ctx of
367-
Types.Stanza _ name -> name
368-
_ -> Nothing
369-
}
370-
completions <- completer completerRecorder completerData
371-
pure completions
372-
where
373-
pos = Ghcide.cursorPos prefix
373+
374+
computeCompletionsAt :: Recorder (WithPriority Log) -> IdeState -> Types.CabalPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
375+
computeCompletionsAt recorder ide prefInfo fp fields = do
376+
runMaybeT (context fields) >>= \case
377+
Nothing -> pure []
378+
Just ctx -> do
379+
logWith recorder Debug $ LogCompletionContext ctx pos
380+
let completer = Completions.contextToCompleter ctx
381+
let completerData = CompleterTypes.CompleterData
382+
{ getLatestGPD = do
383+
-- We decide on useWithStaleFast here, since we mostly care about the file's meta information,
384+
-- thus, a quick response gives us the desired result most of the time.
385+
-- The `withStale` option is very important here, since we often call this rule with invalid cabal files.
386+
mGPD <- runAction "cabal-plugin.modulesCompleter.gpd" ide $ useWithStale ParseCabalFile $ toNormalizedFilePath fp
387+
pure $ fmap fst mGPD
388+
, cabalPrefixInfo = prefInfo
389+
, stanzaName =
390+
case fst ctx of
391+
Types.Stanza _ name -> name
392+
_ -> Nothing
393+
}
394+
completions <- completer completerRecorder completerData
395+
pure completions
396+
where
397+
pos = Types.completionCursorPosition prefInfo
374398
context fields = Completions.getContext completerRecorder prefInfo fields
375-
prefInfo = Completions.getCabalPrefixInfo fp prefix
399+
completerRecorder = cmapWithPrio LogCompletions recorder

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

+37-37
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: \"(.*)\""

0 commit comments

Comments
 (0)