Skip to content

Commit

Permalink
Add Inline code action to Retrie plugin (#3444)
Browse files Browse the repository at this point in the history
  • Loading branch information
pepeiborra authored Jan 29, 2023
1 parent 00f4e61 commit 2b691b6
Show file tree
Hide file tree
Showing 33 changed files with 645 additions and 155 deletions.
4 changes: 4 additions & 0 deletions .github/workflows/test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -259,6 +259,10 @@ jobs:
name: Test hls-cabal-plugin test suite
run: cabal test hls-cabal-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-cabal-plugin --test-options="$TEST_OPTS"

- if: matrix.test
name: Test hls-retrie-plugin test suite
run: cabal test hls-retrie-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-retrie-plugin --test-options="$TEST_OPTS"

test_post_job:
if: always()
runs-on: ubuntu-latest
Expand Down
1 change: 1 addition & 0 deletions ghcide/src/Development/IDE/Core/Actions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Development.IDE.Core.Actions
, useNoFileE
, usesE
, workspaceSymbols
, lookupMod
) where

import Control.Monad.Reader
Expand Down
7 changes: 5 additions & 2 deletions ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -315,7 +315,7 @@ getShakeExtrasRules :: Rules ShakeExtras
getShakeExtrasRules = do
mExtras <- getShakeExtraRules @ShakeExtras
case mExtras of
Just x -> return x
Just x -> return x
-- This will actually crash HLS
Nothing -> liftIO $ fail "missing ShakeExtras"

Expand Down Expand Up @@ -982,7 +982,10 @@ usesWithStale_ key files = do
--
-- Run via 'runIdeAction'.
newtype IdeAction a = IdeAction { runIdeActionT :: (ReaderT ShakeExtras IO) a }
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad)
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad, Semigroup)

-- https://hub.darcs.net/ross/transformers/issue/86
deriving instance (Semigroup (m a)) => Semigroup (ReaderT r m a)

runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
runIdeAction _herald s i = runReaderT (runIdeActionT i) s
Expand Down
2 changes: 2 additions & 0 deletions ghcide/src/Development/IDE/GHC/Compat/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -447,6 +447,7 @@ module Development.IDE.GHC.Compat.Core (
-- * Syntax re-exports
#if MIN_VERSION_ghc(9,0,0)
module GHC.Hs,
module GHC.Hs.Binds,
module GHC.Parser,
module GHC.Parser.Header,
module GHC.Parser.Lexer,
Expand Down Expand Up @@ -786,6 +787,7 @@ import qualified Finder as GHC
-- (until the CPP extension is actually needed).
import GHC.LanguageExtensions.Type hiding (Cpp)

import GHC.Hs.Binds

mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO Module.ModLocation
#if MIN_VERSION_ghc(9,3,0)
Expand Down
2 changes: 2 additions & 0 deletions ghcide/src/Development/IDE/Spans/AtPoint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ module Development.IDE.Spans.AtPoint (
, getNamesAtPoint
, toCurrentLocation
, rowToLoc
, nameToLocation
, LookupModule
) where

import Development.IDE.GHC.Error
Expand Down
18 changes: 9 additions & 9 deletions hls-test-utils/src/Test/Hls.hs
Original file line number Diff line number Diff line change
Expand Up @@ -176,7 +176,7 @@ goldenWithDoc fileType plugin title testDataDir path desc ext act =
-- ------------------------------------------------------------

-- | Plugin under test where a fitting recorder is injected.
type PluginTestDescriptor b = Recorder (WithPriority b) -> PluginDescriptor IdeState
type PluginTestDescriptor b = Recorder (WithPriority b) -> IdePlugins IdeState

-- | Wrap a plugin you want to test, and inject a fitting recorder as required.
--
Expand All @@ -197,7 +197,7 @@ mkPluginTestDescriptor
:: (Recorder (WithPriority b) -> PluginId -> PluginDescriptor IdeState)
-> PluginId
-> PluginTestDescriptor b
mkPluginTestDescriptor pluginDesc plId recorder = pluginDesc recorder plId
mkPluginTestDescriptor pluginDesc plId recorder = IdePlugins [pluginDesc recorder plId]

-- | Wrap a plugin you want to test.
--
Expand All @@ -207,7 +207,7 @@ mkPluginTestDescriptor'
:: (PluginId -> PluginDescriptor IdeState)
-> PluginId
-> PluginTestDescriptor b
mkPluginTestDescriptor' pluginDesc plId _recorder = pluginDesc plId
mkPluginTestDescriptor' pluginDesc plId _recorder = IdePlugins [pluginDesc plId]

-- | Initialise a recorder that can be instructed to write to stderr by
-- setting the environment variable "HLS_TEST_PLUGIN_LOG_STDERR=1" before
Expand Down Expand Up @@ -260,18 +260,18 @@ initialiseTestRecorder envVars = do
runSessionWithServer :: Pretty b => PluginTestDescriptor b -> FilePath -> Session a -> IO a
runSessionWithServer plugin fp act = do
recorder <- pluginTestRecorder
runSessionWithServer' [plugin recorder] def def fullCaps fp act
runSessionWithServer' (plugin recorder) def def fullCaps fp act

runSessionWithServerAndCaps :: Pretty b => PluginTestDescriptor b -> ClientCapabilities -> FilePath -> Session a -> IO a
runSessionWithServerAndCaps plugin caps fp act = do
recorder <- pluginTestRecorder
runSessionWithServer' [plugin recorder] def def caps fp act
runSessionWithServer' (plugin recorder) def def caps fp act

runSessionWithServerFormatter :: Pretty b => PluginTestDescriptor b -> String -> PluginConfig -> FilePath -> Session a -> IO a
runSessionWithServerFormatter plugin formatter conf fp act = do
recorder <- pluginTestRecorder
runSessionWithServer'
[plugin recorder]
(plugin recorder)
def
{ formattingProvider = T.pack formatter
, plugins = M.singleton (PluginId $ T.pack formatter) conf
Expand Down Expand Up @@ -329,7 +329,7 @@ runSessionWithCabalServerFormatter :: Pretty b => PluginTestDescriptor b -> Stri
runSessionWithCabalServerFormatter plugin formatter conf fp act = do
recorder <- pluginTestRecorder
runSessionWithServer'
[plugin recorder]
(plugin recorder)
def
{ cabalFormattingProvider = T.pack formatter
, plugins = M.singleton (PluginId $ T.pack formatter) conf
Expand All @@ -354,7 +354,7 @@ runSessionWithServer' ::
--
-- For improved logging, make sure these plugins have been initalised with
-- the recorder produced by @pluginTestRecorder@.
[PluginDescriptor IdeState] ->
IdePlugins IdeState ->
-- | lsp config for the server
Config ->
-- | config for the test session
Expand All @@ -380,7 +380,7 @@ runSessionWithServer' plugins conf sconf caps root s = withLock lock $ keepCurre
-- exists until old logging style is phased out
logger = Logger $ \p m -> logger_ (WithPriority p emptyCallStack (pretty m))

hlsPlugins = IdePlugins $ Test.blockCommandDescriptor "block-command" : plugins
hlsPlugins = IdePlugins [Test.blockCommandDescriptor "block-command"] <> plugins

arguments@Arguments{ argsIdeOptions, argsLogger } =
testing (cmapWithPrio LogIDEMain recorder) logger hlsPlugins
Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-call-hierarchy-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,10 +12,10 @@ import Data.Functor ((<&>))
import Data.List (sort, tails)
import qualified Data.Map as M
import qualified Data.Text as T
import Development.IDE.Test
import Ide.Plugin.CallHierarchy
import qualified Language.LSP.Test as Test
import qualified Language.LSP.Types.Lens as L
import Development.IDE.Test
import System.Directory.Extra
import System.FilePath
import qualified System.IO.Extra
Expand Down
1 change: 1 addition & 0 deletions plugins/hls-eval-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import qualified Ide.Plugin.Config as Plugin
import qualified Ide.Plugin.Eval as Eval
import Ide.Plugin.Eval.Types (EvalParams (..), Section (..),
testOutput)
import Ide.Types (IdePlugins (IdePlugins))
import Language.LSP.Types.Lens (arguments, command, range, title)
import System.FilePath ((</>))
import Test.Hls
Expand Down
4 changes: 2 additions & 2 deletions plugins/hls-refactor-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,11 +64,11 @@ import qualified Test.AddArgument
main :: IO ()
main = defaultTestRunner tests

refactorPlugin :: IO [PluginDescriptor IdeState]
refactorPlugin :: IO (IdePlugins IdeState)
refactorPlugin = do
exactprintLog <- pluginTestRecorder
ghcideLog <- pluginTestRecorder
pure $
pure $ IdePlugins $
[ Refactor.iePluginDescriptor exactprintLog "ghcide-code-actions-imports-exports"
, Refactor.typeSigsPluginDescriptor exactprintLog "ghcide-code-actions-type-signatures"
, Refactor.bindingsPluginDescriptor exactprintLog "ghcide-code-actions-bindings"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,19 @@ import Ide.Plugin.ExplicitImports (extractMinimalImports,
import Ide.PluginUtils (mkLspCommand)
import Ide.Types
import Language.LSP.Server
import Language.LSP.Types
import Language.LSP.Types (ApplyWorkspaceEditParams (ApplyWorkspaceEditParams),
CodeAction (CodeAction, _command, _diagnostics, _disabled, _edit, _isPreferred, _kind, _title, _xdata),
CodeActionKind (CodeActionUnknown),
CodeActionParams (CodeActionParams),
CodeLens (..),
CodeLensParams (CodeLensParams, _textDocument),
Method (TextDocumentCodeAction, TextDocumentCodeLens),
SMethod (STextDocumentCodeAction, STextDocumentCodeLens, SWorkspaceApplyEdit),
TextDocumentIdentifier (TextDocumentIdentifier, _uri),
TextEdit (..),
WorkspaceEdit (..),
type (|?) (InR),
uriToNormalizedFilePath)

newtype Log = LogShake Shake.Log deriving Show

Expand Down
1 change: 1 addition & 0 deletions plugins/hls-rename-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ import Data.Aeson
import qualified Data.Map as M
import Ide.Plugin.Config
import qualified Ide.Plugin.Rename as Rename
import Ide.Types (IdePlugins (IdePlugins))
import System.FilePath
import Test.Hls

Expand Down
19 changes: 19 additions & 0 deletions plugins/hls-retrie-plugin/hls-retrie-plugin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ library
, ghcide ^>=1.9
, hashable
, hls-plugin-api ^>=1.6
, hls-refactor-plugin
, lsp
, lsp-types
, retrie >=0.1.1.0
Expand All @@ -46,3 +47,21 @@ library
TypeOperators

ghc-options: -Wno-unticked-promoted-constructors

test-suite tests
buildable: True
type: exitcode-stdio-1.0
default-language: Haskell2010
hs-source-dirs: test
main-is: Main.hs
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
, aeson
, base
, containers
, filepath
, hls-plugin-api
, hls-refactor-plugin
, hls-retrie-plugin
, hls-test-utils ^>=1.5
, text
Loading

0 comments on commit 2b691b6

Please sign in to comment.