Skip to content

Commit 5580ffc

Browse files
authored
GHC 9.8 support (#3727)
* GHC 9.8 support for ghcide and non-exactprint plugins Requires head.hackage to build * Werror * Werror
1 parent 168976d commit 5580ffc

File tree

50 files changed

+345
-87
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

50 files changed

+345
-87
lines changed
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
[ "9.6", "9.4" , "9.2" , "9.0" ]
1+
[ "9.8", "9.6", "9.4" , "9.2" , "9.0" ]

.github/workflows/test.yml

+11-11
Original file line numberDiff line numberDiff line change
@@ -135,15 +135,15 @@ jobs:
135135
HLS_WRAPPER_TEST_EXE: hls-wrapper
136136
run: cabal test wrapper-test --test-options="$TEST_OPTS --rerun-log-file .tasty-rerun-log-wrapper"
137137

138-
- if: matrix.test
138+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
139139
name: Test hls-refactor-plugin
140140
run: cabal test hls-refactor-plugin --test-options="$TEST_OPTS" || cabal test hls-refactor-plugin --test-options="$TEST_OPTS"
141141

142-
- if: matrix.test && matrix.ghc != '9.6'
142+
- if: matrix.test && matrix.ghc != '9.6' && !startsWith(matrix.ghc,'9.8')
143143
name: Test hls-floskell-plugin
144144
run: cabal test hls-floskell-plugin --test-options="$TEST_OPTS" || cabal test hls-floskell-plugin --test-options="$TEST_OPTS"
145145

146-
- if: matrix.test
146+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
147147
name: Test hls-class-plugin
148148
run: cabal test hls-class-plugin --test-options="$TEST_OPTS" || cabal test hls-class-plugin --test-options="$TEST_OPTS"
149149

@@ -155,19 +155,19 @@ jobs:
155155
name: Test hls-eval-plugin
156156
run: cabal test hls-eval-plugin --test-options="$TEST_OPTS" || cabal test hls-eval-plugin --test-options="$TEST_OPTS"
157157

158-
- if: matrix.test
158+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
159159
name: Test hls-splice-plugin
160160
run: cabal test hls-splice-plugin --test-options="$TEST_OPTS" || cabal test hls-splice-plugin --test-options="$TEST_OPTS"
161161

162-
- if: matrix.test
162+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
163163
name: Test hls-stylish-haskell-plugin
164164
run: cabal test hls-stylish-haskell-plugin --test-options="$TEST_OPTS" || cabal test hls-stylish-haskell-plugin --test-options="$TEST_OPTS"
165165

166-
- if: matrix.test
166+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
167167
name: Test hls-ormolu-plugin
168168
run: cabal test hls-ormolu-plugin --test-options="$TEST_OPTS" || cabal test hls-ormolu-plugin --test-options="$TEST_OPTS"
169169

170-
- if: matrix.test
170+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
171171
name: Test hls-fourmolu-plugin
172172
run: cabal test hls-fourmolu-plugin --test-options="$TEST_OPTS" || cabal test hls-fourmolu-plugin --test-options="$TEST_OPTS"
173173

@@ -179,11 +179,11 @@ jobs:
179179
name: Test hls-call-hierarchy-plugin test suite
180180
run: cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS" || cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS"
181181

182-
- if: matrix.test && matrix.os != 'windows-latest'
182+
- if: matrix.test && matrix.os != 'windows-latest' && !startsWith(matrix.ghc,'9.8')
183183
name: Test hls-rename-plugin test suite
184184
run: cabal test hls-rename-plugin --test-options="$TEST_OPTS" || cabal test hls-rename-plugin --test-options="$TEST_OPTS"
185185

186-
- if: matrix.test
186+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
187187
name: Test hls-hlint-plugin test suite
188188
run: cabal test hls-hlint-plugin --test-options="$TEST_OPTS" || cabal test hls-hlint-plugin --test-options="$TEST_OPTS"
189189

@@ -207,7 +207,7 @@ jobs:
207207
name: Test hls-change-type-signature test suite
208208
run: cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS" || cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS"
209209

210-
- if: matrix.test
210+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
211211
name: Test hls-gadt-plugin test suit
212212
run: cabal test hls-gadt-plugin --test-options="$TEST_OPTS" || cabal test hls-gadt-plugin --test-options="$TEST_OPTS"
213213

@@ -228,7 +228,7 @@ jobs:
228228
name: Test hls-cabal-plugin test suite
229229
run: cabal test hls-cabal-plugin --test-options="$TEST_OPTS" || cabal test hls-cabal-plugin --test-options="$TEST_OPTS"
230230

231-
- if: matrix.test
231+
- if: matrix.test && !startsWith(matrix.ghc,'9.8')
232232
name: Test hls-retrie-plugin test suite
233233
run: cabal test hls-retrie-plugin --test-options="$TEST_OPTS" || cabal test hls-retrie-plugin --test-options="$TEST_OPTS"
234234

cabal.project

+30-1
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ package *
5252

5353
write-ghc-environment-files: never
5454

55-
index-state: 2023-09-08T00:00:00Z
55+
index-state: 2023-10-06T06:12:29Z
5656

5757
constraints:
5858
-- For GHC 9.4, older versions of entropy fail to build on Windows
@@ -101,3 +101,32 @@ if impl(ghc >= 9.5)
101101
-- ghc-9.6
102102
ekg-core:ghc-prim,
103103
stm-hamt:transformers,
104+
105+
if impl(ghc >= 9.7)
106+
allow-newer:
107+
-- ghc-9.8
108+
base,
109+
template-haskell,
110+
ghc,
111+
ghc-prim,
112+
integer-gmp,
113+
ghc-bignum,
114+
template-haskell,
115+
text,
116+
binary,
117+
bytestring,
118+
Cabal,
119+
unix,
120+
deepseq,
121+
122+
if impl(ghc >= 9.7)
123+
repository head.hackage.ghc.haskell.org
124+
url: https://ghc.gitlab.haskell.org/head.hackage/
125+
secure: True
126+
key-threshold: 3
127+
root-keys:
128+
f76d08be13e9a61a377a85e2fb63f4c5435d40f8feb3e12eb05905edb8cdea89
129+
26021a13b401500c8eb2761ca95c61f2d625bfef951b939a8124ed12ecf07329
130+
7541f32a4ccca4f97aea3b22f5e593ba2c0267546016b992dfadcd2fe944e55d
131+
132+
active-repositories: hackage.haskell.org, head.hackage.ghc.haskell.org

ghcide/ghcide.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ library
5959
dependent-sum,
6060
dlist,
6161
exceptions,
62-
extra >= 1.7.4,
62+
extra >= 1.7.14,
6363
enummapset,
6464
filepath,
6565
fingertree,

ghcide/session-loader/Development/IDE/Session.hs

+5-3
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,8 @@ import Data.Function
4040
import Data.Hashable hiding (hash)
4141
import qualified Data.HashMap.Strict as HM
4242
import Data.List
43+
import qualified Data.List.NonEmpty as NE
44+
import Data.List.NonEmpty (NonEmpty(..))
4345
import qualified Data.Map.Strict as Map
4446
import Data.Maybe
4547
import Data.Proxy
@@ -520,9 +522,9 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
520522
-- information.
521523

522524
new_deps = RawComponentInfo (homeUnitId_ df) df targets cfp opts dep_info
523-
: maybe [] snd oldDeps
525+
:| maybe [] snd oldDeps
524526
-- Get all the unit-ids for things in this component
525-
inplace = map rawComponentUnitId new_deps
527+
inplace = map rawComponentUnitId $ NE.toList new_deps
526528

527529
new_deps' <- forM new_deps $ \RawComponentInfo{..} -> do
528530
-- Remove all inplace dependencies from package flags for
@@ -572,7 +574,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
572574
-- . The information for the new component which caused this cache miss
573575
-- . The modified information (without -inplace flags) for
574576
-- existing packages
575-
pure (Map.insert hieYaml (newHscEnv, new_deps) m, (newHscEnv, head new_deps', tail new_deps'))
577+
pure (Map.insert hieYaml (newHscEnv, NE.toList new_deps) m, (newHscEnv, NE.head new_deps', NE.tail new_deps'))
576578

577579

578580
let session :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)

