Skip to content

Commit

Permalink
WIP: GHC 9.8 support
Browse files Browse the repository at this point in the history
Requires head.hackage to build

Will add tests to CI once 9.8 alpha 1 is released

rebase

ci: Test against 9.8-rc1

cabal.project fixes

wip
  • Loading branch information
wz1000 committed Oct 6, 2023
1 parent c941dac commit 45dc97d
Show file tree
Hide file tree
Showing 40 changed files with 252 additions and 66 deletions.
1 change: 1 addition & 0 deletions .github/actions/setup-build/action.yml
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ runs:
with:
ghc-version : ${{ inputs.ghc }}
cabal-version: ${{ inputs.cabal }}
ghcup-release-channel: "https://raw.githubusercontent.com/haskell/ghcup-metadata/master/ghcup-prereleases-0.0.7.yaml"
enable-stack: false

- if: inputs.os == 'Windows'
Expand Down
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.6", "9.4" , "9.2" , "9.0" ]
[ "9.8.0.20230929", "9.6", "9.4" , "9.2" , "9.0" ]
4 changes: 2 additions & 2 deletions .github/workflows/test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -135,15 +135,15 @@ jobs:
HLS_WRAPPER_TEST_EXE: hls-wrapper
run: cabal test wrapper-test --test-options="$TEST_OPTS --rerun-log-file .tasty-rerun-log-wrapper"

- if: matrix.test
- if: matrix.test && matrix.ghc != '9.8'
name: Test hls-refactor-plugin
run: cabal test hls-refactor-plugin --test-options="$TEST_OPTS" || cabal test hls-refactor-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.6'
name: Test hls-floskell-plugin
run: cabal test hls-floskell-plugin --test-options="$TEST_OPTS" || cabal test hls-floskell-plugin --test-options="$TEST_OPTS"

- if: matrix.test
- if: matrix.test && matrix.ghc != '9.8'
name: Test hls-class-plugin
run: cabal test hls-class-plugin --test-options="$TEST_OPTS" || cabal test hls-class-plugin --test-options="$TEST_OPTS"

Expand Down
33 changes: 30 additions & 3 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ package *

write-ghc-environment-files: never

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

constraints:
-- For GHC 9.4, older versions of entropy fail to build on Windows
Expand All @@ -72,8 +72,6 @@ constraints:
setup.happy == 1.20.1.1,
happy == 1.20.1.1,
filepath installed,
-- for ghc 8.10, stm-hamt 1.2.0.10 doesn't build
stm-hamt < 1.2.0.10,
-- Centos 7 comes with an old gcc version that doesn't know about
-- the flag '-fopen-simd', which blocked the release 2.2.0.0.
-- We want to be able to benefit from the performance optimisations
Expand Down Expand Up @@ -103,3 +101,32 @@ if impl(ghc >= 9.5)
-- ghc-9.6
ekg-core:ghc-prim,
stm-hamt:transformers,

if impl(ghc >= 9.7)
allow-newer:
-- ghc-9.8
base,
template-haskell,
ghc,
ghc-prim,
integer-gmp,
ghc-bignum,
template-haskell,
text,
binary,
bytestring,
Cabal,
unix,
deepseq,

if impl(ghc >= 9.7)
repository head.hackage.ghc.haskell.org
url: https://ghc.gitlab.haskell.org/head.hackage/
secure: True
key-threshold: 3
root-keys:
f76d08be13e9a61a377a85e2fb63f4c5435d40f8feb3e12eb05905edb8cdea89
26021a13b401500c8eb2761ca95c61f2d625bfef951b939a8124ed12ecf07329
7541f32a4ccca4f97aea3b22f5e593ba2c0267546016b992dfadcd2fe944e55d

active-repositories: hackage.haskell.org, head.hackage.ghc.haskell.org
2 changes: 1 addition & 1 deletion ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ library
dependent-sum,
dlist,
exceptions,
extra >= 1.7.4,
extra >= 1.7.14,
enummapset,
filepath,
fingertree,
Expand Down
11 changes: 10 additions & 1 deletion ghcide/src/Development/IDE/Core/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -479,11 +479,15 @@ filterUsages = id
-- Important to do this immediately after reading the unit before
-- anything else has a chance to read `mi_usages`
shareUsages :: ModIface -> ModIface
shareUsages iface = iface {mi_usages = usages}
shareUsages iface
= iface
#if !MIN_VERSION_ghc(9,7,0)
{mi_usages = usages}
where usages = map go (mi_usages iface)
go usg@UsageFile{} = usg {usg_file_path = fp}
where !fp = shareFilePath (usg_file_path usg)
go usg = usg
#endif


