Skip to content

Commit 75320f1

Browse files
authored
Merge branch 'master' into wip/9.4-rename
2 parents 1592496 + dfd8f0b commit 75320f1

File tree

11 files changed

+64
-45
lines changed

11 files changed

+64
-45
lines changed

.github/mergify.yml

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,3 +13,15 @@ pull_request_rules:
1313
queue:
1414
method: squash
1515
name: default
16+
# The queue action automatically updates PRs that
17+
# have entered the queue, but in order to do that
18+
# they must have passed CI. Since our CI is a bit
19+
# flaky, PRs can fail to get in, which then means
20+
# they don't get updated, which is extra annoying.
21+
# This just adds the updating as an independent
22+
# step.
23+
- name: Automatically update pull requests
24+
conditions:
25+
- label=merge me
26+
actions:
27+
update:

.github/workflows/test.yml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,7 @@ jobs:
169169
name: Test hls-brittany-plugin
170170
run: cabal test hls-brittany-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-brittany-plugin --test-options="$TEST_OPTS"
171171

172-
- if: matrix.test && matrix.ghc != '9.4.2' && matrix.ghc != '9.4.3'
172+
- if: matrix.test
173173
name: Test hls-refactor-plugin
174174
run: cabal test hls-refactor-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-refactor-plugin --test-options="$TEST_OPTS"
175175

@@ -193,7 +193,7 @@ jobs:
193193
name: Test hls-haddock-comments-plugin
194194
run: cabal test hls-haddock-comments-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-haddock-comments-plugin --test-options="$TEST_OPTS"
195195

196-
- if: matrix.test && matrix.ghc != '9.4.2' && matrix.ghc != '9.4.3'
196+
- if: matrix.test
197197
name: Test hls-splice-plugin
198198
run: cabal test hls-splice-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-splice-plugin --test-options="$TEST_OPTS"
199199

@@ -205,7 +205,7 @@ jobs:
205205
name: Test hls-ormolu-plugin
206206
run: cabal test hls-ormolu-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-ormolu-plugin --test-options="$TEST_OPTS"
207207

208-
- if: matrix.test && matrix.ghc != '9.4.2' && matrix.ghc != '9.4.3'
208+
- if: matrix.test
209209
name: Test hls-fourmolu-plugin
210210
run: cabal test hls-fourmolu-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-fourmolu-plugin --test-options="$TEST_OPTS"
211211

@@ -229,7 +229,7 @@ jobs:
229229
name: Test hls-rename-plugin test suite
230230
run: cabal test hls-rename-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-rename-plugin --test-options="$TEST_OPTS"
231231

232-
- if: matrix.test && matrix.ghc != '9.4.2' && matrix.ghc != '9.4.3'
232+
- if: matrix.test
233233
name: Test hls-hlint-plugin test suite
234234
run: cabal test hls-hlint-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-hlint-plugin --test-options="$TEST_OPTS"
235235

@@ -249,15 +249,15 @@ jobs:
249249
name: Test hls-qualify-imported-names-plugin test suite
250250
run: cabal test hls-qualify-imported-names-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-qualify-imported-names-plugin --test-options="$TEST_OPTS"
251251

252-
- if: matrix.test && matrix.ghc != '9.4.2' && matrix.ghc != '9.4.3'
252+
- if: matrix.test
253253
name: Test hls-code-range-plugin test suite
254254
run: cabal test hls-code-range-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-code-range-plugin --test-options="$TEST_OPTS"
255255

256256
- if: matrix.test
257257
name: Test hls-change-type-signature test suite
258258
run: cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS"
259259

260-
- if: matrix.test && matrix.ghc != '9.4.2' && matrix.ghc != '9.4.3'
260+
- if: matrix.test
261261
name: Test hls-gadt-plugin test suit
262262
run: cabal test hls-gadt-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-gadt-plugin --test-options="$TEST_OPTS"
263263

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

Lines changed: 18 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -427,14 +427,24 @@ tcRnModule hsc_env tc_helpers pmod = do
427427
tc_gbl_env = tc_gbl_env' { tcg_ann_env = extendAnnEnvList (tcg_ann_env tc_gbl_env') mod_env_anns }
428428
pure (TcModuleResult pmod rn_info tc_gbl_env splices False mod_env)
429429

