Skip to content

Commit a233b43

Browse files
pepeiborrawz1000
authored andcommitted
Add Inline code action to Retrie plugin (#3444)
1 parent b691529 commit a233b43

File tree

33 files changed

+645
-155
lines changed

33 files changed

+645
-155
lines changed

.github/workflows/test.yml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -259,6 +259,10 @@ jobs:
259259
name: Test hls-cabal-plugin test suite
260260
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"
261261

262+
- if: matrix.test
263+
name: Test hls-retrie-plugin test suite
264+
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"
265+
262266
test_post_job:
263267
if: always()
264268
runs-on: ubuntu-latest

ghcide/src/Development/IDE/Core/Actions.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.Core.Actions
1010
, useNoFileE
1111
, usesE
1212
, workspaceSymbols
13+
, lookupMod
1314
) where
1415

1516
import Control.Monad.Reader

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -315,7 +315,7 @@ getShakeExtrasRules :: Rules ShakeExtras
315315
getShakeExtrasRules = do
316316
mExtras <- getShakeExtraRules @ShakeExtras
317317
case mExtras of
318-
Just x -> return x
318+
Just x -> return x
319319
-- This will actually crash HLS
320320
Nothing -> liftIO $ fail "missing ShakeExtras"
321321

@@ -982,7 +982,10 @@ usesWithStale_ key files = do
982982
--
983983
-- Run via 'runIdeAction'.
984984
newtype IdeAction a = IdeAction { runIdeActionT :: (ReaderT ShakeExtras IO) a }
985-
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad)
985+
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad, Semigroup)
986+
987+
-- https://hub.darcs.net/ross/transformers/issue/86
988+
deriving instance (Semigroup (m a)) => Semigroup (ReaderT r m a)
986989

987990
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
988991
runIdeAction _herald s i = runReaderT (runIdeActionT i) s