mkHiFileResultNoCompile :: HscEnv -> TcModuleResult -> IO HiFileResult
Expand Down Expand Up @@ -779,7 +783,9 @@ unnecessaryDeprecationWarningFlags
, Opt_WarnUnusedForalls
, Opt_WarnUnusedRecordWildcards
, Opt_WarnInaccessibleCode
#if !MIN_VERSION_ghc(9,7,0)
, Opt_WarnWarningsDeprecations
#endif
]

-- | Add a unnecessary/deprecated tag to the required diagnostics.
Expand All @@ -794,8 +800,11 @@ tagDiag (w@(Reason warning), (nfp, sh, fd))
= (w, (nfp, sh, fd { _tags = Just $ tag : concat (_tags fd) }))
where
requiresTag :: WarningFlag -> Maybe DiagnosticTag
#if !MIN_VERSION_ghc(9,7,0)
-- TODO wz1000: handle deprecations in 9.7+
requiresTag Opt_WarnWarningsDeprecations
= Just DiagnosticTag_Deprecated
#endif
requiresTag wflag -- deprecation was already considered above
| wflag `elem` unnecessaryDeprecationWarningFlags
= Just DiagnosticTag_Unnecessary
Expand Down
8 changes: 6 additions & 2 deletions ghcide/src/Development/IDE/GHC/CPP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,12 @@ doCpp env input_fn output_fn =