430+
431+
-- Note [Clearing mi_globals after generating an iface]
432+
-- GHC populates the mi_global field in interfaces for GHCi if we are using the bytecode
433+
-- interpreter.
434+
-- However, this field is expensive in terms of heap usage, and we don't use it in HLS
435+
-- anywhere. So we zero it out.
436+
-- The field is not serialized or deserialised from disk, so we don't need to remove it
437+
-- while reading an iface from disk, only if we just generated an iface in memory
438+
430439
mkHiFileResultNoCompile :: HscEnv -> TcModuleResult -> IO HiFileResult
431440
mkHiFileResultNoCompile session tcm = do
432441
let hsc_env_tmp = hscSetFlags (ms_hspp_opts ms) session
433442
ms = pm_mod_summary $ tmrParsed tcm
434443
tcGblEnv = tmrTypechecked tcm
435444
details <- makeSimpleDetails hsc_env_tmp tcGblEnv
436445
sf <- finalSafeMode (ms_hspp_opts ms) tcGblEnv
437-
iface <- mkIfaceTc hsc_env_tmp sf details ms tcGblEnv
446+
iface' <- mkIfaceTc hsc_env_tmp sf details ms tcGblEnv
447+
let iface = iface' { mi_globals = Nothing } -- See Note [Clearing mi_globals after generating an iface]
438448
pure $! mkHiFileResult ms iface details (tmrRuntimeModules tcm) Nothing
439449

440450
mkHiFileResultCompile
@@ -467,15 +477,16 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
467477
#endif
468478
simplified_guts
469479

470-
final_iface <- mkFullIface session partial_iface Nothing
480+
final_iface' <- mkFullIface session partial_iface Nothing
471481
#if MIN_VERSION_ghc(9,4,2)
472482
Nothing
473483
#endif
474484

475485
#else
476486
let !partial_iface = force (mkPartialIface session details simplified_guts)
477-
final_iface <- mkFullIface session partial_iface
487+
final_iface' <- mkFullIface session partial_iface
478488
#endif
489+
let final_iface = final_iface' {mi_globals = Nothing} -- See Note [Clearing mi_globals after generating an iface]
479490