ghcide/src/Development/IDE/Core/Compile.hs

+49-6
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ import Data.Time (UTCTime (..))
7373
import Data.Tuple.Extra (dupe)
7474
import Data.Unique as Unique
7575
import Debug.Trace
76-
import Development.IDE.Core.FileStore (resetInterfaceStore, shareFilePath)
76+
import Development.IDE.Core.FileStore (resetInterfaceStore)
7777
import Development.IDE.Core.Preprocessor
7878
import Development.IDE.Core.RuleTypes
7979
import Development.IDE.Core.Shake
@@ -147,6 +147,13 @@ import GHC.Driver.Config.CoreToStg.Prep
147147
import GHC.Core.Lint.Interactive
148148
#endif
149149

150+
#if MIN_VERSION_ghc(9,7,0)
151+
import Data.Foldable (toList)
152+
import GHC.Unit.Module.Warnings
153+
#else
154+
import Development.IDE.Core.FileStore (shareFilePath)
155+
#endif
156+
150157
--Simple constants to make sure the source is consistently named
151158
sourceTypecheck :: T.Text
152159
sourceTypecheck = "typecheck"
@@ -479,11 +486,16 @@ filterUsages = id
479486
-- Important to do this immediately after reading the unit before
480487
-- anything else has a chance to read `mi_usages`
481488
shareUsages :: ModIface -> ModIface
482-
shareUsages iface = iface {mi_usages = usages}
489+
shareUsages iface
490+
= iface
491+
-- Fixed upstream in GHC 9.8
492+
#if !MIN_VERSION_ghc(9,7,0)
493+
{mi_usages = usages}
483494
where usages = map go (mi_usages iface)
484495
go usg@UsageFile{} = usg {usg_file_path = fp}
485496
where !fp = shareFilePath (usg_file_path usg)
486497
go usg = usg
498+
#endif
487499

