Skip to content

Commit

Permalink
Support for 9.10 (#4233)
Browse files Browse the repository at this point in the history
* Support for 9.10

This includes supports for all plugins, other than formatters and hlint.

We need ghc-exactprint and retrie release before merging this.

* Remove indexed-traversable allow-newer

* Fix couple of warnings

* Fix flags job for hls-graph

* foldl' exposed from Prelude since base 4.20

* Fix flags job for hls-plugin-api

* Fix ghcide hover test

* Fix flags job for hls-eval-plugin

* unzip since 4.19

* More pedantic fixes

* Don't CPP in tests, fix another test

* Switch to ghc-exactprint and witherable from hackage

* Fix all warnings in hls-refactor-plugin

* Remove more no longer necessary allow newers

* Fix all warnings in hls-gadp-plugin and hls-qualify-imported-names-plugin

* Remove allow-newer for boring

* Bump to lsp 2.6, remove more allow-newers

* outline tests

* disable simple plugin on 9.10

* Remove allow-newer for ghc-trace-events

* fix appendConstraint

* stylish

* Remove commutative-semigroups and monoid-subclasses from allow-newer

* Remove free from allow-newer

* Fix 'type wilcard actions' tests

* Remove hie-bios from allow-newer

* Fix suggestNewDefinition tests

* Revert "Fix suggestNewDefinition tests"

This reverts commit 2f3300e.

* Remove makeDeltaAst breaking tests unrelated to addArgument

* Fix 79 code action tests

* Fix 12 more tests

* Remove co-log-core from allow-newer

* Fix 21 more tests

* Fix 8 import disambiguation tests

* fix windows ghcide tests

* Fix adding argument to function body

* update retrie commit, progress in add argument tests

* Fix few stylish-haskell parse errors

* Fix remaining redundant constraint tests

* Remove allow-newer for constraint-extras

* Fix warnings after master merge

* Fix most add argument tests except for one

* Remove dependent-map from allow-newer

* Try removing some allow-newers from lsp

* Ormolu is updated, add links for other tool dependencies

* Revert "Try removing some allow-newers from lsp"

This reverts commit 6f60029.

* Try this

* Fix all gadt plugin and most class plugin tests, enable 2 tests for ghc 9.4+

* Undo spurious changes

* Update eval plugin tests

* Disable broken refactor plugin test for now

* Fix warnings

* Add source-repository-package to unblock floskell

* Make call hierarchy plugin tests green

* fix semantic tokens 9.10

* Fix remaining class plugin test

* Update hls-change-type tests

* Make class plugin more robust

* Fix stylish parse errors, simplify CPP

* Cleanups

* Remove retrie dep from hls-refactor-plugin

* More retrie fixes

* Fix cabal-plugin-tests by respecting maxCompletions client cfg + a bit of CPP

* Fixup ghcide-tests

* disable retrie, splice and floskell plugins for 9.10

* Update tested-with + fix import warning

* Fix stylish

* Fix compilation with 9.2.8, fix stack jobs

* Remove no longer relevant :type +v test

* Disable tests of disabled plugins in CI

* Try a better broken specifier?

* Fix invalid CI config

* Use getClientConfigAction instead of introducing new HandlerM action

* Move CPPd imports to prevent stylish from evaluating CPP

* Disable stan tests with ghc 9.10 in CI

* attempt fixing exactprint <9.10

* Try enabling fourmolu now

* Revert "Try enabling fourmolu now"

This reverts commit 7142686.

* Update code-range-plugin tests

* Fix No newline at the end of file

* Use more recent cabal-gild

* Try setting some linker flags for macos

* Ignore non-local variable completion test on windows for GHC 9.8

---------

Co-authored-by: Jan Hrček <[email protected]>
Co-authored-by: Patrick <[email protected]>
Co-authored-by: Michael Peyton Jones <[email protected]>
Co-authored-by: Fendor <[email protected]>
  • Loading branch information
5 people authored Jun 13, 2024
1 parent c11f32b commit 3009a45
Show file tree
Hide file tree
Showing 182 changed files with 1,572 additions and 432 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/supported-ghc-versions.json
Original file line number Diff line number Diff line change
@@ -1 +1 @@
[ "9.8", "9.6", "9.4" , "9.2" ]
["9.10", "9.8", "9.6", "9.4" , "9.2" ]
23 changes: 15 additions & 8 deletions .github/workflows/test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ jobs:
- uses: ./.github/actions/setup-build
with:
ghc: ${{ matrix.ghc }}
os: ${{ runner.os }}
os: ${{ runner.os }}

- name: Build
run: cabal build all
Expand Down Expand Up @@ -141,7 +141,8 @@ jobs:
name: Test hls-refactor-plugin
run: cabal test hls-refactor-plugin-tests || cabal test hls-refactor-plugin-tests

- if: matrix.test
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.10'
name: Test hls-floskell-plugin
run: cabal test hls-floskell-plugin-tests || cabal test hls-floskell-plugin-tests

Expand All @@ -157,23 +158,27 @@ jobs:
name: Test hls-eval-plugin
run: cabal test hls-eval-plugin-tests || cabal test hls-eval-plugin-tests

- if: matrix.test
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.10'
name: Test hls-splice-plugin
run: cabal test hls-splice-plugin-tests || cabal test hls-splice-plugin-tests

- if: matrix.test && matrix.ghc != '9.2'
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.2' && matrix.ghc != '9.10'
name: Test hls-stan-plugin
run: cabal test hls-stan-plugin-tests || cabal test hls-stan-plugin-tests

- if: matrix.test
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.10'
name: Test hls-stylish-haskell-plugin
run: cabal test hls-stylish-haskell-plugin-tests || cabal test hls-stylish-haskell-plugin-tests

- if: matrix.test
name: Test hls-ormolu-plugin
run: cabal test hls-ormolu-plugin-tests || cabal test hls-ormolu-plugin-tests

- if: matrix.test
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.10'
name: Test hls-fourmolu-plugin
run: cabal test hls-fourmolu-plugin-tests || cabal test hls-fourmolu-plugin-tests

Expand All @@ -189,7 +194,8 @@ jobs:
name: Test hls-rename-plugin test suite
run: cabal test hls-rename-plugin-tests || cabal test hls-rename-plugin-tests

- if: matrix.test
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.10'
name: Test hls-hlint-plugin test suite
run: cabal test hls-hlint-plugin-tests || cabal test hls-hlint-plugin-tests

Expand Down Expand Up @@ -238,7 +244,8 @@ jobs:
name: Test hls-cabal-plugin test suite
run: cabal test hls-cabal-plugin-tests || cabal test hls-cabal-plugin-tests

- if: matrix.test
# TODO enable when it supports 9.10
- if: matrix.test && matrix.ghc != '9.10'
name: Test hls-retrie-plugin test suite
run: cabal test hls-retrie-plugin-tests || cabal test hls-retrie-plugin-tests

Expand Down
31 changes: 28 additions & 3 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -7,12 +7,12 @@ packages:
./hls-plugin-api
./hls-test-utils

index-state: 2024-06-07T00:00:00Z
index-state: 2024-06-10T12:08:58Z

tests: True
test-show-details: direct

benchmarks: True
-- benchmarks: True

write-ghc-environment-files: never

Expand Down Expand Up @@ -40,4 +40,29 @@ constraints:
-- the flag '-fopen-simd', which blocked the release 2.2.0.0.
-- We want to be able to benefit from the performance optimisations
-- in the future, thus: TODO: remove this flag.
bitvec -simd
bitvec -simd,


if impl(ghc >= 9.9)
benchmarks: False
constraints:
lens >= 5.3.2,
-- See
-- https://github.com/haskell/stylish-haskell/issues/479
-- https://github.com/fourmolu/fourmolu/issues/412
-- https://github.com/ennocramer/floskell/pull/82
-- https://github.com/ndmitchell/hlint/pull/1594
haskell-language-server -stylishHaskell -fourmolu -hlint -retrie -splice -floskell,
allow-newer:
entropy:base,
entropy:directory,
entropy:filepath,
entropy:process,
haddock-library:base,
haddock-library:containers,
-- These can be removed when we get a new lsp release
quickcheck-instances:base,
quickcheck-instances:containers,
uuid-types:template-haskell,
else
benchmarks: True
2 changes: 1 addition & 1 deletion ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ homepage:
https://github.com/haskell/haskell-language-server/tree/master/ghcide#readme

bug-reports: https://github.com/haskell/haskell-language-server/issues
tested-with: GHC ==9.8.2 || ==9.6.5 || ==9.4.8 || ==9.2.8
tested-with: GHC ==9.10.1 || ==9.8.2 || ==9.6.5 || ==9.4.8 || ==9.2.8
extra-source-files:
CHANGELOG.md
README.md
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Core/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ import Development.IDE.Core.Shake
import Development.IDE.Core.Tracing (withTrace)
import Development.IDE.GHC.Compat hiding (loadInterface,
parseHeader, parseModule,
tcRnModule, writeHieFile)
tcRnModule, writeHieFile, assert)
import qualified Development.IDE.GHC.Compat as Compat
import qualified Development.IDE.GHC.Compat as GHC
import qualified Development.IDE.GHC.Compat.Util as Util
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Core/ProgressReporting.hs
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ progressReporting (Just lspEnv) optProgressStyle = do
when (nextPct == prevPct) retry
pure (todo, done, nextPct)

