|
| 1 | +{-# LANGUAGE CPP #-} |
1 | 2 | {-# LANGUAGE DeriveAnyClass #-}
|
2 | 3 | {-# LANGUAGE DeriveGeneric #-}
|
3 | 4 | {-# LANGUAGE OverloadedStrings #-}
|
@@ -32,6 +33,7 @@ import Ide.Types
|
32 | 33 | import Language.Haskell.GHC.ExactPrint
|
33 | 34 | import Language.Haskell.GHC.ExactPrint.Parsers (parseDecl)
|
34 | 35 | import Language.Haskell.GHC.ExactPrint.Types hiding (GhcPs, Parens)
|
| 36 | +import Language.Haskell.GHC.ExactPrint.Utils (rs) |
35 | 37 | import Language.LSP.Server
|
36 | 38 | import Language.LSP.Types
|
37 | 39 | import qualified Language.LSP.Types.Lens as J
|
@@ -85,20 +87,19 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
|
85 | 87 | Right (ann, d) -> Just (setPrecedingLines d 1 indent ann, d)
|
86 | 88 | Left _ -> Nothing
|
87 | 89 |
|
88 |
| - addMethodDecls :: ParsedSource -> [LHsDecl GhcPs] -> Transform (Located (HsModule GhcPs)) |
89 | 90 | addMethodDecls ps mDecls = do
|
90 | 91 | d <- findInstDecl ps
|
91 | 92 | newSpan <- uniqueSrcSpanT
|
92 | 93 | let
|
93 | 94 | annKey = mkAnnKey d
|
94 |
| - newAnnKey = AnnKey newSpan (CN "HsValBinds") |
| 95 | + newAnnKey = AnnKey (rs newSpan) (CN "HsValBinds") |
95 | 96 | addWhere mkds@(Map.lookup annKey -> Just ann)
|
96 | 97 | = Map.insert newAnnKey ann2 mkds2
|
97 | 98 | where
|
98 | 99 | ann1 = ann
|
99 | 100 | { annsDP = annsDP ann ++ [(G AnnWhere, DP (0, 1))]
|
100 | 101 | , annCapturedSpan = Just newAnnKey
|
101 |
| - , annSortKey = Just (fmap getLoc mDecls) |
| 102 | + , annSortKey = Just (fmap (rs . getLoc) mDecls) |
102 | 103 | }
|
103 | 104 | mkds2 = Map.insert annKey ann1 mkds
|
104 | 105 | ann2 = annNone
|
@@ -168,9 +169,15 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
|
168 | 169 | pure
|
169 | 170 | $ head . head
|
170 | 171 | $ pointCommand hf (fromJust (fromCurrentRange pmap range) ^. J.start & J.character -~ 1)
|
| 172 | +#if !MIN_VERSION_ghc(9,0,0) |
171 | 173 | ( (Map.keys . Map.filter isClassNodeIdentifier . nodeIdentifiers . nodeInfo)
|
172 | 174 | <=< nodeChildren
|
173 | 175 | )
|
| 176 | +#else |
| 177 | + ( (Map.keys . Map.filter isClassNodeIdentifier . sourcedNodeIdents . sourcedNodeInfo) |
| 178 | + <=< nodeChildren |
| 179 | + ) |
| 180 | +#endif |
174 | 181 |
|
175 | 182 | findClassFromIdentifier docPath (Right name) = do
|
176 | 183 | (hscEnv -> hscenv, _) <- MaybeT . runAction "classplugin" state $ useWithStale GhcSessionDeps docPath
|
|
0 commit comments