Skip to content

Commit

Permalink
Merge remote-tracking branch 'upstream/master' into inlay-hints-recor…
Browse files Browse the repository at this point in the history
…d-wildcards
  • Loading branch information
jetjinser committed Jul 16, 2024
2 parents f229b81 + ce486f7 commit 6a51da6
Show file tree
Hide file tree
Showing 7 changed files with 296 additions and 85 deletions.
2 changes: 2 additions & 0 deletions haskell-language-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -242,6 +242,7 @@ library hls-cabal-plugin
Ide.Plugin.Cabal.Completion.Completions
Ide.Plugin.Cabal.Completion.Data
Ide.Plugin.Cabal.Completion.Types
Ide.Plugin.Cabal.FieldSuggest
Ide.Plugin.Cabal.LicenseSuggest
Ide.Plugin.Cabal.Orphans
Ide.Plugin.Cabal.Parse
Expand Down Expand Up @@ -285,6 +286,7 @@ test-suite hls-cabal-plugin-tests
, base
, bytestring
, Cabal-syntax >= 3.7
, extra
, filepath
, ghcide
, haskell-language-server:hls-cabal-plugin
Expand Down
104 changes: 69 additions & 35 deletions plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,14 +19,14 @@ import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List.NonEmpty as NE
import qualified Data.Maybe as Maybe
import qualified Data.Text as T
import qualified Data.Text.Encoding as Encoding
import Data.Typeable
import Development.IDE as D
import Development.IDE.Core.Shake (restartShakeSession)
import qualified Development.IDE.Core.Shake as Shake
import Development.IDE.Graph (Key, alwaysRerun)
import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
import qualified Development.IDE.Plugin.Completions.Types as Ghcide
import Development.IDE.Types.Shake (toKey)
import qualified Distribution.Fields as Syntax
import qualified Distribution.Parsec.Position as Syntax
Expand All @@ -38,6 +38,7 @@ import Ide.Plugin.Cabal.Completion.Types (ParseCabalCommonSe
ParseCabalFile (..))
import qualified Ide.Plugin.Cabal.Completion.Types as Types
import qualified Ide.Plugin.Cabal.Diagnostics as Diagnostics
import qualified Ide.Plugin.Cabal.FieldSuggest as FieldSuggest
import qualified Ide.Plugin.Cabal.LicenseSuggest as LicenseSuggest
import Ide.Plugin.Cabal.Orphans ()
import qualified Ide.Plugin.Cabal.Parse as Parse
Expand Down Expand Up @@ -89,6 +90,7 @@ descriptor recorder plId =
mconcat
[ mkPluginHandler LSP.SMethod_TextDocumentCodeAction licenseSuggestCodeAction
, mkPluginHandler LSP.SMethod_TextDocumentCompletion $ completion recorder
, mkPluginHandler LSP.SMethod_TextDocumentCodeAction $ fieldSuggestCodeAction recorder
]
, pluginNotificationHandlers =
mconcat
Expand Down Expand Up @@ -238,6 +240,41 @@ licenseSuggestCodeAction ideState _ (CodeActionParams _ _ (TextDocumentIdentifie
maxCompls <- fmap maxCompletions . liftIO $ runAction "cabal-plugin.suggestLicense" ideState getClientConfigAction
pure $ InL $ diags >>= (fmap InR . LicenseSuggest.licenseErrorAction maxCompls uri)

-- | CodeActions for correcting field names with typos in them.
--
-- Provides CodeActions that fix typos in both stanzas and top-level field names.
-- The suggestions are computed based on the completion context, where we "move" a fake cursor
-- to the end of the field name and trigger cabal file completions. The completions are then
-- suggested to the user.
--
-- TODO: Relying on completions here often does not produce the desired results, we should
-- use some sort of fuzzy matching in the future, see issue #4357.
fieldSuggestCodeAction :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
fieldSuggestCodeAction recorder ide _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _ CodeActionContext{_diagnostics=diags}) = do
vfileM <- lift (pluginGetVirtualFile $ toNormalizedUri uri)
case (,) <$> vfileM <*> uriToFilePath' uri of
Nothing -> pure $ InL []
Just (vfile, path) -> do
-- We decide on `useWithStale` here, since `useWithStaleFast` often leads to the wrong completions being suggested.
-- In case it fails, we still will get some completion results instead of an error.
mFields <- liftIO $ runAction "cabal-plugin.fields" ide $ useWithStale ParseCabalFields $ toNormalizedFilePath path
case mFields of
Nothing ->
pure $ InL []
Just (cabalFields, _) -> do
let fields = Maybe.mapMaybe FieldSuggest.fieldErrorName diags
results <- forM fields (getSuggestion vfile path cabalFields)
pure $ InL $ map InR $ concat results
where
getSuggestion vfile fp cabalFields (fieldName,Diagnostic{ _range=_range@(Range (Position lineNr col) _) }) = do
let -- Compute where we would anticipate the cursor to be.
fakeLspCursorPosition = Position lineNr (col + fromIntegral (T.length fieldName))
lspPrefixInfo = Ghcide.getCompletionPrefix fakeLspCursorPosition vfile
cabalPrefixInfo = Completions.getCabalPrefixInfo fp lspPrefixInfo
completions <- liftIO $ computeCompletionsAt recorder ide cabalPrefixInfo fp cabalFields
let completionTexts = fmap (^. JL.label) completions
pure $ FieldSuggest.fieldErrorAction uri fieldName completionTexts _range

-- ----------------------------------------------------------------
-- Cabal file of Interest rules and global variable
-- ----------------------------------------------------------------
Expand Down Expand Up @@ -319,7 +356,7 @@ deleteFileOfInterest recorder state f = do

completion :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCompletion
completion recorder ide _ complParams = do
let (TextDocumentIdentifier uri) = complParams ^. JL.textDocument
let TextDocumentIdentifier uri = complParams ^. JL.textDocument
position = complParams ^. JL.position
mVf <- lift $ pluginGetVirtualFile $ toNormalizedUri uri
case (,) <$> mVf <*> uriToFilePath' uri of
Expand All @@ -331,39 +368,36 @@ completion recorder ide _ complParams = do
Nothing ->
pure . InR $ InR Null
Just (fields, _) -> do
let pref = Ghcide.getCompletionPrefix position cnts
let res = produceCompletions pref path fields
let lspPrefInfo = Ghcide.getCompletionPrefix position cnts
cabalPrefInfo = Completions.getCabalPrefixInfo path lspPrefInfo
let res = computeCompletionsAt recorder ide cabalPrefInfo path fields
liftIO $ fmap InL res
Nothing -> pure . InR $ InR Null
where
completerRecorder = cmapWithPrio LogCompletions recorder

produceCompletions :: Ghcide.PosPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
produceCompletions prefix fp fields = do
runMaybeT (context fields) >>= \case
Nothing -> pure []
Just ctx -> do
logWith recorder Debug $ LogCompletionContext ctx pos
let completer = Completions.contextToCompleter ctx
let completerData = CompleterTypes.CompleterData
{ getLatestGPD = do
-- We decide on useWithStaleFast here, since we mostly care about the file's meta information,
-- thus, a quick response gives us the desired result most of the time.
-- The `withStale` option is very important here, since we often call this rule with invalid cabal files.
mGPD <- runIdeAction "cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast ParseCabalFile $ toNormalizedFilePath fp
pure $ fmap fst mGPD
, getCabalCommonSections = do
mSections <- runIdeAction "cabal-plugin.modulesCompleter.commonsections" (shakeExtras ide) $ useWithStaleFast ParseCabalCommonSections $ toNormalizedFilePath fp
pure $ fmap fst mSections
, cabalPrefixInfo = prefInfo
, stanzaName =
case fst ctx of
Types.Stanza _ name -> name
_ -> Nothing
}
completions <- completer completerRecorder completerData
pure completions
where
pos = Ghcide.cursorPos prefix

computeCompletionsAt :: Recorder (WithPriority Log) -> IdeState -> Types.CabalPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
computeCompletionsAt recorder ide prefInfo fp fields = do
runMaybeT (context fields) >>= \case
Nothing -> pure []
Just ctx -> do
logWith recorder Debug $ LogCompletionContext ctx pos
let completer = Completions.contextToCompleter ctx
let completerData = CompleterTypes.CompleterData
{ getLatestGPD = do
-- We decide on useWithStaleFast here, since we mostly care about the file's meta information,
-- thus, a quick response gives us the desired result most of the time.
-- The `withStale` option is very important here, since we often call this rule with invalid cabal files.
mGPD <- runAction "cabal-plugin.modulesCompleter.gpd" ide $ useWithStale ParseCabalFile $ toNormalizedFilePath fp
pure $ fmap fst mGPD
, getCabalCommonSections = runAction "cabal-plugin.commonSections" ide $ use ParseCabalCommonSections $ toNormalizedFilePath fp
, cabalPrefixInfo = prefInfo
, stanzaName =
case fst ctx of
Types.Stanza _ name -> name
_ -> Nothing
}
completions <- completer completerRecorder completerData
pure completions
where
pos = Types.completionCursorPosition prefInfo
context fields = Completions.getContext completerRecorder prefInfo fields
prefInfo = Completions.getCabalPrefixInfo fp prefix
completerRecorder = cmapWithPrio LogCompletions recorder
70 changes: 70 additions & 0 deletions plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/FieldSuggest.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

module Ide.Plugin.Cabal.FieldSuggest
( fieldErrorName,
fieldErrorAction,
-- * Re-exports
T.Text,
Diagnostic (..),
)
where

import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import Language.LSP.Protocol.Types (CodeAction (..),
CodeActionKind (..),
Diagnostic (..), Position (..),
Range (..), TextEdit (..), Uri,
WorkspaceEdit (..))
import Text.Regex.TDFA

-- | Generate all code actions for given file, erroneous/unknown field and suggestions
fieldErrorAction
:: Uri
-- ^ File for which the diagnostic was generated
-> T.Text
-- ^ Original (unknown) field
-> [T.Text]
-- ^ Suggestions for the given file
-> Range
-- ^ Location of diagnostic
-> [CodeAction]
fieldErrorAction uri original suggestions range =
fmap mkCodeAction suggestions
where
mkCodeAction suggestion =
let
-- Range returned by cabal here represents fragment from start of offending identifier
-- to end of line, we modify this range to be to the end of the identifier
adjustRange (Range rangeFrom@(Position lineNr col) _) =
Range rangeFrom (Position lineNr (col + fromIntegral (T.length original)))
title = "Replace with " <> suggestion'
tedit = [TextEdit (adjustRange range ) suggestion']
edit = WorkspaceEdit (Just $ Map.singleton uri tedit) Nothing Nothing
in CodeAction title (Just CodeActionKind_QuickFix) (Just []) Nothing Nothing (Just edit) Nothing Nothing
where
-- dropping colon from the end of suggestion
suggestion' = T.dropEnd 1 suggestion

-- | Given a diagnostic returned by 'Ide.Plugin.Cabal.Diag.errorDiagnostic',
-- if it represents an "Unknown field"-error with incorrect identifier
-- then return the incorrect identifier together with original diagnostics.
fieldErrorName ::
Diagnostic ->
-- ^ Output of 'Ide.Plugin.Cabal.Diag.errorDiagnostic'
Maybe (T.Text, Diagnostic)
-- ^ Original (incorrect) field name with the suggested replacement
fieldErrorName diag =
mSuggestion (_message diag) >>= \case
[original] -> Just (original, diag)
_ -> Nothing
where
regex :: T.Text
regex = "Unknown field: \"(.*)\""
mSuggestion msg = getMatch <$> (msg :: T.Text) =~~ regex
getMatch :: (T.Text, T.Text, T.Text, [T.Text]) -> [T.Text]
getMatch (_, _, _, results) = results
Loading

0 comments on commit 6a51da6

Please sign in to comment.