Skip to content

Commit 0deb1d2

Browse files
committed
plugins build with 9.14
1 parent f9b06ff commit 0deb1d2

File tree

18 files changed

+177
-58
lines changed

18 files changed

+177
-58
lines changed
Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
["9.12", "9.10", "9.8", "9.6"]
1+
["9.14", "9.12", "9.10", "9.8", "9.6"]

.github/workflows/test.yml

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -146,7 +146,7 @@ jobs:
146146
run: cabal test hls-refactor-plugin-tests || cabal test hls-refactor-plugin-tests
147147

148148
# TODO enable when it supports 9.10
149-
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.10.2'
149+
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.14' && matrix.ghc != '9.10.2'
150150
name: Test hls-floskell-plugin
151151
run: cabal test hls-floskell-plugin-tests || cabal test hls-floskell-plugin-tests
152152

@@ -163,11 +163,11 @@ jobs:
163163
run: cabal test hls-eval-plugin-tests || cabal test hls-eval-plugin-tests
164164

165165
# TODO enable when it supports 9.10
166-
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.10.2'
166+
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.14' && matrix.ghc != '9.10.2'
167167
name: Test hls-splice-plugin
168168
run: cabal test hls-splice-plugin-tests || cabal test hls-splice-plugin-tests
169169

170-
- if: matrix.test && matrix.ghc != '9.12'
170+
- if: matrix.test && matrix.ghc != '9.12' && matrix.ghc != '9.14'
171171
name: Test hls-stan-plugin
172172
run: cabal test hls-stan-plugin-tests || cabal test hls-stan-plugin-tests
173173

@@ -196,7 +196,7 @@ jobs:
196196
run: cabal test hls-rename-plugin-tests || cabal test hls-rename-plugin-tests
197197

198198
# TODO enable when it supports 9.10
199-
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.10.2'
199+
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.14' && matrix.ghc != '9.10.2'
200200
name: Test hls-hlint-plugin test suite
201201
run: cabal test hls-hlint-plugin-tests || cabal test hls-hlint-plugin-tests
202202

@@ -233,11 +233,11 @@ jobs:
233233
run: cabal test hls-explicit-record-fields-plugin-tests || cabal test hls-explicit-record-fields-plugin-tests
234234

235235
# versions need to be limited since the tests depend on cabal-fmt which only builds with ghc <9.10
236-
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.10.2'
236+
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.14' && matrix.ghc != '9.10.2'
237237
name: Test hls-cabal-fmt-plugin test suite
238238
run: cabal test hls-cabal-fmt-plugin-tests --flag=isolateCabalfmtTests || cabal test hls-cabal-fmt-plugin-tests --flag=isolateCabalfmtTests
239239

240-
- if: matrix.test && matrix.ghc != '9.12'
240+
- if: matrix.test && matrix.ghc != '9.12' && matrix.ghc != '9.14'
241241
name: Test hls-cabal-gild-plugin test suite
242242
run: cabal test hls-cabal-gild-plugin-tests --flag=isolateCabalGildTests || cabal test hls-cabal-gild-plugin-tests --flag=isolateCabalGildTests
243243

@@ -246,7 +246,7 @@ jobs:
246246
run: cabal test hls-cabal-plugin-tests || cabal test hls-cabal-plugin-tests
247247

248248
# TODO enable when it supports 9.10
249-
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.10.2'
249+
- if: matrix.test && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.14' && matrix.ghc != '9.10.2'
250250
name: Test hls-retrie-plugin test suite
251251
run: cabal test hls-retrie-plugin-tests || cabal test hls-retrie-plugin-tests
252252

@@ -264,7 +264,7 @@ jobs:
264264

265265
# The plugin tutorial is only compatible with 9.6 and 9.8.
266266
# No particular reason, just to avoid excessive CPP.
267-
- if: matrix.test && matrix.ghc != '9.4' && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.10.2'
267+
- if: matrix.test && matrix.ghc != '9.4' && matrix.ghc != '9.10' && matrix.ghc != '9.12' && matrix.ghc != '9.14' && matrix.ghc != '9.10.2'
268268
name: Compile the plugin-tutorial
269269
run: cabal build plugin-tutorial
270270

cabal.project

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
packages:
2-
-- ./
2+
./
33
./shake-bench
44
./hls-graph
55
./ghcide
@@ -133,3 +133,9 @@ if impl(ghc >= 9.14)
133133
th-compat:template-haskell,
134134
lsp-test:time,
135135
ghc-lib-parser:base,
136+
lukko:base,
137+
binary-instances:base,
138+
binary-orphans:base,
139+
generic-deriving:template-haskell,
140+
generic-deriving:containers,
141+
cabal-install-parsers:containers,