488500

489501
mkHiFileResultNoCompile :: HscEnv -> TcModuleResult -> IO HiFileResult
@@ -646,11 +658,24 @@ compileModule (RunSimplifier simplify) session ms tcg =
646658
fmap (either (, Nothing) (second Just)) $
647659
catchSrcErrors (hsc_dflags session) "compile" $ do
648660
(warnings,desugared_guts) <- withWarnings "compile" $ \tweak -> do
649-
let session' = tweak (hscSetFlags (ms_hspp_opts ms) session)
661+
-- Breakpoints don't survive roundtripping from disk
662+
-- and this trips up the verify-core-files check
663+
-- They may also lead to other problems.
664+
-- We have to setBackend ghciBackend in 9.8 as otherwise
665+
-- non-exported definitions are stripped out.
666+
-- However, setting this means breakpoints are generated.
667+
-- Solution: prevent breakpoing generation by unsetting
668+
-- Opt_InsertBreakpoints
669+
let session' = tweak $ flip hscSetFlags session
670+
#if MIN_VERSION_ghc(9,7,0)
671+
$ flip gopt_unset Opt_InsertBreakpoints
672+
$ setBackend ghciBackend
673+
#endif
674+
$ ms_hspp_opts ms
650675
-- TODO: maybe settings ms_hspp_opts is unnecessary?
651676
-- MP: the flags in ModSummary should be right, if they are wrong then
652677
-- the correct place to fix this is when the ModSummary is created.
653-
desugar <- hscDesugar session' (ms { ms_hspp_opts = hsc_dflags session' }) tcg
678+
desugar <- hscDesugar session' (ms { ms_hspp_opts = hsc_dflags session' }) tcg
654679
if simplify
655680
then do
656681
plugins <- readIORef (tcg_th_coreplugins tcg)
@@ -779,23 +804,41 @@ unnecessaryDeprecationWarningFlags
779804
, Opt_WarnUnusedForalls
780805
, Opt_WarnUnusedRecordWildcards
781806
, Opt_WarnInaccessibleCode
807+
#if !MIN_VERSION_ghc(9,7,0)
782808
, Opt_WarnWarningsDeprecations
809+
#endif
783810
]
784811

785812
-- | Add a unnecessary/deprecated tag to the required diagnostics.
786813
#if MIN_VERSION_ghc(9,3,0)
787814
tagDiag :: (Maybe DiagnosticReason, FileDiagnostic) -> (Maybe DiagnosticReason, FileDiagnostic)
788-
tagDiag (w@(Just (WarningWithFlag warning)), (nfp, sh, fd))
789815
#else
790816
tagDiag :: (WarnReason, FileDiagnostic) -> (WarnReason, FileDiagnostic)
791-
tagDiag (w@(Reason warning), (nfp, sh, fd))
792817
#endif
818+
819+
#if MIN_VERSION_ghc(9,7,0)
820+
tagDiag (w@(Just (WarningWithCategory cat)), (nfp, sh, fd))
821+
| cat == defaultWarningCategory -- default warning category is for deprecations
822+
= (w, (nfp, sh, fd { _tags = Just $ DiagnosticTag_Deprecated : concat (_tags fd) }))
823+
tagDiag (w@(Just (WarningWithFlags warnings)), (nfp, sh, fd))
824+
| tags <- mapMaybe requiresTag (toList warnings)
825+
= (w, (nfp, sh, fd { _tags = Just $ tags ++ concat (_tags fd) }))
826+
#elif MIN_VERSION_ghc(9,3,0)
827+
tagDiag (w@(Just (WarningWithFlag warning)), (nfp, sh, fd))
828+
| Just tag <- requiresTag warning
829+
= (w, (nfp, sh, fd { _tags = Just $ tag : concat (_tags fd) }))
830+
#else
831+
tagDiag (w@(Reason warning), (nfp, sh, fd))
793832
| Just tag <- requiresTag warning
794833
= (w, (nfp, sh, fd { _tags = Just $ tag : concat (_tags fd) }))
834+
#endif
795835
where
796836
requiresTag :: WarningFlag -> Maybe DiagnosticTag
837+
#if !MIN_VERSION_ghc(9,7,0)
838+
-- doesn't exist on 9.8, we use WarningWithCategory instead
797839
requiresTag Opt_WarnWarningsDeprecations
798840
= Just DiagnosticTag_Deprecated
841+
#endif
799842
requiresTag wflag -- deprecation was already considered above
800843
| wflag `elem` unnecessaryDeprecationWarningFlags
801844
= Just DiagnosticTag_Unnecessary

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

