Skip to content

Commit

Permalink
refact: remove unnecessary cpp
Browse files Browse the repository at this point in the history
  • Loading branch information
Santiago Weight committed Nov 16, 2022
1 parent 1041a25 commit fae8f37
Show file tree
Hide file tree
Showing 5 changed files with 16 additions and 7 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ import Development.IDE.Plugin.CodeAction.PositionIndexed
import Development.IDE.Plugin.CodeAction.Util
import Development.IDE.Plugin.Completions.Types
import qualified Development.IDE.Plugin.Plugins.AddArgument
import Development.IDE.Plugin.Plugins.Diagnostic
import Development.IDE.Plugin.TypeLenses (suggestSignature)
import Development.IDE.Types.Exports
import Development.IDE.Types.Location
Expand Down Expand Up @@ -92,7 +93,6 @@ import qualified Text.Fuzzy.Parallel as TFP
import Text.Regex.TDFA (mrAfter,
(=~), (=~~))
#if MIN_VERSION_ghc(9,2,0)
import Development.IDE.Plugin.Plugins.Diagnostic
import GHC (AddEpAnn (AddEpAnn),
Anchor (anchor_op),
AnchorOperation (..),
Expand Down Expand Up @@ -171,9 +171,7 @@ bindingsPluginDescriptor recorder plId = mkExactprintPluginDescriptor recorder $
, wrap suggestImplicitParameter
#endif
, wrap suggestNewDefinition
#if MIN_VERSION_ghc(9,2,1)
, wrap Development.IDE.Plugin.Plugins.AddArgument.plugin
#endif
, wrap suggestDeleteUnusedBinding
]
plId
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
{-# LANGUAGE CPP #-}
module Development.IDE.Plugin.Plugins.AddArgument (plugin) where

#if !MIN_VERSION_ghc(9,2,1)
import qualified Data.Text as T
import Language.LSP.Types

plugin :: [(T.Text, [TextEdit])]
plugin = []
#else
Expand All @@ -19,7 +23,7 @@ import GHC (EpAnn (..),
import GHC.Hs (IsUnicodeSyntax (..))
import Language.Haskell.GHC.ExactPrint.Transform (d1)
import Development.IDE.GHC.Compat
import Development.IDE
import Development.IDE.GHC.Error ( spanContainsRange )
import Language.LSP.Types
import qualified Data.Text as T
import Development.IDE.GHC.ExactPrint (modifyMgMatchesT', modifySigWithM, modifySmallestDeclWithM, genAnchor1)
Expand Down
10 changes: 7 additions & 3 deletions plugins/hls-refactor-plugin/test/Test/AddArgument.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ tests =
#if !MIN_VERSION_ghc(9,2,1)
[]
#else
[ mkGoldenAddArgTest "Hole" (r 0 0 0 50),
[ mkGoldenAddArgTest' "Hole" (r 0 0 0 50) "_new_def",
mkGoldenAddArgTest "NoTypeSuggestion" (r 0 0 0 50),
mkGoldenAddArgTest "MultipleDeclAlts" (r 0 0 0 50),
mkGoldenAddArgTest "AddArgWithSig" (r 1 0 1 50),
Expand All @@ -51,13 +51,17 @@ tests =
r x y x' y' = Range (Position x y) (Position x' y')

mkGoldenAddArgTest :: FilePath -> Range -> TestTree
mkGoldenAddArgTest testFileName range = do
mkGoldenAddArgTest testFileName range = mkGoldenAddArgTest' testFileName range "new_def"

-- Make a golden test for the add argument action. Given varName is the name of the variable not yet defined.
mkGoldenAddArgTest' :: FilePath -> Range -> T.Text -> TestTree
mkGoldenAddArgTest' testFileName range varName = do
let action docB = do
_ <- waitForDiagnostics
InR action@CodeAction {_title = actionTitle} : _ <-
filter (\(InR CodeAction {_title = x}) -> "Add" `isPrefixOf` T.unpack x)
<$> getCodeActions docB range
liftIO $ actionTitle @?= "Add argument ‘new_def’ to function"
liftIO $ actionTitle @?= ("Add argument ‘" <> varName <> "’ to function")
executeCodeAction action
goldenWithHaskellDoc
(Refactor.bindingsPluginDescriptor mempty "ghcide-code-actions-bindings")
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
foo _new_def = _new_def
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
foo True new_def = new_def
foo False new_def = 1

0 comments on commit fae8f37

Please # to comment.