#if MIN_VERSION_ghc(9,5,0)
let cpp_opts = Pipeline.CppOpts
{ cppUseCc = False
, cppLinePragmas = True
{ cppLinePragmas = True
# if MIN_VERSION_ghc(9,9,0)
, useHsCpp = True
# else
, cppUseCc = False
# endif
} in
#else
let cpp_opts = True in
Expand Down
20 changes: 19 additions & 1 deletion ghcide/src/Development/IDE/GHC/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,8 @@ module Development.IDE.GHC.Compat(

Usage(..),

liftZonkM,

FastStringCompat,
bytesFS,
mkFastStringByteString,
Expand All @@ -55,6 +57,7 @@ module Development.IDE.GHC.Compat(
combineRealSrcSpans,

nonDetOccEnvElts,
nonDetFoldOccEnv,

isQualifiedImport,
GhcVersion(..),
Expand Down Expand Up @@ -93,6 +96,7 @@ module Development.IDE.GHC.Compat(
simplifyExpr,
tidyExpr,
emptyTidyEnv,
tcInitTidyEnv,
corePrepExpr,
corePrepPgm,
lintInteractiveExpr,
Expand Down Expand Up @@ -165,6 +169,9 @@ import qualified Data.Set as S

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

#if MIN_VERSION_ghc(9,7,0)
import GHC.Tc.Zonk.TcType (tcInitTidyEnv)
#endif
import qualified GHC.Core.Opt.Pipeline as GHC
import GHC.Core.Tidy (tidyExpr)
import GHC.CoreToStg.Prep (corePrepPgm)
Expand Down Expand Up @@ -247,6 +254,15 @@ import GHC.Driver.Config.CoreToStg (initCoreTo
import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig)
#endif

#if !MIN_VERSION_ghc(9,7,0)
liftZonkM :: a -> a
liftZonkM = id
#endif

#if !MIN_VERSION_ghc(9,7,0)
nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
nonDetFoldOccEnv = foldOccEnv
#endif

#if !MIN_VERSION_ghc(9,3,0)
nonDetOccEnvElts :: OccEnv a -> [a]
Expand Down Expand Up @@ -328,7 +344,9 @@ myCoreToStg logger dflags ictxt
#endif
this_mod ml prepd_binds

#if MIN_VERSION_ghc(9,4,2)
#if MIN_VERSION_ghc(9,8,0)
(unzip -> (stg_binds2,_),_)
#elif MIN_VERSION_ghc(9,4,2)
(stg_binds2,_)
#else
stg_binds2
Expand Down
22 changes: 19 additions & 3 deletions ghcide/src/Development/IDE/GHC/Compat/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,9 @@ module Development.IDE.GHC.Compat.Core (
pattern AvailTC,
Avail.availName,
Avail.availNames,
#if !MIN_VERSION_ghc(9,7,0)
Avail.availNamesWithSelectors,
#endif
Avail.availsToNameSet,
-- * TcGblEnv
TcGblEnv(..),
Expand Down Expand Up @@ -376,7 +378,9 @@ module Development.IDE.GHC.Compat.Core (
module GHC.Types.Name.Reader,
module GHC.Utils.Error,
#if MIN_VERSION_ghc(9,2,0)
#if !MIN_VERSION_ghc(9,7,0)
module GHC.Types.Avail,
#endif
module GHC.Types.SourceFile,
module GHC.Types.SourceText,
module GHC.Types.TyThing,
Expand Down Expand Up @@ -556,7 +560,9 @@ import GHC.Parser.Lexer hiding (initParserState, getPsMess
import GHC.Parser.Annotation (EpAnn (..))
import GHC.Platform.Ways
import GHC.Runtime.Context (InteractiveImport (..))
#if !MIN_VERSION_ghc(9,7,0)
import GHC.Types.Avail (greNamePrintableName)
#endif
import GHC.Types.Fixity (LexicalFixity (..), Fixity (..), defaultFixity)
import GHC.Types.Meta
import GHC.Types.Name.Set
Expand Down Expand Up @@ -631,7 +637,9 @@ pattern RealSrcLoc x y = SrcLoc.RealSrcLoc x y


pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 902
#if __GLASGOW_HASKELL__ >= 907
pattern AvailTC n names pieces <- Avail.AvailTC n ((,[]) -> (names,pieces))
#elif __GLASGOW_HASKELL__ >= 902
pattern AvailTC n names pieces <- Avail.AvailTC n ((\gres -> foldr (\gre (names, pieces) -> case gre of
Avail.NormalGreName name -> (name: names, pieces)
Avail.FieldGreName label -> (names, label:pieces)) ([], []) gres) -> (names, pieces))
Expand All @@ -640,14 +648,18 @@ pattern AvailTC n names pieces <- Avail.AvailTC n names pieces
#endif

pattern AvailName :: Name -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 902
#if __GLASGOW_HASKELL__ >= 907
pattern AvailName n <- Avail.Avail n
#elif __GLASGOW_HASKELL__ >= 902
pattern AvailName n <- Avail.Avail (Avail.NormalGreName n)
#else
pattern AvailName n <- Avail.Avail n
#endif

pattern AvailFL :: FieldLabel -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 902
#if __GLASGOW_HASKELL__ >= 907
pattern AvailFL fl <- (const Nothing -> Just fl) -- this pattern always fails as this field was removed in 9.7
#elif __GLASGOW_HASKELL__ >= 902
pattern AvailFL fl <- Avail.Avail (Avail.FieldGreName fl)
#else
-- pattern synonym that is never populated
Expand Down Expand Up @@ -835,7 +847,11 @@ pattern GRE :: Name -> Parent -> Bool -> [ImportSpec] -> RdrName.GlobalRdrElt
{-# COMPLETE GRE #-}
#if MIN_VERSION_ghc(9,2,0)
pattern GRE{gre_name, gre_par, gre_lcl, gre_imp} <- RdrName.GRE
#if MIN_VERSION_ghc(9,7,0)
{gre_name = gre_name
#else
{gre_name = (greNamePrintableName -> gre_name)
#endif
,gre_par, gre_lcl, gre_imp = (toList -> gre_imp)}
#else
pattern GRE{gre_name, gre_par, gre_lcl, gre_imp} = RdrName.GRE{..}
Expand Down
9 changes: 8 additions & 1 deletion ghcide/src/Development/IDE/GHC/Compat/Iface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,11 @@ import GHC

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

#if MIN_VERSION_ghc(9,7,0)
import GHC.Iface.Errors.Ppr (missingInterfaceErrorDiagnostic)
import GHC.Iface.Errors.Types (IfaceMessage)
#endif

#if !MIN_VERSION_ghc(9,2,0)
import qualified GHC.Driver.Finder as Finder
import GHC.Driver.Types (FindResult)
Expand All @@ -38,7 +43,9 @@ writeIfaceFile env = Iface.writeIface (hsc_dflags env)

cannotFindModule :: HscEnv -> ModuleName -> FindResult -> SDoc
cannotFindModule env modname fr =
#if MIN_VERSION_ghc(9,2,0)
#if MIN_VERSION_ghc(9,7,0)
missingInterfaceErrorDiagnostic (defaultDiagnosticOpts @IfaceMessage) $ Iface.cannotFindModule env modname fr
#elif MIN_VERSION_ghc(9,2,0)
Iface.cannotFindModule env modname fr
#else
Finder.cannotFindModule (hsc_dflags env) modname fr
Expand Down
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/GHC/Compat/Logger.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,9 @@ type LogActionCompat = LogFlags -> Maybe DiagnosticReason -> Maybe Severity -> S

-- alwaysQualify seems to still do the right thing here, according to the "unqualified warnings" test.
logActionCompat :: LogActionCompat -> LogAction
#if MIN_VERSION_ghc(9,5,0)
#if MIN_VERSION_ghc(9,7,0)
logActionCompat logAction logFlags (MCDiagnostic severity (ResolvedDiagnosticReason wr) _) loc = logAction logFlags (Just wr) (Just severity) loc alwaysQualify
#elif MIN_VERSION_ghc(9,5,0)
logActionCompat logAction logFlags (MCDiagnostic severity wr _) loc = logAction logFlags (Just wr) (Just severity) loc alwaysQualify
#else
logActionCompat logAction logFlags (MCDiagnostic severity wr) loc = logAction logFlags (Just wr) (Just severity) loc alwaysQualify
Expand Down
13 changes: 11 additions & 2 deletions ghcide/src/Development/IDE/GHC/Compat/Outputable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,10 @@ module Development.IDE.GHC.Compat.Outputable (
#if MIN_VERSION_ghc(9,5,0)
defaultDiagnosticOpts,
GhcMessage,
DriverMessage,
Messages,
initDiagOpts,
pprMessages,
#endif
#if MIN_VERSION_ghc(9,3,0)
DiagnosticReason(..),
Expand Down Expand Up @@ -67,6 +71,9 @@ import GHC.Driver.Env
import GHC.Driver.Ppr
import GHC.Driver.Session
import qualified GHC.Types.Error as Error
#if MIN_VERSION_ghc(9,7,0)
import GHC.Types.Error (defaultDiagnosticOpts)
#endif
import GHC.Types.Name.Ppr
import GHC.Types.Name.Reader
import GHC.Types.SourceError
Expand All @@ -89,7 +96,7 @@ import GHC.Parser.Errors.Types
#endif

#if MIN_VERSION_ghc(9,5,0)
import GHC.Driver.Errors.Types (GhcMessage)
import GHC.Driver.Errors.Types (GhcMessage, DriverMessage)
#endif

#if MIN_VERSION_ghc(9,5,0)
Expand Down Expand Up @@ -171,7 +178,9 @@ pprNoLocMsgEnvelope (MsgEnvelope { errMsgDiagnostic = e
, errMsgContext = unqual })
= sdocWithContext $ \ctx ->
withErrStyle unqual $
#if MIN_VERSION_ghc(9,3,0)
#if MIN_VERSION_ghc(9,7,0)
(formatBulleted e)
#elif MIN_VERSION_ghc(9,3,0)
(formatBulleted ctx $ e)
#else
(formatBulleted ctx $ Error.renderDiagnostic e)
Expand Down
6 changes: 6 additions & 0 deletions ghcide/src/Development/IDE/GHC/Orphans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -195,7 +195,13 @@ instance (NFData HsModule) where
rnf = rwhnf

instance Show OccName where show = unpack . printOutputable


#if MIN_VERSION_ghc(9,7,0)
instance Hashable OccName where hashWithSalt s n = hashWithSalt s (getKey $ getUnique $ occNameFS n, getKey $ getUnique $ occNameSpace n)
#else
instance Hashable OccName where hashWithSalt s n = hashWithSalt s (getKey $ getUnique n)
#endif

instance Show HomeModInfo where show = show . mi_module . hm_iface

Expand Down
8 changes: 8 additions & 0 deletions ghcide/src/Development/IDE/Plugin/Completions/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -370,7 +370,11 @@ cacheDataProducer uri visibleMods curMod globalEnv inScopeEnv limports =
fieldMap = Map.fromListWith (++) $ flip mapMaybe rdrElts $ \elt -> do
#if MIN_VERSION_ghc(9,2,0)
par <- greParent_maybe elt
#if MIN_VERSION_ghc(9,7,0)
flbl <- greFieldLabel_maybe elt
#else
flbl <- greFieldLabel elt
#endif
Just (par,[flLabel flbl])
#else
case gre_par elt of
Expand Down Expand Up @@ -402,7 +406,11 @@ cacheDataProducer uri visibleMods curMod globalEnv inScopeEnv limports =
| is_qual spec = Map.singleton asMod compItem
| otherwise = Map.fromList [(asMod,compItem),(origMod,compItem)]
asMod = showModName (is_as spec)
#if MIN_VERSION_ghc(9,8,0)
origMod = showModName (moduleName $ is_mod spec)
#else
origMod = showModName (is_mod spec)
#endif
in (unqual,QualCompls qual)

toCompItem :: Parent -> Module -> T.Text -> Name -> Maybe (LImportDecl GhcPs) -> [CompItem]
Expand Down
Loading

0 comments on commit 45dc97d

Please sign in to comment.