Skip to content

Commit e29f61f

Browse files
July541pepeiborra
andauthored
Fix hls-class-plugin on ghc-9.2 (#2733)
* Fix codeAction on 9.2 * Enable test * pointCommand: MIN_VERSION_ghc to 9.2 * Specify version * Fix edit command * Enable class plugin in cabal * Comment addWhere * Unify the method of obtaining identifiers * Remove CPP * Remove compile flag * Rewrite filter with more restricts Co-authored-by: Pepe Iborra <pepeiborra@gmail.com>
1 parent 30b3fec commit e29f61f

File tree

7 files changed

+94
-34
lines changed

7 files changed

+94
-34
lines changed

.github/workflows/test.yml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -164,7 +164,7 @@ jobs:
164164
name: Test hls-floskell-plugin
165165
run: cabal test hls-floskell-plugin --test-options="$TEST_OPTS" || cabal test hls-floskell-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-floskell-plugin --test-options="$TEST_OPTS"
166166

167-
- if: matrix.test && matrix.ghc != '9.2.1'
167+
- if: matrix.test
168168
name: Test hls-class-plugin
169169
run: cabal test hls-class-plugin --test-options="$TEST_OPTS" || cabal test hls-class-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-class-plugin --test-options="$TEST_OPTS"
170170

cabal-ghc921.project

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,6 @@ constraints:
4646
haskell-language-server
4747
+ignore-plugins-ghc-bounds
4848
-brittany
49-
-class
5049
-haddockComments
5150
-hlint
5251
-retrie

plugins/hls-class-plugin/src/Ide/Plugin/Class.hs

Lines changed: 74 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -21,10 +21,11 @@ import Data.List
2121
import qualified Data.Map.Strict as Map
2222
import Data.Maybe
2323
import qualified Data.Text as T
24+
import qualified Data.Set as Set
2425
import Development.IDE hiding (pluginHandlers)
2526
import Development.IDE.Core.PositionMapping (fromCurrentRange,
2627
toCurrentRange)
27-
import Development.IDE.GHC.Compat
28+
import Development.IDE.GHC.Compat as Compat hiding (locA)
2829
import Development.IDE.GHC.Compat.Util
2930
import Development.IDE.Spans.AtPoint
3031
import qualified GHC.Generics as Generics
@@ -38,6 +39,11 @@ import Language.LSP.Server
3839
import Language.LSP.Types
3940
import qualified Language.LSP.Types.Lens as J
4041

42+
#if MIN_VERSION_ghc(9,2,0)
43+
import GHC.Hs (AnnsModule(AnnsModule))
44+
import GHC.Parser.Annotation
45+
#endif
46+
4147
descriptor :: PluginId -> PluginDescriptor IdeState
4248
descriptor plId = (defaultPluginDescriptor plId)
4349
{ pluginCommands = commands
@@ -63,25 +69,78 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
6369
medit <- liftIO $ runMaybeT $ do
6470
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
6571
pm <- MaybeT . runAction "classplugin" state $ use GetParsedModule docPath
66-
let
67-
ps = pm_parsed_source pm
68-
anns = relativiseApiAnns ps (pm_annotations pm)
69-
old = T.pack $ exactPrint ps anns
70-
7172
(hsc_dflags . hscEnv -> df) <- MaybeT . runAction "classplugin" state $ use GhcSessionDeps docPath
72-
List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
73-
let
74-
(ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
75-
new = T.pack $ exactPrint ps' anns'
76-
73+
(old, new) <- makeEditText pm df
7774
pure (workspaceEdit caps old new)
75+
7876
forM_ medit $ \edit ->
7977
sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\_ -> pure ())
8078
pure (Right Null)
8179
where
82-
8380
indent = 2
8481

82+
workspaceEdit caps old new
83+
= diffText caps (uri, old) new IncludeDeletions
84+
85+
toMethodName n
86+
| Just (h, _) <- T.uncons n
87+
, not (isAlpha h || h == '_')
88+
= "(" <> n <> ")"
89+
| otherwise
90+
= n
91+
92+
#if MIN_VERSION_ghc(9,2,0)
93+
makeEditText pm df = do
94+
List mDecls <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
95+
let ps = makeDeltaAst $ pm_parsed_source pm
96+
old = T.pack $ exactPrint ps
97+
(ps', _, _) = runTransform (addMethodDecls ps mDecls)
98+
new = T.pack $ exactPrint ps'
99+
pure (old, new)
100+
101+
makeMethodDecl df mName =
102+
either (const Nothing) Just . parseDecl df (T.unpack mName) . T.unpack
103+
$ toMethodName mName <> " = _"
104+
105+
addMethodDecls ps mDecls = do
106+
allDecls <- hsDecls ps
107+
let (before, ((L l inst): after)) = break (containRange range . getLoc) allDecls
108+
replaceDecls ps (before ++ (L l (addWhere inst)): (map newLine mDecls ++ after))
109+
where
110+
-- Add `where` keyword for `instance X where` if `where` is missing.
111+
--
112+
-- The `where` in ghc-9.2 is now stored in the instance declaration
113+
-- directly. More precisely, giving an `HsDecl GhcPs`, we have:
114+
-- InstD --> ClsInstD --> ClsInstDecl --> XCClsInstDecl --> (EpAnn [AddEpAnn], AnnSortKey),
115+
-- here `AnnEpAnn` keeps the track of Anns.
116+
--
117+
-- See the link for the original definition:
118+
-- https://hackage.haskell.org/package/ghc-9.2.1/docs/Language-Haskell-Syntax-Extension.html#t:XCClsInstDecl
119+
addWhere (InstD xInstD (ClsInstD ext decl@ClsInstDecl{..})) =
120+
let ((EpAnn entry anns comments), key) = cid_ext
121+
in InstD xInstD (ClsInstD ext decl {
122+
cid_ext = (EpAnn
123+
entry
124+
(AddEpAnn AnnWhere (EpaDelta (SameLine 1) []) : anns)
125+
comments
126+
, key)
127+
})
128+
addWhere decl = decl
129+
130+
newLine (L l e) =
131+
let dp = deltaPos 1 (indent + 1) -- Not sure why there need one more space
132+
in L (noAnnSrcSpanDP (locA l) dp <> l) e
133+
134+
#else
135+
makeEditText pm df = do
136+
List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
137+
let ps = pm_parsed_source pm
138+
anns = relativiseApiAnns ps (pm_annotations pm)
139+
old = T.pack $ exactPrint ps anns
140+
(ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
141+
new = T.pack $ exactPrint ps' anns'
142+
pure (old, new)
143+
85144
makeMethodDecl df mName =
86145
case parseDecl df (T.unpack mName) . T.unpack $ toMethodName mName <> " = _" of
87146
Right (ann, d) -> Just (setPrecedingLines d 1 indent ann, d)
@@ -112,16 +171,7 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
112171

113172
findInstDecl :: ParsedSource -> Transform (LHsDecl GhcPs)
114173
findInstDecl ps = head . filter (containRange range . getLoc) <$> hsDecls ps
115-
116-
workspaceEdit caps old new
117-
= diffText caps (uri, old) new IncludeDeletions
118-
119-
toMethodName n
120-
| Just (h, _) <- T.uncons n
121-
, not (isAlpha h || h == '_')
122-
= "(" <> n <> ")"
123-
| otherwise
124-
= n
174+
#endif
125175

126176
-- |
127177
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
@@ -169,15 +219,9 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
169219
pure
170220
$ head . head
171221
$ pointCommand hf (fromJust (fromCurrentRange pmap range) ^. J.start & J.character -~ 1)
172-
#if !MIN_VERSION_ghc(9,0,0)
173-
( (Map.keys . Map.filter isClassNodeIdentifier . nodeIdentifiers . nodeInfo)
222+
( (Map.keys . Map.filter isClassNodeIdentifier . Compat.getNodeIds)
174223
<=< nodeChildren
175224
)
176-
#else
177-
( (Map.keys . Map.filter isClassNodeIdentifier . sourcedNodeIdents . sourcedNodeInfo)
178-
<=< nodeChildren
179-
)
180-
#endif
181225

182226
findClassFromIdentifier docPath (Right name) = do
183227
(hscEnv -> hscenv, _) <- MaybeT . runAction "classplugin" state $ useWithStale GhcSessionDeps docPath
@@ -197,7 +241,7 @@ containRange :: Range -> SrcSpan -> Bool
197241
containRange range x = isInsideSrcSpan (range ^. J.start) x || isInsideSrcSpan (range ^. J.end) x
198242

199243
isClassNodeIdentifier :: IdentifierDetails a -> Bool
200-
isClassNodeIdentifier = isNothing . identType
244+
isClassNodeIdentifier ident = (isNothing . identType) ident && Use `Set.member` (identInfo ident)
201245

202246
isClassMethodWarning :: T.Text -> Bool
203247
isClassMethodWarning = T.isPrefixOf "• No explicit implementation for"

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

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE TypeOperators #-}
44

55
{-# OPTIONS_GHC -Wall #-}
6+
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
67
module Main
78
( main
89
) where
@@ -45,6 +46,8 @@ tests = testGroup
4546
executeCodeAction mmAction
4647
, goldenWithClass "Creates a placeholder for a method starting with '_'" "T4" "" $ \(_fAction:_) -> do
4748
executeCodeAction _fAction
49+
, goldenWithClass "Creates a placeholder for '==' with extra lines" "T5" "" $ \(eqAction:_) -> do
50+
executeCodeAction eqAction
4851
]
4952

5053
_CACodeAction :: Prism' (Command |? CodeAction) CodeAction
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module T1 where
2+
3+
data X = X
4+
5+
instance Eq X where
6+
(==) = _
7+
8+
x = ()
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
module T1 where
2+
3+
data X = X
4+
5+
instance Eq X where
6+
7+
x = ()

stack-9.2.1.yaml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ packages:
1010
- ./hls-test-utils
1111
- ./shake-bench
1212
- ./plugins/hls-call-hierarchy-plugin
13-
# - ./plugins/hls-class-plugin
13+
- ./plugins/hls-class-plugin
1414
# - ./plugins/hls-haddock-comments-plugin
1515
# - ./plugins/hls-eval-plugin
1616
- ./plugins/hls-explicit-imports-plugin
@@ -116,7 +116,6 @@ flags:
116116
ignore-plugins-ghc-bounds: true
117117
alternateNumberFormat: false
118118
brittany: false
119-
class: false
120119
eval: false
121120
haddockComments: false
122121
hlint: false

0 commit comments

Comments
 (0)