ghcide/src/Development/IDE/GHC/Compat/Core.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -447,6 +447,7 @@ module Development.IDE.GHC.Compat.Core (
447447
-- * Syntax re-exports
448448
#if MIN_VERSION_ghc(9,0,0)
449449
module GHC.Hs,
450+
module GHC.Hs.Binds,
450451
module GHC.Parser,
451452
module GHC.Parser.Header,
452453
module GHC.Parser.Lexer,
@@ -786,6 +787,7 @@ import qualified Finder as GHC
786787
-- (until the CPP extension is actually needed).
787788
import GHC.LanguageExtensions.Type hiding (Cpp)
788789

790+
import GHC.Hs.Binds
789791

790792
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO Module.ModLocation
791793
#if MIN_VERSION_ghc(9,3,0)

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,8 @@ module Development.IDE.Spans.AtPoint (
2020
, getNamesAtPoint
2121
, toCurrentLocation
2222
, rowToLoc
23+
, nameToLocation
24+
, LookupModule
2325
) where
2426

2527
import Development.IDE.GHC.Error

hls-test-utils/src/Test/Hls.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -176,7 +176,7 @@ goldenWithDoc fileType plugin title testDataDir path desc ext act =
176176
-- ------------------------------------------------------------
177177

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

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

202202
-- | Wrap a plugin you want to test.
203203
--
@@ -207,7 +207,7 @@ mkPluginTestDescriptor'
207207
:: (PluginId -> PluginDescriptor IdeState)
208208
-> PluginId
209209
-> PluginTestDescriptor b
210-
mkPluginTestDescriptor' pluginDesc plId _recorder = pluginDesc plId
210+
mkPluginTestDescriptor' pluginDesc plId _recorder = IdePlugins [pluginDesc plId]
211211

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

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

270270
runSessionWithServerFormatter :: Pretty b => PluginTestDescriptor b -> String -> PluginConfig -> FilePath -> Session a -> IO a
271271
runSessionWithServerFormatter plugin formatter conf fp act = do
272272
recorder <- pluginTestRecorder
273273
runSessionWithServer'
274-
[plugin recorder]
274+
(plugin recorder)
275275
def
276276
{ formattingProvider = T.pack formatter
277277
, plugins = M.singleton (PluginId $ T.pack formatter) conf
@@ -329,7 +329,7 @@ runSessionWithCabalServerFormatter :: Pretty b => PluginTestDescriptor b -> Stri
329329
runSessionWithCabalServerFormatter plugin formatter conf fp act = do
330330
recorder <- pluginTestRecorder
331331
runSessionWithServer'
332-
[plugin recorder]
332+
(plugin recorder)
333333
def
334334
{ cabalFormattingProvider = T.pack formatter
335335
, plugins = M.singleton (PluginId $ T.pack formatter) conf
@@ -354,7 +354,7 @@ runSessionWithServer' ::
354354
--
355355
-- For improved logging, make sure these plugins have been initalised with
356356
-- the recorder produced by @pluginTestRecorder@.
357-
[PluginDescriptor IdeState] ->
357+
IdePlugins IdeState ->
358358
-- | lsp config for the server
359359
Config ->
360360
-- | config for the test session
@@ -380,7 +380,7 @@ runSessionWithServer' plugins conf sconf caps root s = withLock lock $ keepCurre
380380
-- exists until old logging style is phased out
381381
logger = Logger $ \p m -> logger_ (WithPriority p emptyCallStack (pretty m))
382382

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

385385
arguments@Arguments{ argsIdeOptions, argsLogger } =
386386
testing (cmapWithPrio LogIDEMain recorder) logger hlsPlugins

plugins/hls-call-hierarchy-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,10 +12,10 @@ import Data.Functor ((<&>))
1212
import Data.List (sort, tails)
1313
import qualified Data.Map as M
1414
import qualified Data.Text as T
15+
import Development.IDE.Test
1516
import Ide.Plugin.CallHierarchy
1617
import qualified Language.LSP.Test as Test
1718
import qualified Language.LSP.Types.Lens as L
18-
import Development.IDE.Test
1919
import System.Directory.Extra
2020
import System.FilePath
2121
import qualified System.IO.Extra

plugins/hls-eval-plugin/test/Main.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import qualified Ide.Plugin.Config as Plugin
2222
import qualified Ide.Plugin.Eval as Eval
2323
import Ide.Plugin.Eval.Types (EvalParams (..), Section (..),
2424
testOutput)
25+
import Ide.Types (IdePlugins (IdePlugins))
2526
import Language.LSP.Types.Lens (arguments, command, range, title)
2627
import System.FilePath ((</>))
2728
import Test.Hls

plugins/hls-refactor-plugin/test/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -64,11 +64,11 @@ import qualified Test.AddArgument
6464
main :: IO ()
6565
main = defaultTestRunner tests
6666

67-
refactorPlugin :: IO [PluginDescriptor IdeState]
67+
refactorPlugin :: IO (IdePlugins IdeState)
6868
refactorPlugin = do
6969
exactprintLog <- pluginTestRecorder
7070
ghcideLog <- pluginTestRecorder
71-
pure $
71+
pure $ IdePlugins $
7272
[ Refactor.iePluginDescriptor exactprintLog "ghcide-code-actions-imports-exports"
7373
, Refactor.typeSigsPluginDescriptor exactprintLog "ghcide-code-actions-type-signatures"
7474
, Refactor.bindingsPluginDescriptor exactprintLog "ghcide-code-actions-bindings"

plugins/hls-refine-imports-plugin/src/Ide/Plugin/RefineImports.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,19 @@ import Ide.Plugin.ExplicitImports (extractMinimalImports,
4747
import Ide.PluginUtils (mkLspCommand)
4848
import Ide.Types
4949
import Language.LSP.Server
50-
import Language.LSP.Types
50+
import Language.LSP.Types (ApplyWorkspaceEditParams (ApplyWorkspaceEditParams),
51+
CodeAction (CodeAction, _command, _diagnostics, _disabled, _edit, _isPreferred, _kind, _title, _xdata),
52+
CodeActionKind (CodeActionUnknown),
53+
CodeActionParams (CodeActionParams),
54+
CodeLens (..),
55+
CodeLensParams (CodeLensParams, _textDocument),
56+
Method (TextDocumentCodeAction, TextDocumentCodeLens),
57+
SMethod (STextDocumentCodeAction, STextDocumentCodeLens, SWorkspaceApplyEdit),
58+
TextDocumentIdentifier (TextDocumentIdentifier, _uri),
59+
TextEdit (..),
60+
WorkspaceEdit (..),
61+
type (|?) (InR),
62+
uriToNormalizedFilePath)
5163

5264
newtype Log = LogShake Shake.Log deriving Show
5365

plugins/hls-rename-plugin/test/Main.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ import Data.Aeson
66
import qualified Data.Map as M
77
import Ide.Plugin.Config
88
import qualified Ide.Plugin.Rename as Rename
9+
import Ide.Types (IdePlugins (IdePlugins))
910
import System.FilePath
1011
import Test.Hls
1112

plugins/hls-retrie-plugin/hls-retrie-plugin.cabal

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ library
3131
, ghcide ^>=1.9
3232
, hashable
3333
, hls-plugin-api ^>=1.6
34+
, hls-refactor-plugin
3435
, lsp
3536
, lsp-types
3637
, retrie >=0.1.1.0
@@ -46,3 +47,21 @@ library
4647
TypeOperators
4748

4849
ghc-options: -Wno-unticked-promoted-constructors
50+
51+
test-suite tests
52+
buildable: True
53+
type: exitcode-stdio-1.0
54+
default-language: Haskell2010
55+
hs-source-dirs: test
56+
main-is: Main.hs
57+
ghc-options: -threaded -rtsopts -with-rtsopts=-N
58+
build-depends:
59+
, aeson
60+
, base
61+
, containers
62+
, filepath
63+
, hls-plugin-api
64+
, hls-refactor-plugin
65+
, hls-retrie-plugin
66+
, hls-test-utils ^>=1.5
67+
, text

0 commit comments

Comments
 (0)