+6-2
Original file line numberDiff line numberDiff line change
@@ -52,8 +52,12 @@ doCpp env input_fn output_fn =
5252

5353
#if MIN_VERSION_ghc(9,5,0)
5454
let cpp_opts = Pipeline.CppOpts
55-
{ cppUseCc = False
56-
, cppLinePragmas = True
55+
{ cppLinePragmas = True
56+
# if MIN_VERSION_ghc(9,9,0)
57+
, useHsCpp = True
58+
# else
59+
, cppUseCc = False
60+
# endif
5761
} in
5862
#else
5963
let cpp_opts = True in

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

+23-2
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,8 @@ module Development.IDE.GHC.Compat(
4141

4242
Usage(..),
4343

44+
liftZonkM,
45+
4446
FastStringCompat,
4547
bytesFS,
4648
mkFastStringByteString,
@@ -55,6 +57,7 @@ module Development.IDE.GHC.Compat(
5557
combineRealSrcSpans,
5658

5759
nonDetOccEnvElts,
60+
nonDetFoldOccEnv,
5861

5962
isQualifiedImport,
6063
GhcVersion(..),
@@ -93,6 +96,7 @@ module Development.IDE.GHC.Compat(
9396
simplifyExpr,
9497
tidyExpr,
9598
emptyTidyEnv,
99+
tcInitTidyEnv,
96100
corePrepExpr,
97101
corePrepPgm,
98102
lintInteractiveExpr,
@@ -165,6 +169,9 @@ import qualified Data.Set as S
165169

166170
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
167171

172+
#if MIN_VERSION_ghc(9,7,0)
173+
import GHC.Tc.Zonk.TcType (tcInitTidyEnv)
174+
#endif
168175
import qualified GHC.Core.Opt.Pipeline as GHC
169176
import GHC.Core.Tidy (tidyExpr)
170177
import GHC.CoreToStg.Prep (corePrepPgm)
@@ -247,6 +254,15 @@ import GHC.Driver.Config.CoreToStg (initCoreTo
247254
import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig)
248255
#endif
249256

257+
#if !MIN_VERSION_ghc(9,7,0)
258+
liftZonkM :: a -> a
259+
liftZonkM = id
260+
#endif
261+
262+
#if !MIN_VERSION_ghc(9,7,0)
263+
nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
264+
nonDetFoldOccEnv = foldOccEnv
265+
#endif
250266

251267
#if !MIN_VERSION_ghc(9,3,0)
252268
nonDetOccEnvElts :: OccEnv a -> [a]
@@ -328,7 +344,9 @@ myCoreToStg logger dflags ictxt
328344
#endif
329345
this_mod ml prepd_binds
330346

331-
#if MIN_VERSION_ghc(9,4,2)
347+
#if MIN_VERSION_ghc(9,8,0)
348+
(unzip -> (stg_binds2,_),_)
349+
#elif MIN_VERSION_ghc(9,4,2)
332350
(stg_binds2,_)
333351
#else
334352
stg_binds2
@@ -537,13 +555,16 @@ data GhcVersion
537555
| GHC92
538556
| GHC94
539557
| GHC96
558+
| GHC98
540559
deriving (Eq, Ord, Show)
541560

542561
ghcVersionStr :: String
543562
ghcVersionStr = VERSION_ghc
544563

545564
ghcVersion :: GhcVersion
546-
#if MIN_VERSION_GLASGOW_HASKELL(9,6,0,0)
565+
#if MIN_VERSION_GLASGOW_HASKELL(9,8,0,0)
566+
ghcVersion = GHC98
567+
#elif MIN_VERSION_GLASGOW_HASKELL(9,6,0,0)
547568
ghcVersion = GHC96
548569
#elif MIN_VERSION_GLASGOW_HASKELL(9,4,0,0)
549570
ghcVersion = GHC94

0 commit comments

Comments
 (0)