Skip to content

Commit de8ef08

Browse files
upgrade to ghc-9.12
1 parent 4747d37 commit de8ef08

File tree

3 files changed

+30
-10
lines changed

3 files changed

+30
-10
lines changed

.github/workflows/test.yml

+1-1
Original file line numberDiff line numberDiff line change
@@ -213,7 +213,7 @@ jobs:
213213
name: Test hls-change-type-signature test suite
214214
run: cabal test hls-change-type-signature-plugin-tests || cabal test hls-change-type-signature-plugin-tests
215215

216-
- if: matrix.test && matrix.ghc != '9.12'
216+
- if: matrix.test
217217
name: Test hls-gadt-plugin test suit
218218
run: cabal test hls-gadt-plugin-tests || cabal test hls-gadt-plugin-tests
219219

haskell-language-server.cabal

+3-3
Original file line numberDiff line numberDiff line change
@@ -1208,13 +1208,13 @@ flag gadt
12081208
manual: True
12091209

12101210
common gadt
1211-
if flag(gadt) && (impl(ghc < 9.11) || flag(ignore-plugins-ghc-bounds))
1211+
if flag(gadt)
12121212
build-depends: haskell-language-server:hls-gadt-plugin
12131213
cpp-options: -Dhls_gadt
12141214

12151215
library hls-gadt-plugin
12161216
import: defaults, pedantic, warnings
1217-
if !flag(gadt) || (impl(ghc > 9.11) && !flag(ignore-plugins-ghc-bounds))
1217+
if !flag(gadt)
12181218
buildable: False
12191219
exposed-modules: Ide.Plugin.GADT
12201220
other-modules: Ide.Plugin.GHC
@@ -1238,7 +1238,7 @@ library hls-gadt-plugin
12381238

12391239
test-suite hls-gadt-plugin-tests
12401240
import: defaults, pedantic, test-defaults, warnings
1241-
if !flag(gadt) || (impl(ghc > 9.11) && !flag(ignore-plugins-ghc-bounds))
1241+
if !flag(gadt)
12421242
buildable: False
12431243
type: exitcode-stdio-1.0
12441244
hs-source-dirs: plugins/hls-gadt-plugin/test

plugins/hls-gadt-plugin/src/Ide/Plugin/GHC.hs

+26-6
Original file line numberDiff line numberDiff line change
@@ -7,14 +7,15 @@
77
{-# OPTIONS_GHC -Wno-overlapping-patterns #-}
88
module Ide.Plugin.GHC where
99

10+
#if !MIN_VERSION_ghc(9,11,0)
1011
import Data.Functor ((<&>))
12+
#endif
1113
import Data.List.Extra (stripInfix)
1214
import qualified Data.Text as T
1315
import Development.IDE
1416
import Development.IDE.GHC.Compat
1517
import Development.IDE.GHC.Compat.ExactPrint
16-
import GHC.Parser.Annotation (AddEpAnn (..),
17-
DeltaPos (..),
18+
import GHC.Parser.Annotation (DeltaPos (..),
1819
EpAnn (..),
1920
EpAnnComments (EpaComments))
2021
import Ide.PluginUtils (subRange)
@@ -44,6 +45,11 @@ import GHC.Parser.Annotation (EpUniToken (..),
4445
import Language.Haskell.GHC.ExactPrint.Utils (showAst)
4546
#endif
4647

48+
#if MIN_VERSION_ghc(9,11,0)
49+
import GHC.Types.SrcLoc (UnhelpfulSpanReason (..))
50+
#else
51+
import GHC.Parser.Annotation (AddEpAnn (..))
52+
#endif
4753

4854
type GP = GhcPass Parsed
4955

@@ -97,7 +103,9 @@ h98ToGADTConDecl ::
97103
h98ToGADTConDecl dataName tyVars ctxt = \case
98104
ConDeclH98{..} ->
99105
ConDeclGADT
100-
#if MIN_VERSION_ghc(9,9,0)
106+
#if MIN_VERSION_ghc(9,11,0)
107+
(AnnConDeclGADT [] [] NoEpUniTok)
108+
#elif MIN_VERSION_ghc(9,9,0)
101109
(NoEpUniTok, con_ext)
102110
#else
103111
con_ext
@@ -218,7 +226,11 @@ prettyGADTDecl df decl =
218226

219227
-- Make every data constructor start with a new line and 2 spaces
220228
adjustCon :: LConDecl GP -> LConDecl GP
221-
#if MIN_VERSION_ghc(9,9,0)
229+
#if MIN_VERSION_ghc(9,11,0)
230+
adjustCon (L _ r) =
231+
let delta = EpaDelta (UnhelpfulSpan UnhelpfulNoLocationInfo) (DifferentLine 1 3) []
232+
in L (EpAnn delta (AnnListItem []) (EpaComments [])) r
233+
#elif MIN_VERSION_ghc(9,9,0)
222234
adjustCon (L _ r) =
223235
let delta = EpaDelta (DifferentLine 1 3) []
224236
in L (EpAnn delta (AnnListItem []) (EpaComments [])) r
@@ -229,16 +241,20 @@ prettyGADTDecl df decl =
229241
#endif
230242

231243
-- Adjust where annotation to the same line of the type constructor
244+
#if MIN_VERSION_ghc(9,11,0)
245+
-- tcdDext is just a placeholder in ghc-9.12
246+
adjustWhere tcdDExt = tcdDExt
247+
#else
232248
adjustWhere tcdDExt = tcdDExt <&>
233249
#if !MIN_VERSION_ghc(9,9,0)
234250
map
235251
#endif
236-
(\(AddEpAnn ann l) ->
252+
(\(AddEpAnn ann l) ->
237253
if ann == AnnWhere
238254
then AddEpAnn AnnWhere d1
239255
else AddEpAnn ann l
240256
)
241-
257+
#endif
242258
-- Remove the first extra line if exist
243259
removeExtraEmptyLine s = case stripInfix "\n\n" s of
244260
Just (x, xs) -> x <> "\n" <> xs
@@ -257,6 +273,10 @@ noUsed = EpAnnNotUsed
257273
#endif
258274

259275
pattern UserTyVar' :: LIdP pass -> HsTyVarBndr flag pass
276+
#if MIN_VERSION_ghc(9,11,0)
277+
pattern UserTyVar' s <- HsTvb _ _ (HsBndrVar _ s) _
278+
#else
260279
pattern UserTyVar' s <- UserTyVar _ _ s
280+
#endif
261281

262282
implicitTyVars = wrapXRec @GP mkHsOuterImplicit

0 commit comments

Comments
 (0)