update (ProgressAmount (Just nextPct) (Just $ T.pack $ show done <> "/" <> show todo))
_ <- update (ProgressAmount (Just nextPct) (Just $ T.pack $ show done <> "/" <> show todo))
loop update nextPct
updateStateForFile inProgress file = actionBracket (f succ) (const $ f pred) . const
-- This functions are deliberately eta-expanded to avoid space leaks.
Expand Down
8 changes: 4 additions & 4 deletions ghcide/src/Development/IDE/Core/RuleTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module Development.IDE.Core.RuleTypes(
) where

import Control.DeepSeq
import Control.Exception (assert)
import qualified Control.Exception as E
import Control.Lens
import Data.Aeson.Types (Value)
import Data.Hashable
Expand Down Expand Up @@ -188,9 +188,9 @@ hiFileFingerPrint HiFileResult{..} = hirIfaceFp <> maybe "" snd hirCoreFp

mkHiFileResult :: ModSummary -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult
mkHiFileResult hirModSummary hirModIface hirModDetails hirRuntimeModules hirCoreFp =
assert (case hirCoreFp of Just (CoreFile{cf_iface_hash}, _)
-> getModuleHash hirModIface == cf_iface_hash
_ -> True)
E.assert (case hirCoreFp of
Just (CoreFile{cf_iface_hash}, _) -> getModuleHash hirModIface == cf_iface_hash
_ -> True)
HiFileResult{..}
where
hirIfaceFp = fingerprintToBS . getModuleHash $ hirModIface -- will always be two bytes
Expand Down
8 changes: 7 additions & 1 deletion ghcide/src/Development/IDE/GHC/CPP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,10 @@ import qualified GHC.Driver.Pipeline.Execute as Pipeline
import qualified GHC.SysTools.Cpp as Pipeline
#endif