ghcide/src/Development/IDE/GHC/Compat.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ module Development.IDE.GHC.Compat(
6666
simplifyExpr,
6767
tidyExpr,
6868
emptyTidyEnv,
69+
tidyOpenType,
6970
corePrepExpr,
7071
corePrepPgm,
7172
lintInteractiveExpr,
@@ -138,6 +139,7 @@ import Prelude hiding (mod)
138139

139140
import qualified GHC.Core.Opt.Pipeline as GHC
140141
import GHC.Core.Tidy (tidyExpr)
142+
import GHC.Core.TyCo.Tidy (tidyOpenType)
141143
import GHC.CoreToStg.Prep (corePrepPgm)
142144
import qualified GHC.CoreToStg.Prep as GHC
143145
import GHC.Driver.Hooks (hscCompileCoreExprHook)

haskell-language-server.cabal

Lines changed: 25 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -353,7 +353,7 @@ library hls-class-plugin
353353
, deepseq
354354
, extra
355355
, ghc
356-
, ghc-exactprint >= 1.5 && < 1.13.0.0
356+
, ghc-exactprint >= 1.5 && < 1.15
357357
, ghcide == 2.12.0.0
358358
, hls-graph
359359
, hls-plugin-api == 2.12.0.0
@@ -712,7 +712,8 @@ common hlint
712712
-- Hlint isn't compatible with GHC 9.10, and crashes in subtle ways.
713713
-- See https://github.com/haskell/haskell-language-server/issues/4674
714714
-- for its wake of destruction.
715-
if flag(hlint) && !impl(ghc ==9.10.*)
715+
-- hlint depends on ghc-lib-parser which doesn't support GHC 9.14
716+
if flag(hlint) && !impl(ghc ==9.10.*) && !impl(ghc >= 9.14)
716717
build-depends: haskell-language-server:hls-hlint-plugin
717718
cpp-options: -Dhls_hlint
718719

@@ -721,7 +722,8 @@ library hls-hlint-plugin
721722
-- Hlint isn't compatible with GHC 9.10, and crashes in subtle ways.
722723
-- See https://github.com/haskell/haskell-language-server/issues/4674
723724
-- for its wake of destruction.
724-
if !flag(hlint) || impl(ghc ==9.10.*)
725+
-- hlint depends on ghc-lib-parser which doesn't support GHC 9.14
726+
if !flag(hlint) || impl(ghc ==9.10.*) || impl(ghc >= 9.14)
725727
buildable: False
726728
exposed-modules: Ide.Plugin.Hlint
727729
hs-source-dirs: plugins/hls-hlint-plugin/src
@@ -771,7 +773,8 @@ test-suite hls-hlint-plugin-tests
771773
-- Hlint isn't compatible with GHC 9.10, and crashes in subtle ways.
772774
-- See https://github.com/haskell/haskell-language-server/issues/4674
773775
-- for its wake of destruction.
774-
if !flag(hlint) || impl(ghc ==9.10.*)
776+
-- hlint depends on ghc-lib-parser which doesn't support GHC 9.14
777+
if !flag(hlint) || impl(ghc ==9.10.*) || impl(ghc >= 9.14)
775778
buildable: False
776779
type: exitcode-stdio-1.0
777780
hs-source-dirs: plugins/hls-hlint-plugin/test
@@ -1519,13 +1522,15 @@ flag fourmolu
15191522
manual: True
15201523

15211524
common fourmolu
1522-
if flag(fourmolu)
1525+
-- fourmolu depends on ghc-lib-parser which doesn't support GHC 9.14
1526+
if flag(fourmolu) && !impl(ghc >= 9.14)
15231527
build-depends: haskell-language-server:hls-fourmolu-plugin
15241528
cpp-options: -Dhls_fourmolu
15251529

15261530
library hls-fourmolu-plugin
15271531
import: defaults, pedantic, warnings
1528-
if !flag(fourmolu)
1532+
-- fourmolu depends on ghc-lib-parser which doesn't support GHC 9.14
1533+
if !flag(fourmolu) || impl(ghc >= 9.14)
15291534
buildable: False
15301535
exposed-modules: Ide.Plugin.Fourmolu
15311536
hs-source-dirs: plugins/hls-fourmolu-plugin/src
@@ -1545,7 +1550,8 @@ library hls-fourmolu-plugin
15451550

15461551
test-suite hls-fourmolu-plugin-tests
15471552
import: defaults, pedantic, test-defaults, warnings
1548-
if !flag(fourmolu)
1553+
-- fourmolu depends on ghc-lib-parser which doesn't support GHC 9.14
1554+
if !flag(fourmolu) || impl(ghc >= 9.14)
15491555
buildable: False
15501556
type: exitcode-stdio-1.0
15511557
hs-source-dirs: plugins/hls-fourmolu-plugin/test
@@ -1573,13 +1579,15 @@ flag ormolu
15731579
manual: True
15741580

15751581
common ormolu
1576-
if flag(ormolu)
1582+
-- ormolu depends on ghc-lib-parser which doesn't support GHC 9.14
1583+
if flag(ormolu) && !impl(ghc >= 9.14)
15771584
build-depends: haskell-language-server:hls-ormolu-plugin
15781585
cpp-options: -Dhls_ormolu
15791586

15801587
library hls-ormolu-plugin
15811588
import: defaults, pedantic, warnings
1582-
if !flag(ormolu)
1589+
-- ormolu depends on ghc-lib-parser which doesn't support GHC 9.14
1590+
if !flag(ormolu) || impl(ghc >= 9.14)
15831591
buildable: False
15841592
exposed-modules: Ide.Plugin.Ormolu
15851593
hs-source-dirs: plugins/hls-ormolu-plugin/src
@@ -1599,7 +1607,8 @@ library hls-ormolu-plugin
15991607

16001608
test-suite hls-ormolu-plugin-tests
16011609
import: defaults, pedantic, test-defaults, warnings
1602-
if !flag(ormolu)
1610+
-- ormolu depends on ghc-lib-parser which doesn't support GHC 9.14
1611+
if !flag(ormolu) || impl(ghc >= 9.14)
16031612
buildable: False
16041613
type: exitcode-stdio-1.0
16051614
hs-source-dirs: plugins/hls-ormolu-plugin/test
@@ -1628,14 +1637,16 @@ flag stylishHaskell
16281637
manual: True
16291638

16301639
common stylishHaskell
1631-
if flag(stylishHaskell)
1640+
-- stylish-haskell depends on ghc-lib-parser which doesn't support GHC 9.14
1641+
if flag(stylishHaskell) && !impl(ghc >= 9.14)
16321642
build-depends: haskell-language-server:hls-stylish-haskell-plugin
16331643
cpp-options: -Dhls_stylishHaskell
16341644

16351645
library hls-stylish-haskell-plugin
16361646
import: defaults, pedantic, warnings
16371647
-- https://github.com/haskell/stylish-haskell/issues/479
1638-
if !flag(stylishHaskell)
1648+
-- stylish-haskell depends on ghc-lib-parser which doesn't support GHC 9.14
1649+
if !flag(stylishHaskell) || impl(ghc >= 9.14)
16391650
buildable: False
16401651
exposed-modules: Ide.Plugin.StylishHaskell
16411652
hs-source-dirs: plugins/hls-stylish-haskell-plugin/src
@@ -1653,7 +1664,8 @@ library hls-stylish-haskell-plugin
16531664

16541665
test-suite hls-stylish-haskell-plugin-tests
16551666
import: defaults, pedantic, test-defaults, warnings
1656-
if !flag(stylishHaskell)
1667+
-- stylish-haskell depends on ghc-lib-parser which doesn't support GHC 9.14
1668+
if !flag(stylishHaskell) || impl(ghc >= 9.14)
16571669
buildable: False
16581670
type: exitcode-stdio-1.0
16591671
hs-source-dirs: plugins/hls-stylish-haskell-plugin/test

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Literals.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,17 +66,21 @@ getPattern :: LPat GhcPs -> Maybe Literal
6666
getPattern (L (locA -> (RealSrcSpan patSpan _)) pat) = case pat of
6767
LitPat _ lit -> case lit of
6868
HsInt _ val -> fromIntegralLit patSpan val
69+
#if __GLASGOW_HASKELL__ < 913
6970
HsRat _ val _ -> fromFractionalLit patSpan val
71+
#endif
7072
_ -> Nothing
7173
NPat _ (L (locA -> (RealSrcSpan sSpan _)) overLit) _ _ -> fromOverLit overLit sSpan
7274
NPlusKPat _ _ (L (locA -> (RealSrcSpan sSpan _)) overLit1) _ _ _ -> fromOverLit overLit1 sSpan
7375
_ -> Nothing
7476
getPattern _ = Nothing
7577

76-
fromLit :: HsLit p -> RealSrcSpan -> Maybe Literal
78+
fromLit :: HsLit GhcPs -> RealSrcSpan -> Maybe Literal
7779
fromLit lit sSpan = case lit of
7880
HsInt _ val -> fromIntegralLit sSpan val
81+
#if __GLASGOW_HASKELL__ < 913
7982
HsRat _ val _ -> fromFractionalLit sSpan val
83+
#endif
8084
_ -> Nothing
8185

8286
fromOverLit :: HsOverLit p -> RealSrcSpan -> Maybe Literal

plugins/hls-change-type-signature-plugin/src/Ide/Plugin/ChangeTypeSignature.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,10 @@ import Development.IDE.Types.Diagnostics (_SomeStructuredMessage)
4242
import Generics.SYB (extQ, something)
4343
import GHC.Tc.Errors.Types (ErrInfo (..),
4444
TcRnMessageDetailed (..))
45+
#if MIN_VERSION_ghc(9,13,0)
46+
import GHC.Tc.Errors.Ppr (pprErrCtxtMsg)
47+
import GHC.Utils.Outputable (vcat)
48+
#endif
4549
import qualified Ide.Logger as Logger
4650
import Ide.Plugin.Error (PluginError,
4751
getNormalizedFilePathE)
@@ -61,8 +65,13 @@ data Log
6165

6266
instance Pretty Log where
6367
pretty = \case
68+
#if MIN_VERSION_ghc(9,13,0)
69+
LogErrInfoCtxt (ErrInfo ctxt _ _) ->
70+
fromSDoc (vcat $ map pprErrCtxtMsg ctxt)
71+
#else
6472
LogErrInfoCtxt (ErrInfo ctxt suppl) ->
6573
Logger.vcat [fromSDoc ctxt, fromSDoc suppl]
74+
#endif
6675
LogFindSigLocFailure name ->
6776
pretty ("Lookup signature location failure: " <> name)
6877
where
@@ -175,7 +184,11 @@ matchingDiagnostic ErrInfo{errInfoContext} =
175184
unwrapMatch (_, _, _, [name]) = Just name
176185
unwrapMatch _ = Nothing
177186

187+
#if MIN_VERSION_ghc(9,13,0)
188+
errInfoTxt = printOutputable (vcat $ map pprErrCtxtMsg errInfoContext)
189+
#else
178190
errInfoTxt = printOutputable errInfoContext
191+
#endif
179192

180193
-- | List of regexes that match various Error Messages
181194
errorMessageRegexes :: [Text]

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

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE GADTs #-}
23
{-# LANGUAGE LambdaCase #-}
34
{-# LANGUAGE OverloadedLists #-}
@@ -225,14 +226,18 @@ signatureToName :: InstanceBindTypeSig -> T.Text
225226
signatureToName sig = T.drop (T.length bindingPrefix) (printOutputable (bindName sig))
226227

227228
-- Return [groupName text, [(methodName text, signature text)]]
228-
minDefToMethodGroups :: HscEnv -> TcGblEnv -> Range -> [InstanceBindTypeSig] -> BooleanFormula Name -> [MethodGroup]
229+
minDefToMethodGroups :: HscEnv -> TcGblEnv -> Range -> [InstanceBindTypeSig] -> ClassMinimalDef -> [MethodGroup]
229230
minDefToMethodGroups hsc gblEnv range sigs minDef = makeMethodGroup <$> go minDef
230231
where
231232
makeMethodGroup methodDefinitions =
232233
let name = mconcat $ intersperse "," $ (\x -> "'" <> x <> "'") . fst <$> methodDefinitions
233234
in (name, methodDefinitions)
234235

236+
#if __GLASGOW_HASKELL__ >= 913
237+
go (Var lmn) = pure $ makeMethodDefinitions hsc gblEnv range $ filter ((==) (printOutputable (unLoc lmn)) . signatureToName) sigs
238+
#else
235239
go (Var mn) = pure $ makeMethodDefinitions hsc gblEnv range $ filter ((==) (printOutputable mn) . signatureToName) sigs
240+
#endif
236241
go (Or ms) = concatMap (go . unLoc) ms
237242
go (And ms) = foldr (liftA2 (<>) . go . unLoc) [[]] ms
238243
go (Parens m) = go (unLoc m)

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Handlers.hs

Lines changed: 33 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -87,6 +87,11 @@ import Data.List.Extra (unsnoc)
8787
import Development.IDE.Core.PluginUtils
8888
import Development.IDE.Types.Shake (toKey)
8989
import GHC.Types.SrcLoc (UnhelpfulSpanReason (UnhelpfulInteractive))
90+
#if MIN_VERSION_ghc(9,13,0)
91+
import GHC.Types.Avail (DetOrdAvails (DefinitelyDeterministicAvails))
92+
import GHC.Tc.Types (tcg_exports)
93+
import GHC.Types.Name.Set (nameSetElemsStable)
94+
#endif
9095
import Ide.Logger (Priority (..),
9196
Recorder,
9297
WithPriority,
@@ -262,11 +267,12 @@ initialiseSessionForEval needs_quickcheck st nfp = do
262267
-- it back to the iface for the current module.
263268
tm <- tmrTypechecked <$> use_ TypeCheck nfp
264269
let rdr_env = tcg_rdr_env tm
265-
let linkable_hsc = loadModulesHome (map (addRdrEnv . linkableHomeMod) linkables) deps_hsc
266270
addRdrEnv hmi
267271
| iface <- hm_iface hmi
268272
, ms_mod ms == mi_module iface
269-
#if MIN_VERSION_ghc(9,11,0)
273+
#if MIN_VERSION_ghc(9,13,0)
274+
= hmi { hm_iface = set_mi_top_env (IfaceTopEnv (DefinitelyDeterministicAvails $ tcg_exports tm) (mkIfaceImports $ tcg_import_decls tm)) iface}
275+
#elif MIN_VERSION_ghc(9,11,0)
270276
= hmi { hm_iface = set_mi_top_env (Just $ IfaceTopEnv (forceGlobalRdrEnv (globalRdrEnvLocal rdr_env)) (mkIfaceImports $ tcg_import_decls tm)) iface}
271277
#else
272278
= hmi { hm_iface = iface { mi_globals = Just $!
@@ -277,12 +283,20 @@ initialiseSessionForEval needs_quickcheck st nfp = do
277283
}}
278284
#endif
279285
| otherwise = hmi
280-
286+
#if MIN_VERSION_ghc(9,13,0)
287+
linkable_hsc <- liftIO $ loadModulesHome (map (addRdrEnv . linkableHomeMod) linkables) deps_hsc
288+
#else
289+
let linkable_hsc = loadModulesHome (map (addRdrEnv . linkableHomeMod) linkables) deps_hsc
290+
#endif
281291
return (ms, linkable_hsc)
282292
-- Bit awkward we need to use evalGhcEnv here but setContext requires to run
283293
-- in the Ghc monad
284294
env2 <- liftIO $ evalGhcEnv env1 $ do
295+
#if MIN_VERSION_ghc(9,13,0)
296+
setContext [Compat.IIModule (ms_mod ms)]
297+
#else
285298
setContext [Compat.IIModule (moduleName (ms_mod ms))]
299+
#endif
286300
let df = flip xopt_set LangExt.ExtendedDefaultRules
287301
. flip xopt_unset LangExt.MonomorphismRestriction
288302
. flip gopt_set Opt_ImplicitImportQualified
@@ -296,7 +310,14 @@ initialiseSessionForEval needs_quickcheck st nfp = do
296310
getSession
297311
return env2
298312

299-
#if MIN_VERSION_ghc(9,11,0)
313+
#if MIN_VERSION_ghc(9,13,0)
314+
mkIfaceImports :: [ImportUserSpec] -> [IfaceImport]
315+
mkIfaceImports = map go
316+
where
317+
go (ImpUserSpec decl ImpUserAll) = IfaceImport decl ImpIfaceAll
318+
go (ImpUserSpec decl (ImpUserExplicit avails parents)) = IfaceImport decl (ImpIfaceExplicit (DefinitelyDeterministicAvails avails) (nameSetElemsStable parents))
319+
go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut (nameSetElemsStable ns))
320+
#elif MIN_VERSION_ghc(9,11,0)
300321
mkIfaceImports :: [ImportUserSpec] -> [IfaceImport]
301322
mkIfaceImports = map go
302323
where
@@ -463,10 +484,18 @@ evals recorder mark_exception fp df stmts = do
463484
dbg $ LogEvalFlags flags
464485
ndf <- getInteractiveDynFlags
465486
dbg $ LogEvalPreSetDynFlags ndf
487+
#if MIN_VERSION_ghc(9,13,0)
488+
hsc_env <- getSession
489+
eans <-
490+
liftIO $ try @GhcException $
491+
parseDynamicFlagsCmdLine (hsc_logger hsc_env) ndf
492+
(map (L $ UnhelpfulSpan unhelpfulReason) flags)
493+
#else
466494
eans <-
467495
liftIO $ try @GhcException $
468496
parseDynamicFlagsCmdLine ndf
469497
(map (L $ UnhelpfulSpan unhelpfulReason) flags)
498+
#endif
470499
dbg $ LogEvalParsedFlags eans
471500
case eans of
472501
Left err -> pure $ Just $ errorLines $ show err

0 commit comments

Comments
 (0)