Skip to content

Commit 96ac5b3

Browse files
committed
fix build issues
1 parent 8c85ffd commit 96ac5b3

File tree

3 files changed

+43
-13
lines changed

3 files changed

+43
-13
lines changed

.github/workflows/test.yml

+1-1
Original file line numberDiff line numberDiff line change
@@ -202,7 +202,7 @@ jobs:
202202
name: Test hls-call-hierarchy-plugin test suite
203203
run: cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS" || cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS"
204204

205-
- if: matrix.test && matrix.ghc != '9.2.1'
205+
- if: matrix.test
206206
name: Test hls-rename-plugin test suite
207207
run: cabal test hls-rename-plugin --test-options="$TEST_OPTS" || cabal test hls-rename-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-rename-plugin --test-options="$TEST_OPTS"
208208

cabal-ghc921.project

+1-3
Original file line numberDiff line numberDiff line change
@@ -65,9 +65,7 @@ constraints:
6565
-retrie
6666
-splice
6767
-stylishhaskell
68-
-tactic
69-
-- the rename plugin builds, but doesn't work
70-
-rename,
68+
-tactic,
7169
ghc-lib-parser ^>= 9.2,
7270
attoparsec ^>= 0.14.3,
7371
ghc-exactprint >= 1.3,

plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs

+41-9
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,10 @@
1-
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE DataKinds #-}
3-
{-# LANGUAGE GADTs #-}
4-
{-# LANGUAGE NamedFieldPuns #-}
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE DataKinds #-}
3+
{-# LANGUAGE GADTs #-}
4+
{-# LANGUAGE NamedFieldPuns #-}
5+
{-# LANGUAGE RankNTypes #-}
6+
{-# LANGUAGE ScopedTypeVariables #-}
7+
{-# LANGUAGE TypeApplications #-}
58

69
module Ide.Plugin.Rename (descriptor) where
710

@@ -11,7 +14,7 @@ import Control.Monad.Trans.Class
1114
import Control.Monad.Trans.Except
1215
import Data.Containers.ListUtils
1316
import Data.Generics
14-
import Data.List.Extra hiding (nubOrd)
17+
import Data.List.Extra hiding (nubOrd, replace)
1518
import qualified Data.Map as M
1619
import Data.Maybe
1720
import qualified Data.Text as T
@@ -20,11 +23,16 @@ import Development.IDE.Core.PositionMapping
2023
import Development.IDE.Core.Shake
2124
import Development.IDE.GHC.Compat
2225
import Development.IDE.Spans.AtPoint
26+
#if MIN_VERSION_ghc(9,2,1)
27+
import GHC.Parser.Annotation (AnnContext, AnnList,
28+
AnnParen, AnnPragma)
29+
#endif
2330
#if MIN_VERSION_ghc(9,0,1)
2431
import GHC.Types.Name
2532
#else
2633
import Name
2734
#endif
35+
import Debug.Trace
2836
import Development.IDE.GHC.ExactPrint (GetAnnotatedParsedSource (GetAnnotatedParsedSource))
2937
import HieDb.Query
3038
import Ide.Plugin.Config
@@ -44,11 +52,16 @@ renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _pr
4452
response $ do
4553
nfp <- safeUriToNfp uri
4654
oldName <- getNameAtPos state nfp pos
55+
traceM $ "oldName: " <> prettyPrint oldName
4756
workspaceRefs <- refsAtName state nfp oldName
57+
traceM $ "workspaceRefs: " <> show workspaceRefs
4858
let filesRefs = groupOn locToUri workspaceRefs
4959
getFileEdits = ap (getSrcEdits state . renameModRefs newNameText) (locToUri . head)
5060

61+
traceM $ "\nfilesRefs: " <> show filesRefs
62+
5163
fileEdits <- mapM getFileEdits filesRefs
64+
traceM $ "\nfileEdits: " <> show fileEdits
5265
pure $ foldl' (<>) mempty fileEdits
5366

5467
-------------------------------------------------------------------------------
@@ -73,7 +86,7 @@ getSrcEdits state updateMod uri = do
7386
"Rename.GetParsedModuleWithComments"
7487
state
7588
(use GetAnnotatedParsedSource nfp)
76-
let (ps, apiAnns) = (astA annotatedAst, annsA annotatedAst)
89+
let (ps, anns) = (astA annotatedAst, annsA annotatedAst)
7790
#if !MIN_VERSION_ghc(9,2,1)
7891
let src = T.pack $ exactPrint ps anns
7992
res = T.pack $ exactPrint (updateMod <$> ps) anns
@@ -95,12 +108,32 @@ renameModRefs ::
95108
HsModule GhcPs
96109
-> HsModule GhcPs
97110
#endif
111+
#if MIN_VERSION_ghc(9,2,1)
112+
renameModRefs newNameText refs = everywhere $
113+
-- there has to be a better way...
114+
mkT (replace @AnnListItem) `extT`
115+
-- replace @AnnList `extT` -- not needed
116+
-- replace @AnnParen `extT` -- not needed
117+
-- replace @AnnPragma `extT` -- not needed
118+
-- replace @AnnContext `extT` -- not needed
119+
-- replace @NoEpAnns `extT` -- not needed
120+
replace @NameAnn
121+
where
122+
replace :: forall an. Typeable an => LocatedAn an RdrName -> LocatedAn an RdrName
123+
replace (L srcSpan oldRdrName)
124+
| isRef (locA srcSpan) = L srcSpan $ newRdrName oldRdrName
125+
replace lOldRdrName = lOldRdrName
126+
#else
98127
renameModRefs newNameText refs = everywhere $ mkT replace
99128
where
100129
replace :: Located RdrName -> Located RdrName
101130
replace (L srcSpan oldRdrName)
102131
| isRef srcSpan = L srcSpan $ newRdrName oldRdrName
103132
replace lOldRdrName = lOldRdrName
133+
#endif
134+
135+
isRef :: SrcSpan -> Bool
136+
isRef = (`elem` refs) . fromJust . srcSpanToLocation
104137

105138
newRdrName :: RdrName -> RdrName
106139
newRdrName oldRdrName = case oldRdrName of
@@ -109,9 +142,8 @@ renameModRefs newNameText refs = everywhere $ mkT replace
109142

110143
newOccName = mkTcOcc $ T.unpack newNameText
111144

112-
isRef :: SrcSpan -> Bool
113-
isRef = (`elem` refs) . fromJust . srcSpanToLocation
114-
145+
newRdrName :: RdrName -> RdrName
146+
newRdrName = error "not implemented"
115147
-------------------------------------------------------------------------------
116148
-- Reference finding
117149

0 commit comments

Comments
 (0)