480491
-- Write the core file now
481492
core_file <- case mguts of
@@ -986,7 +997,7 @@ loadModulesHome
986997
-> HscEnv
987998
loadModulesHome mod_infos e =
988999
#if MIN_VERSION_ghc(9,3,0)
989-
hscUpdateHUG (\hug -> foldr addHomeModInfoToHug hug mod_infos) (e { hsc_type_env_vars = emptyKnotVars })
1000+
hscUpdateHUG (\hug -> foldl' (flip addHomeModInfoToHug) hug mod_infos) (e { hsc_type_env_vars = emptyKnotVars })
9901001
#else
9911002
let !new_modules = addListToHpt (hsc_HPT e) [(mod_name x, x) | x <- mod_infos]
9921003
in e { hsc_HPT = new_modules
@@ -1090,7 +1101,8 @@ getModSummaryFromImports
10901101
-> Maybe Util.StringBuffer
10911102
-> ExceptT [FileDiagnostic] IO ModSummaryResult
10921103
getModSummaryFromImports env fp modTime contents = do
1093-
(contents, opts, env) <- preprocessor env fp contents
1104+
1105+
(contents, opts, env, src_hash) <- preprocessor env fp contents
10941106

10951107
let dflags = hsc_dflags env
10961108

@@ -1141,9 +1153,6 @@ getModSummaryFromImports env fp modTime contents = do
11411153
liftIO $ evaluate $ rnf srcImports
11421154
liftIO $ evaluate $ rnf textualImports
11431155

1144-
#if MIN_VERSION_ghc (9,3,0)
1145-
!src_hash <- liftIO $ fingerprintFromStringBuffer contents
1146-
#endif
11471156

11481157
modLoc <- liftIO $ if mod == mAIN_NAME
11491158
-- specially in tests it's common to have lots of nameless modules
@@ -1454,18 +1463,6 @@ loadInterface session ms linkableNeeded RecompilationInfo{..} = do
14541463

14551464
case (mb_checked_iface, recomp_iface_reqd) of
14561465
(Just iface, UpToDate) -> do
1457-
-- If we have an old value, just return it
1458-
case old_value of
1459-
Just (old_hir, _)
1460-
| isNothing linkableNeeded || isJust (hirCoreFp old_hir)
1461-
-> do
1462-
-- Perform the fine grained recompilation check for TH
1463-
maybe_recomp <- checkLinkableDependencies get_linkable_hashes (hsc_mod_graph sessionWithMsDynFlags) (hirRuntimeModules old_hir)
1464-
case maybe_recomp of
1465-
Just msg -> do_regenerate msg
1466-
Nothing -> return ([], Just old_hir)
1467-
-- Otherwise use the value from disk, provided the core file is up to date if required
1468-
_ -> do
14691466
details <- liftIO $ mkDetailsFromIface sessionWithMsDynFlags iface
14701467
-- parse the runtime dependencies from the annotations
14711468
let runtime_deps
@@ -1552,7 +1549,7 @@ showReason (RecompBecause s) = s
15521549
mkDetailsFromIface :: HscEnv -> ModIface -> IO ModDetails
15531550
mkDetailsFromIface session iface = do
15541551
fixIO $ \details -> do
1555-
let hsc' = hscUpdateHPT (\hpt -> addToHpt hpt (moduleName $ mi_module iface) (HomeModInfo iface details Nothing)) session
1552+
let !hsc' = hscUpdateHPT (\hpt -> addToHpt hpt (moduleName $ mi_module iface) (HomeModInfo iface details Nothing)) session
15561553
initIfaceLoad hsc' (typecheckIface iface)
15571554

15581555
coreFileToCgGuts :: HscEnv -> ModIface -> ModDetails -> CoreFile -> IO CgGuts

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

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Development.IDE.Core.Preprocessor
88

99
import Development.IDE.GHC.Compat
1010
import qualified Development.IDE.GHC.Compat.Util as Util
11+
import qualified Development.IDE.GHC.Util as Util
1112
import Development.IDE.GHC.CPP
1213
import Development.IDE.GHC.Orphans ()
1314

@@ -36,7 +37,7 @@ import GHC.Utils.Outputable (renderWithContext)
3637

3738
-- | Given a file and some contents, apply any necessary preprocessors,
3839
-- e.g. unlit/cpp. Return the resulting buffer and the DynFlags it implies.
39-
preprocessor :: HscEnv -> FilePath -> Maybe Util.StringBuffer -> ExceptT [FileDiagnostic] IO (Util.StringBuffer, [String], HscEnv)
40+
preprocessor :: HscEnv -> FilePath -> Maybe Util.StringBuffer -> ExceptT [FileDiagnostic] IO (Util.StringBuffer, [String], HscEnv, Util.Fingerprint)
4041
preprocessor env filename mbContents = do
4142
-- Perform unlit
4243
(isOnDisk, contents) <-
@@ -48,6 +49,10 @@ preprocessor env filename mbContents = do
4849
let isOnDisk = isNothing mbContents
4950
return (isOnDisk, contents)
5051

52+
-- Compute the source hash before the preprocessor because this is
53+
-- how GHC does it.
54+
!src_hash <- liftIO $ Util.fingerprintFromStringBuffer contents
55+
5156
-- Perform cpp
5257
(opts, env) <- ExceptT $ parsePragmasIntoHscEnv env filename contents
5358
let dflags = hsc_dflags env
@@ -73,11 +78,11 @@ preprocessor env filename mbContents = do
7378

7479
-- Perform preprocessor
7580
if not $ gopt Opt_Pp dflags then
76-
return (contents, opts, env)
81+
return (contents, opts, env, src_hash)
7782
else do
7883
contents <- liftIO $ runPreprocessor env filename $ if isOnDisk then Nothing else Just contents
7984
(opts, env) <- ExceptT $ parsePragmasIntoHscEnv env filename contents
80-
return (contents, opts, env)
85+
return (contents, opts, env, src_hash)
8186
where
8287
logAction :: IORef [CPPLog] -> LogActionCompat
8388
logAction cppLogs dflags _reason severity srcSpan _style msg = do

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -503,7 +503,7 @@ getModuleHash = mi_mod_hash . mi_final_exts
503503

504504
disableWarningsAsErrors :: DynFlags -> DynFlags
505505
disableWarningsAsErrors df =
506-
flip gopt_unset Opt_WarnIsError $ foldl' wopt_unset_fatal df [toEnum 0 ..]
506+
flip gopt_unset Opt_WarnIsError $! foldl' wopt_unset_fatal df [toEnum 0 ..]
507507

508508
isQualifiedImport :: ImportDecl a -> Bool
509509
isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False

ghcide/src/Development/IDE/Types/Action.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -69,13 +69,13 @@ abortQueue :: DelayedActionInternal -> ActionQueue -> STM ()
6969
abortQueue x ActionQueue {..} = do
7070
qq <- flushTQueue newActions
7171
mapM_ (writeTQueue newActions) (filter (/= x) qq)
72-
modifyTVar inProgress (Set.delete x)
72+
modifyTVar' inProgress (Set.delete x)
7373

7474
-- | Mark an action as complete when called after 'popQueue'.
7575
-- Has no effect otherwise
7676
doneQueue :: DelayedActionInternal -> ActionQueue -> STM ()
7777
doneQueue x ActionQueue {..} = do
78-
modifyTVar inProgress (Set.delete x)
78+
modifyTVar' inProgress (Set.delete x)
7979

8080
countQueue :: ActionQueue -> STM Natural
8181
countQueue ActionQueue{..} = do

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE TypeFamilies #-}
66
{-# LANGUAGE ViewPatterns #-}
7+
{-# LANGUAGE BangPatterns #-}
78

89
module Ide.Plugin.Class.Types where
910

@@ -45,7 +46,7 @@ data GetInstanceBindTypeSigs = GetInstanceBindTypeSigs
4546

4647
data InstanceBindTypeSig = InstanceBindTypeSig
4748
{ bindName :: Name
48-
, bindRendered :: T.Text
49+
, bindRendered :: !T.Text
4950
, bindDefSpan :: Maybe SrcSpan
5051
-- ^SrcSpan for the bind definition
5152
}

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -182,11 +182,11 @@ suggestionsTests =
182182
doc <- openDoc "IgnoreAnnHlint.hs" "haskell"
183183
expectNoMoreDiagnostics 3 doc "hlint"
184184

185-
, knownBrokenForGhcVersions [GHC92] "apply-refact has different behavior on v0.10" $
185+
, knownBrokenForGhcVersions [GHC92, GHC94] "apply-refact has different behavior on v0.10" $
186186
testCase "apply-refact preserve regular comments" $ runHlintSession "" $ do
187187
testRefactor "Comments.hs" "Redundant bracket" expectedComments
188188

189-
, onlyRunForGhcVersions [GHC92] "only run test for apply-refact-0.10" $
189+
, onlyRunForGhcVersions [GHC92, GHC94] "only run test for apply-refact-0.10" $
190190
testCase "apply-refact preserve regular comments" $ runHlintSession "" $ do
191191
testRefactor "Comments.hs" "Redundant bracket" expectedComments'
192192

plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -698,7 +698,7 @@ annotate dflags needs_space ast = do
698698
let rendered = render dflags ast
699699
#if MIN_VERSION_ghc(9,4,0)
700700
expr' <- lift $ mapLeft (showSDoc dflags . ppr) $ parseAST dflags uniq rendered
701-
pure expr'
701+
pure $ setPrecedingLines expr' 0 (bool 0 1 needs_space)
702702
#elif MIN_VERSION_ghc(9,2,0)
703703
expr' <- lift $ mapLeft show $ parseAST dflags uniq rendered
704704
pure $ setPrecedingLines expr' 0 (bool 0 1 needs_space)

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

Lines changed: 12 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -608,7 +608,7 @@ renameActionTests = testGroup "rename actions"
608608
doc <- createDoc "Testing.hs" "haskell" content
609609
_ <- waitForDiagnostics
610610
actionsOrCommands <- getCodeActions doc (Range (Position 3 12) (Position 3 20))
611-
[fixTypo] <- pure [action | InR action@CodeAction{ _title = actionTitle } <- actionsOrCommands, "monus" `T.isInfixOf` actionTitle ]
611+
[fixTypo] <- pure [action | InR action@CodeAction{ _title = actionTitle } <- actionsOrCommands, "monus" `T.isInfixOf` actionTitle , "Replace" `T.isInfixOf` actionTitle]
612612
executeCodeAction fixTypo
613613
contentAfterAction <- documentContents doc
614614
let expectedContentAfterAction = T.unlines
@@ -1669,8 +1669,10 @@ suggestImportTests = testGroup "suggest import actions"
16691669
, test True [] "f = empty" [] "import Control.Applicative (empty)"
16701670
, test True [] "f = empty" [] "import Control.Applicative"
16711671
, test True [] "f = (&)" [] "import Data.Function ((&))"
1672-
, test True [] "f = NE.nonEmpty" [] "import qualified Data.List.NonEmpty as NE"
1673-
, test True [] "f = Data.List.NonEmpty.nonEmpty" [] "import qualified Data.List.NonEmpty"
1672+
, ignoreForGHC94 "On GHC 9.4 the error message doesn't contain the qualified module name: https://gitlab.haskell.org/ghc/ghc/-/issues/20472"
1673+
$ test True [] "f = NE.nonEmpty" [] "import qualified Data.List.NonEmpty as NE"
1674+
, ignoreForGHC94 "On GHC 9.4 the error message doesn't contain the qualified module name: https://gitlab.haskell.org/ghc/ghc/-/issues/20472"
1675+
$ test True [] "f = Data.List.NonEmpty.nonEmpty" [] "import qualified Data.List.NonEmpty"
16741676
, test True [] "f :: Typeable a => a" ["f = undefined"] "import Data.Typeable (Typeable)"
16751677
, test True [] "f = pack" [] "import Data.Text (pack)"
16761678
, test True [] "f :: Text" ["f = undefined"] "import Data.Text (Text)"
@@ -1679,14 +1681,17 @@ suggestImportTests = testGroup "suggest import actions"
16791681
, test True [] "f = (.|.)" [] "import Data.Bits (Bits((.|.)))"
16801682
, test True [] "f = (.|.)" [] "import Data.Bits ((.|.))"
16811683
, test True [] "f :: a ~~ b" [] "import Data.Type.Equality ((~~))"
1682-
, test True
1684+
, ignoreForGHC94 "On GHC 9.4 the error message doesn't contain the qualified module name: https://gitlab.haskell.org/ghc/ghc/-/issues/20472"
1685+
$ test True
16831686
["qualified Data.Text as T"
16841687
] "f = T.putStrLn" [] "import qualified Data.Text.IO as T"
1685-
, test True
1688+
, ignoreForGHC94 "On GHC 9.4 the error message doesn't contain the qualified module name: https://gitlab.haskell.org/ghc/ghc/-/issues/20472"
1689+
$ test True
16861690
[ "qualified Data.Text as T"
16871691
, "qualified Data.Function as T"
16881692
] "f = T.putStrLn" [] "import qualified Data.Text.IO as T"
1689-
, test True
1693+
, ignoreForGHC94 "On GHC 9.4 the error message doesn't contain the qualified module name: https://gitlab.haskell.org/ghc/ghc/-/issues/20472"
1694+
$ test True
16901695
[ "qualified Data.Text as T"
16911696
, "qualified Data.Function as T"
16921697
, "qualified Data.Functor as T"
@@ -3784,7 +3789,7 @@ ignoreForGHC92 :: String -> TestTree -> TestTree
37843789
ignoreForGHC92 = ignoreFor (BrokenForGHC [GHC92])
37853790

37863791
ignoreForGHC94 :: String -> TestTree -> TestTree
3787-
ignoreForGHC94 = ignoreFor (BrokenForGHC [GHC94])
3792+
ignoreForGHC94 = knownIssueFor Broken (BrokenForGHC [GHC94])
37883793

37893794
data BrokenTarget =
37903795
BrokenSpecific OS [GhcVersion]

plugins/hls-refactor-plugin/test/data/hiding/hie.yaml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@ cradle:
22
direct:
33
arguments:
44
- -Wall
5-
- HideFunction.hs
65
- AVec.hs
76
- BVec.hs
87
- CVec.hs

0 commit comments

Comments
 (0)