Skip to content

Commit 7235aad

Browse files
author
bendo
committed
Fix action removes ticks from TemplateHaskellQuotes (#628)
1 parent 73b02ef commit 7235aad

File tree

2 files changed

+29
-5
lines changed

2 files changed

+29
-5
lines changed

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1771,15 +1771,17 @@ extractDoesNotExportModuleName x
17711771

17721772

17731773
mkRenameEdit :: Maybe T.Text -> Range -> T.Text -> TextEdit
1774-
mkRenameEdit contents range name =
1775-
if maybeIsInfixFunction == Just True
1776-
then TextEdit range ("`" <> name <> "`")
1777-
else TextEdit range name
1774+
mkRenameEdit contents range name
1775+
| maybeIsInfixFunction == Just True = TextEdit range ("`" <> name <> "`")
1776+
| maybeIsTemplateFunction == Just True = TextEdit range ("'" <> name)
1777+
| otherwise = TextEdit range name
17781778
where
17791779
maybeIsInfixFunction = do
17801780
curr <- textInRange range <$> contents
17811781
pure $ "`" `T.isPrefixOf` curr && "`" `T.isSuffixOf` curr
1782-
1782+
maybeIsTemplateFunction = do
1783+
curr <- textInRange range <$> contents
1784+
pure $ "'" `T.isPrefixOf` curr
17831785

17841786
-- | Extract the type and surround it in parentheses except in obviously safe cases.
17851787
--

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

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -609,6 +609,28 @@ renameActionTests = testGroup "rename actions"
609609
, "foo x y = x `monus` y"
610610
]
611611
liftIO $ expectedContentAfterAction @=? contentAfterAction
612+
, testSession "change template function" $ do
613+
let content = T.unlines
614+
[ "{-# LANGUAGE TemplateHaskellQuotes #-}"
615+
, "module Testing where"
616+
, "import Language.Haskell.TH (Name)"
617+
, "foo :: Name"
618+
, "foo = 'bread"
619+
]
620+
doc <- createDoc "Testing.hs" "haskell" content
621+
diags <- waitForDiagnostics
622+
actionsOrCommands <- getCodeActions doc (Range (Position 4 6) (Position 4 12))
623+
[fixTypo] <- pure [action | InR action@CodeAction{ _title = actionTitle } <- actionsOrCommands, "break" `T.isInfixOf` actionTitle ]
624+
executeCodeAction fixTypo
625+
contentAfterAction <- documentContents doc
626+
let expectedContentAfterAction = T.unlines
627+
[ "{-# LANGUAGE TemplateHaskellQuotes #-}"
628+
, "module Testing where"
629+
, "import Language.Haskell.TH (Name)"
630+
, "foo :: Name"
631+
, "foo = 'break"
632+
]
633+
liftIO $ expectedContentAfterAction @=? contentAfterAction
612634
]
613635

614636
typeWildCardActionTests :: TestTree

0 commit comments

Comments
 (0)