#if MIN_VERSION_ghc(9,11,0)
import qualified GHC.SysTools.Tasks as Pipeline
#endif

addOptP :: String -> DynFlags -> DynFlags
addOptP f = alterToolSettings $ \s -> s
{ toolSettings_opt_P = f : toolSettings_opt_P s
Expand All @@ -52,7 +56,9 @@ doCpp env input_fn output_fn =
#if MIN_VERSION_ghc(9,5,0)
let cpp_opts = Pipeline.CppOpts
{ cppLinePragmas = True
#if MIN_VERSION_ghc(9,9,0)
#if MIN_VERSION_ghc(9,11,0)
, sourceCodePreprocessor = Pipeline.SCPHsCpp
#elif MIN_VERSION_ghc(9,10,0)
, useHsCpp = True
#else
, cppUseCc = False
Expand Down
13 changes: 10 additions & 3 deletions ghcide/src/Development/IDE/GHC/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -335,7 +335,11 @@ myCoreToStg logger dflags ictxt

return (stg_binds2, denv, cost_centre_info)


#if MIN_VERSION_ghc(9,9,0)
reLocA :: (HasLoc (GenLocated a e), HasAnnotation b)
=> GenLocated a e -> GenLocated b e
reLocA = reLoc
#endif

getDependentMods :: ModIface -> [ModuleName]
#if MIN_VERSION_ghc(9,3,0)
Expand Down Expand Up @@ -515,13 +519,16 @@ data GhcVersion
| GHC94
| GHC96
| GHC98
deriving (Eq, Ord, Show)
| GHC910
deriving (Eq, Ord, Show, Enum)

ghcVersionStr :: String
ghcVersionStr = VERSION_ghc

ghcVersion :: GhcVersion
#if MIN_VERSION_GLASGOW_HASKELL(9,8,0,0)
#if MIN_VERSION_GLASGOW_HASKELL(9,10,0,0)
ghcVersion = GHC910
#elif MIN_VERSION_GLASGOW_HASKELL(9,8,0,0)
ghcVersion = GHC98
#elif MIN_VERSION_GLASGOW_HASKELL(9,6,0,0)
ghcVersion = GHC96
Expand Down
37 changes: 33 additions & 4 deletions ghcide/src/Development/IDE/GHC/Compat/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -197,7 +197,9 @@ module Development.IDE.GHC.Compat.Core (
pattern RealSrcLoc,
SrcLoc.SrcLoc(SrcLoc.UnhelpfulLoc),
BufSpan,
#if !MIN_VERSION_ghc(9,9,0)
GHC.SrcAnn,
#endif
SrcLoc.leftmost_smallest,
SrcLoc.containsSpan,
SrcLoc.mkGeneralSrcSpan,
Expand Down Expand Up @@ -494,8 +496,11 @@ import Data.Foldable (toList)
import GHC.Core.Multiplicity (scaledThing)
import GHC.Data.Bag
import GHC.Driver.Env
import GHC.Hs (HsModule (..), SrcSpanAnn')
import GHC.Hs.Decls hiding (FunDep)
import GHC.Hs (HsModule (..))
#if !MIN_VERSION_ghc(9,9,0)
import GHC.Hs (SrcSpanAnn')
#endif
import GHC.Hs.Decls hiding (FunDep)
import GHC.Hs.Doc
import GHC.Hs.Expr
import GHC.Hs.Extension
Expand Down Expand Up @@ -651,20 +656,36 @@ instance HasSrcSpan SrcSpan where
instance HasSrcSpan (SrcLoc.GenLocated SrcSpan a) where
getLoc = GHC.getLoc

#if MIN_VERSION_ghc(9,9,0)
instance HasSrcSpan (EpAnn a) where
getLoc = GHC.getHasLoc
#endif

#if MIN_VERSION_ghc(9,9,0)
instance HasSrcSpan (SrcLoc.GenLocated (EpAnn ann) a) where
getLoc (L l _) = getLoc l
#else
instance HasSrcSpan (SrcSpanAnn' ann) where
getLoc = GHC.locA
instance HasSrcSpan (SrcLoc.GenLocated (SrcSpanAnn' ann) a) where
getLoc (L l _) = l
#endif

pattern L :: HasSrcSpan a => SrcSpan -> e -> SrcLoc.GenLocated a e
pattern L l a <- GHC.L (getLoc -> l) a
{-# COMPLETE L #-}

-- This is from the old api, but it still simplifies
pattern ConPatIn :: SrcLoc.Located (ConLikeP GhcPs) -> HsConPatDetails GhcPs -> Pat GhcPs
#if MIN_VERSION_ghc(9,9,0)
pattern ConPatIn con args <- ConPat _ (L _ (SrcLoc.noLoc -> con)) args
where
ConPatIn con args = ConPat GHC.noAnn (GHC.noLocA $ SrcLoc.unLoc con) args
#else
pattern ConPatIn con args <- ConPat EpAnnNotUsed (L _ (SrcLoc.noLoc -> con)) args
where
ConPatIn con args = ConPat EpAnnNotUsed (GHC.noLocA $ SrcLoc.unLoc con) args
#endif

conPatDetails :: Pat p -> Maybe (HsConPatDetails p)
conPatDetails (ConPat _ _ args) = Just args
Expand All @@ -680,8 +701,16 @@ initObjLinker env =
GHCi.initObjLinker (GHCi.hscInterp env)

loadDLL :: HscEnv -> String -> IO (Maybe String)
loadDLL env =
GHCi.loadDLL (GHCi.hscInterp env)
loadDLL env str = do
res <- GHCi.loadDLL (GHCi.hscInterp env) str
#if MIN_VERSION_ghc(9,11,0)
pure $
case res of
Left err_msg -> Just err_msg
Right _ -> Nothing
#else
pure res
#endif

unload :: HscEnv -> [Linkable] -> IO ()
unload hsc_env linkables =
Expand Down
9 changes: 7 additions & 2 deletions ghcide/src/Development/IDE/GHC/Orphans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,14 +109,19 @@ instance NFData ModSummary where
instance Ord FastString where
compare a b = if a == b then EQ else compare (fs_sbs a) (fs_sbs b)


#if MIN_VERSION_ghc(9,9,0)
instance NFData (EpAnn a) where
rnf = rwhnf
#else
instance NFData (SrcSpanAnn' a) where
rnf = rwhnf
deriving instance Functor SrcSpanAnn'
#endif

instance Bifunctor GenLocated where
bimap f g (L l x) = L (f l) (g x)

deriving instance Functor SrcSpanAnn'

instance NFData ParsedModule where
rnf = rwhnf

Expand Down
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/LSP/Outline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -271,7 +271,9 @@ hsConDeclsBinders cons

get_flds_gadt :: HsConDeclGADTDetails GhcPs
-> [LFieldOcc GhcPs]
#if MIN_VERSION_ghc(9,3,0)
#if MIN_VERSION_ghc(9,9,0)
get_flds_gadt (RecConGADT _ flds) = get_flds (reLoc flds)
#elif MIN_VERSION_ghc(9,3,0)
get_flds_gadt (RecConGADT flds _) = get_flds (reLoc flds)
#else
get_flds_gadt (RecConGADT flds) = get_flds (reLoc flds)
Expand Down
9 changes: 0 additions & 9 deletions ghcide/test/cabal/Development/IDE/Test/Runfiles.hs

This file was deleted.

1 change: 0 additions & 1 deletion ghcide/test/exe/BootTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ import Language.LSP.Protocol.Types hiding
mkRange)
import Language.LSP.Test
import System.FilePath ((</>))
import Test.Hls.FileSystem (toAbsFp)
import Test.Tasty
import Test.Tasty.HUnit

Expand Down
6 changes: 2 additions & 4 deletions ghcide/test/exe/ClientSettingsTests.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
{-# LANGUAGE GADTs #-}
module ClientSettingsTests (tests) where

import Config (lspTestCaps, testWithConfig,
testWithDummyPluginEmpty)
import Config (testWithDummyPluginEmpty)
import Control.Applicative.Combinators
import Control.Monad
import Data.Aeson (toJSON)
Expand All @@ -16,8 +15,7 @@ import Language.LSP.Protocol.Types hiding
SemanticTokensEdit (..),
mkRange)
import Language.LSP.Test
import Test.Hls (testConfigCaps,
waitForProgressDone)
import Test.Hls (waitForProgressDone)
import Test.Tasty

tests :: TestTree
Expand Down
6 changes: 5 additions & 1 deletion ghcide/test/exe/CodeLensTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,11 @@ addSigLensesTests =
, ("symbolKindTest = Proxy @\"qwq\"", "symbolKindTest :: Proxy \"qwq\"")
, ("promotedKindTest = Proxy @Nothing", if ghcVersion >= GHC96 then "promotedKindTest :: Proxy Nothing" else "promotedKindTest :: Proxy 'Nothing")
, ("typeOperatorTest = Refl", "typeOperatorTest :: forall {k} {a :: k}. a :~: a")
, ("notInScopeTest = mkCharType", "notInScopeTest :: String -> Data.Data.DataType")
, ("notInScopeTest = mkCharType"
, if ghcVersion < GHC910
then "notInScopeTest :: String -> Data.Data.DataType"
else "notInScopeTest :: String -> GHC.Internal.Data.Data.DataType"
)
, ("aVeryLongSignature a b c d e f g h i j k l m n = a && b && c && d && e && f && g && h && i && j && k && l && m && n", "aVeryLongSignature :: Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool")
]
in testGroup
Expand Down
Loading

0 comments on commit 3009a45

Please sign in to comment.