Skip to content

Commit 8edb0f7

Browse files
authored
Enable tests for ghc 9 and promote ghcVersion check (#2001)
* Test 9.0.1 for windows and macOS * Refactorize ghc checking in tests * Replace CPP checks with ghcVersion * Use GHC cpp and remove 8.4 * Use the ghc version runtime checker * HLINT ann ignored for ghc-9 too * Mark test as broken for win and ghc-9 * Use GHC90 in eval tests * Disable tests for macos and ghc-9.0.1 * Test 9.0.1 for windows and macOS * Refactorize ghc checking in tests * Correct imports/exports * Replace CPP checks with ghcVersion * Use GHC cpp and remove 8.4 * Use the ghc version runtime checker * HLINT ann ignored for ghc-9 too * Mark test as broken for win and ghc-9 * Use GHC90 in eval tests * Avoid reformatting code * Remove not supported ghc-8.4 * Disable tests for macos and ghc-9.0.1 * Ignore hlint+cpp tests for win and ghc-9.0.
1 parent 5471382 commit 8edb0f7

File tree

8 files changed

+135
-149
lines changed

8 files changed

+135
-149
lines changed

Diff for: .github/workflows/test.yml

+7-4
Original file line numberDiff line numberDiff line change
@@ -49,19 +49,22 @@ jobs:
4949
- os: ubuntu-latest
5050
ghc: '8.6.5'
5151
test: true
52-
# only build rest of supported ghc versions for windows
52+
- os: windows-latest
53+
ghc: '9.0.1'
54+
test: true
5355
- os: windows-latest
5456
ghc: '8.10.5'
5557
test: true
58+
- os: windows-latest
59+
ghc: '8.6.5'
60+
test: true
61+
# only build rest of supported ghc versions for windows
5662
- os: windows-latest
5763
ghc: '8.10.4'
5864
- os: windows-latest
5965
ghc: '8.10.3'
6066
- os: windows-latest
6167
ghc: '8.10.2.2'
62-
- os: windows-latest
63-
ghc: '8.6.5'
64-
test: true
6568
# This build get stuck frequently
6669
# - os: windows-latest
6770
# ghc: '8.6.4'

Diff for: ghcide/session-loader/Development/IDE/Session.hs

+5-7
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE CPP #-}
21
{-# LANGUAGE TypeFamilies #-}
32

43
{-|
@@ -197,7 +196,7 @@ runWithDb fp k = do
197196

198197
getHieDbLoc :: FilePath -> IO FilePath
199198
getHieDbLoc dir = do
200-
let db = intercalate "-" [dirHash, takeBaseName dir, VERSION_ghc, hiedbDataVersion] <.> "hiedb"
199+
let db = intercalate "-" [dirHash, takeBaseName dir, ghcVersionStr, hiedbDataVersion] <.> "hiedb"
201200
dirHash = B.unpack $ B16.encode $ H.hash $ B.pack dir
202201
cDir <- IO.getXdgDirectory IO.XdgCache cacheDir
203202
createDirectoryIfMissing True cDir
@@ -526,11 +525,10 @@ cradleToOptsAndLibDir cradle file = do
526525
emptyHscEnv :: IORef NameCache -> FilePath -> IO HscEnv
527526
emptyHscEnv nc libDir = do
528527
env <- runGhc (Just libDir) getSession
529-
#if !MIN_VERSION_ghc(9,0,0)
530-
-- This causes ghc9 to crash with the error:
531-
-- Couldn't find a target code interpreter. Try with -fexternal-interpreter
532-
initDynLinker env
533-
#endif
528+
when (ghcVersion < GHC90) $
529+
-- This causes ghc9 to crash with the error:
530+
-- Couldn't find a target code interpreter. Try with -fexternal-interpreter
531+
initDynLinker env
534532
pure $ setNameCache nc env{ hsc_dflags = (hsc_dflags env){useUnicode = True } }
535533

536534
data TargetDetails = TargetDetails

Diff for: ghcide/src/Development/IDE.hs

+2
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,8 @@ import Development.IDE.Core.Shake as X (FastResult (..),
4242
useWithStaleFast',
4343
useWithStale_,
4444
use_, uses, uses_)
45+
import Development.IDE.GHC.Compat as X (GhcVersion (..),
46+
ghcVersion)
4547
import Development.IDE.GHC.Error as X
4648
import Development.IDE.GHC.Util as X
4749
import Development.IDE.Graph as X (Action, RuleResult,

Diff for: ghcide/src/Development/IDE/GHC/Compat.hs

+27-6
Original file line numberDiff line numberDiff line change
@@ -127,8 +127,12 @@ module Development.IDE.GHC.Compat(
127127
applyPluginsParsedResultAction,
128128
module Compat.HieTypes,
129129
module Compat.HieUtils,
130-
dropForAll
131-
,isQualifiedImport) where
130+
dropForAll,
131+
isQualifiedImport,
132+
GhcVersion(..),
133+
ghcVersion,
134+
ghcVersionStr
135+
) where
132136

133137
#if MIN_VERSION_ghc(8,10,0)
134138
import LinkerTypes
@@ -524,7 +528,7 @@ dropForAll = snd . GHC.splitLHsForAllTy
524528
#endif
525529

526530
pattern FunTy :: Type -> Type -> Type
527-
#if MIN_VERSION_ghc(8, 10, 0)
531+
#if MIN_VERSION_ghc(8,10,0)
528532
pattern FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res}
529533
#else
530534
pattern FunTy arg res <- TyCoRep.FunTy arg res
@@ -541,7 +545,7 @@ isQualifiedImport _ = False
541545

542546

543547

544-
#if __GLASGOW_HASKELL__ >= 900
548+
#if MIN_VERSION_ghc(9,0,0)
545549
getNodeIds :: HieAST a -> M.Map Identifier (IdentifierDetails a)
546550
getNodeIds = M.foldl' combineNodeIds M.empty . getSourcedNodeInfo . sourcedNodeInfo
547551

@@ -586,6 +590,23 @@ stringToUnit = Module.stringToUnitId
586590
rtsUnit = Module.rtsUnitId
587591
#endif
588592

589-
#if MIN_VERSION_ghc(9,0,0)
590-
#else
593+
data GhcVersion
594+
= GHC86
595+
| GHC88
596+
| GHC810
597+
| GHC90
598+
deriving (Eq, Ord, Show)
599+
600+
ghcVersionStr :: String
601+
ghcVersionStr = VERSION_ghc
602+
603+
ghcVersion :: GhcVersion
604+
#if MIN_VERSION_GLASGOW_HASKELL(9,0,0,0)
605+
ghcVersion = GHC90
606+
#elif MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
607+
ghcVersion = GHC810
608+
#elif MIN_VERSION_GLASGOW_HASKELL(8,8,0,0)
609+
ghcVersion = GHC88
610+
#elif MIN_VERSION_GLASGOW_HASKELL(8,6,0,0)
611+
ghcVersion = GHC86
591612
#endif

Diff for: ghcide/test/exe/Main.hs

+79-93
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,8 @@ import Development.IDE.Core.PositionMapping (PositionResult (..),
3535
positionResultToMaybe,
3636
toCurrent)
3737
import Development.IDE.Core.Shake (Q (..))
38+
import Development.IDE.GHC.Compat (GhcVersion (..),
39+
ghcVersion)
3840
import Development.IDE.GHC.Util
3941
import qualified Development.IDE.Main as IDE
4042
import Development.IDE.Plugin.Completions.Types (extendImportCommandId)
@@ -538,17 +540,15 @@ diagnosticTests = testGroup "diagnostics"
538540
, "foo = 1 {-|-}"
539541
]
540542
_ <- createDoc "Foo.hs" "haskell" fooContent
541-
#if MIN_VERSION_ghc(9,0,1)
542-
-- Haddock parse errors are ignored on ghc-9.0.1
543-
pure ()
544-
#else
545-
expectDiagnostics
546-
[ ( "Foo.hs"
547-
, [(DsWarning, (2, 8), "Haddock parse error on input")
543+
if ghcVersion >= GHC90 then
544+
-- Haddock parse errors are ignored on ghc-9.0.1
545+
pure ()
546+
else
547+
expectDiagnostics
548+
[ ( "Foo.hs"
549+
, [(DsWarning, (2, 8), "Haddock parse error on input")]
550+
)
548551
]
549-
)
550-
]
551-
#endif
552552
, testSessionWait "strip file path" $ do
553553
let
554554
name = "Testing"
@@ -3629,12 +3629,11 @@ findDefinitionAndHoverTests = let
36293629
mkFindTests
36303630
-- def hover look expect
36313631
[
3632-
#if MIN_VERSION_ghc(9,0,0)
3633-
-- It suggests either going to the constructor or to the field
3634-
test broken yes fffL4 fff "field in record definition"
3635-
#else
3636-
test yes yes fffL4 fff "field in record definition"
3637-
#endif
3632+
if ghcVersion >= GHC90 then
3633+
-- It suggests either going to the constructor or to the field
3634+
test broken yes fffL4 fff "field in record definition"
3635+
else
3636+
test yes yes fffL4 fff "field in record definition"
36383637
, test yes yes fffL8 fff "field in record construction #1102"
36393638
, test yes yes fffL14 fff "field name used as accessor" -- https://github.com/haskell/ghcide/pull/120 in Calculate.hs
36403639
, test yes yes aaaL14 aaa "top-level name" -- https://github.com/haskell/ghcide/pull/120
@@ -3657,11 +3656,10 @@ findDefinitionAndHoverTests = let
36573656
, test yes yes lclL33 lcb "listcomp lookup"
36583657
, test yes yes mclL36 mcl "top-level fn 1st clause"
36593658
, test yes yes mclL37 mcl "top-level fn 2nd clause #1030"
3660-
#if MIN_VERSION_ghc(8,10,0)
3661-
, test yes yes spaceL37 space "top-level fn on space #1002"
3662-
#else
3663-
, test yes broken spaceL37 space "top-level fn on space #1002"
3664-
#endif
3659+
, if ghcVersion >= GHC810 then
3660+
test yes yes spaceL37 space "top-level fn on space #1002"
3661+
else
3662+
test yes broken spaceL37 space "top-level fn on space #1002"
36653663
, test no yes docL41 doc "documentation #1129"
36663664
, test no yes eitL40 kindE "kind of Either #1017"
36673665
, test no yes intL40 kindI "kind of Int #1017"
@@ -3670,18 +3668,20 @@ findDefinitionAndHoverTests = let
36703668
, test no broken chrL36 litC "literal Char in hover info #1016"
36713669
, test no broken txtL8 litT "literal Text in hover info #1016"
36723670
, test no broken lstL43 litL "literal List in hover info #1016"
3673-
#if MIN_VERSION_ghc(9,0,0)
3674-
, test no yes docL41 constr "type constraint in hover info #1012"
3675-
#else
3676-
, test no broken docL41 constr "type constraint in hover info #1012"
3677-
#endif
3671+
, if ghcVersion >= GHC90 then
3672+
test no yes docL41 constr "type constraint in hover info #1012"
3673+
else
3674+
test no broken docL41 constr "type constraint in hover info #1012"
36783675
, test broken broken outL45 outSig "top-level signature #767"
36793676
, test broken broken innL48 innSig "inner signature #767"
36803677
, test no yes holeL60 hleInfo "hole without internal name #831"
36813678
, test no skip cccL17 docLink "Haddock html links"
36823679
, testM yes yes imported importedSig "Imported symbol"
36833680
, testM yes yes reexported reexportedSig "Imported symbol (reexported)"
3684-
, test no yes thLocL57 thLoc "TH Splice Hover"
3681+
, if ghcVersion == GHC90 && isWindows then
3682+
test no broken thLocL57 thLoc "TH Splice Hover"
3683+
else
3684+
test no yes thLocL57 thLoc "TH Splice Hover"
36853685
]
36863686
where yes, broken :: (TestTree -> Maybe TestTree)
36873687
yes = Just -- test should run and pass
@@ -3699,7 +3699,7 @@ pluginSimpleTests :: TestTree
36993699
pluginSimpleTests =
37003700
ignoreInWindowsForGHC88And810 $
37013701
#if __GLASGOW_HASKELL__ == 810 && __GLASGOW_HASKELL_PATCHLEVEL1__ == 5
3702-
expectFailBecause "known broken (see GHC #19763)" $
3702+
expectFailBecause "known broken for ghc 8.10.5 (see GHC #19763)" $
37033703
#endif
37043704
testSessionWithExtraFiles "plugin-knownnat" "simple plugin" $ \dir -> do
37053705
_ <- openDoc (dir </> "KnownNat.hs") "haskell"
@@ -4404,34 +4404,26 @@ highlightTests = testGroup "highlight"
44044404
, DocumentHighlight (R 6 10 6 13) (Just HkRead)
44054405
, DocumentHighlight (R 7 12 7 15) (Just HkRead)
44064406
]
4407-
,
4408-
#if MIN_VERSION_ghc(9,0,0)
4409-
expectFailBecause "Ghc9 highlights the constructor and not just this field" $
4410-
#endif
4411-
testSessionWait "record" $ do
4412-
doc <- createDoc "A.hs" "haskell" recsource
4413-
_ <- waitForDiagnostics
4414-
highlights <- getHighlights doc (Position 4 15)
4415-
liftIO $ highlights @?= List
4416-
-- Span is just the .. on 8.10, but Rec{..} before
4417-
[
4418-
#if MIN_VERSION_ghc(8,10,0)
4419-
DocumentHighlight (R 4 8 4 10) (Just HkWrite)
4420-
#else
4421-
DocumentHighlight (R 4 4 4 11) (Just HkWrite)
4422-
#endif
4423-
, DocumentHighlight (R 4 14 4 20) (Just HkRead)
4424-
]
4425-
highlights <- getHighlights doc (Position 3 17)
4426-
liftIO $ highlights @?= List
4427-
[ DocumentHighlight (R 3 17 3 23) (Just HkWrite)
4428-
-- Span is just the .. on 8.10, but Rec{..} before
4429-
#if MIN_VERSION_ghc(8,10,0)
4430-
, DocumentHighlight (R 4 8 4 10) (Just HkRead)
4431-
#else
4432-
, DocumentHighlight (R 4 4 4 11) (Just HkRead)
4433-
#endif
4434-
]
4407+
, knownBrokenForGhcVersions [GHC90] "Ghc9 highlights the constructor and not just this field" $
4408+
testSessionWait "record" $ do
4409+
doc <- createDoc "A.hs" "haskell" recsource
4410+
_ <- waitForDiagnostics
4411+
highlights <- getHighlights doc (Position 4 15)
4412+
liftIO $ highlights @?= List
4413+
-- Span is just the .. on 8.10, but Rec{..} before
4414+
[ if ghcVersion >= GHC810
4415+
then DocumentHighlight (R 4 8 4 10) (Just HkWrite)
4416+
else DocumentHighlight (R 4 4 4 11) (Just HkWrite)
4417+
, DocumentHighlight (R 4 14 4 20) (Just HkRead)
4418+
]
4419+
highlights <- getHighlights doc (Position 3 17)
4420+
liftIO $ highlights @?= List
4421+
[ DocumentHighlight (R 3 17 3 23) (Just HkWrite)
4422+
-- Span is just the .. on 8.10, but Rec{..} before
4423+
, if ghcVersion >= GHC810
4424+
then DocumentHighlight (R 4 8 4 10) (Just HkRead)
4425+
else DocumentHighlight (R 4 4 4 11) (Just HkRead)
4426+
]
44354427
]
44364428
where
44374429
source = T.unlines
@@ -4636,23 +4628,27 @@ xfail :: TestTree -> String -> TestTree
46364628
xfail = flip expectFailBecause
46374629

46384630
ignoreInWindowsBecause :: String -> TestTree -> TestTree
4639-
ignoreInWindowsBecause = if isWindows then ignoreTestBecause else (\_ x -> x)
4631+
ignoreInWindowsBecause
4632+
| isWindows = ignoreTestBecause
4633+
| otherwise = \_ x -> x
46404634

46414635
ignoreInWindowsForGHC88And810 :: TestTree -> TestTree
4642-
#if MIN_VERSION_ghc(8,8,1) && !MIN_VERSION_ghc(9,0,0)
4643-
ignoreInWindowsForGHC88And810 =
4644-
ignoreInWindowsBecause "tests are unreliable in windows for ghc 8.8 and 8.10"
4645-
#else
4646-
ignoreInWindowsForGHC88And810 = id
4647-
#endif
4636+
ignoreInWindowsForGHC88And810
4637+
| ghcVersion `elem` [GHC88, GHC810] =
4638+
ignoreInWindowsBecause "tests are unreliable in windows for ghc 8.8 and 8.10"
4639+
| otherwise = id
46484640

46494641
ignoreInWindowsForGHC88 :: TestTree -> TestTree
4650-
#if MIN_VERSION_ghc(8,8,1) && !MIN_VERSION_ghc(8,10,1)
4651-
ignoreInWindowsForGHC88 =
4652-
ignoreInWindowsBecause "tests are unreliable in windows for ghc 8.8"
4653-
#else
4654-
ignoreInWindowsForGHC88 = id
4655-
#endif
4642+
ignoreInWindowsForGHC88
4643+
| ghcVersion == GHC88 =
4644+
ignoreInWindowsBecause "tests are unreliable in windows for ghc 8.8"
4645+
| otherwise = id
4646+
4647+
knownBrokenForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree
4648+
knownBrokenForGhcVersions ghcVers
4649+
| ghcVersion `elem` ghcVers = expectFailBecause
4650+
| otherwise = \_ x -> x
4651+
46564652

46574653
data Expect
46584654
= ExpectRange Range -- Both gotoDef and hover should report this range
@@ -4811,13 +4807,11 @@ dependentFileTest = testGroup "addDependentFile"
48114807
let bazContent = T.unlines ["module Baz where", "import Foo ()"]
48124808
_ <- createDoc "Foo.hs" "haskell" fooContent
48134809
doc <- createDoc "Baz.hs" "haskell" bazContent
4814-
expectDiagnostics
4815-
#if MIN_VERSION_ghc(9,0,0)
4816-
-- String vs [Char] causes this change in error message
4817-
[("Foo.hs", [(DsError, (4, 6), "Couldn't match type")])]
4818-
#else
4819-
[("Foo.hs", [(DsError, (4, 6), "Couldn't match expected type")])]
4820-
#endif
4810+
expectDiagnostics $
4811+
if ghcVersion >= GHC90
4812+
-- String vs [Char] causes this change in error message
4813+
then [("Foo.hs", [(DsError, (4, 6), "Couldn't match type")])]
4814+
else [("Foo.hs", [(DsError, (4, 6), "Couldn't match expected type")])]
48214815
-- Now modify the dependent file
48224816
liftIO $ writeFile depFilePath "B"
48234817
sendNotification SWorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
@@ -5083,13 +5077,11 @@ sessionDepsArePickedUp = testSession'
50835077
"cradle: {direct: {arguments: []}}"
50845078
-- Open without OverloadedStrings and expect an error.
50855079
doc <- createDoc "Foo.hs" "haskell" fooContent
5086-
expectDiagnostics
5087-
#if MIN_VERSION_ghc(9,0,0)
5088-
-- String vs [Char] causes this change in error message
5089-
[("Foo.hs", [(DsError, (3, 6), "Couldn't match type")])]
5090-
#else
5091-
[("Foo.hs", [(DsError, (3, 6), "Couldn't match expected type")])]
5092-
#endif
5080+
expectDiagnostics $
5081+
if ghcVersion >= GHC90
5082+
-- String vs [Char] causes this change in error message
5083+
then [("Foo.hs", [(DsError, (3, 6), "Couldn't match type")])]
5084+
else [("Foo.hs", [(DsError, (3, 6), "Couldn't match expected type")])]
50935085
-- Update hie.yaml to enable OverloadedStrings.
50945086
liftIO $
50955087
writeFileUTF8
@@ -5799,16 +5791,10 @@ assertJust s = \case
57995791

58005792
-- | Before ghc9, lists of Char is displayed as [Char], but with ghc9 and up, it's displayed as String
58015793
listOfChar :: T.Text
5802-
#if MIN_VERSION_ghc(9,0,1)
5803-
listOfChar = "String"
5804-
#else
5805-
listOfChar = "[Char]"
5806-
#endif
5794+
listOfChar | ghcVersion >= GHC90 = "String"
5795+
| otherwise = "[Char]"
58075796

58085797
-- | Ghc 9 doesn't include the $-sign in TH warnings like earlier versions did
58095798
thDollarIdx :: Int
5810-
#if MIN_VERSION_ghc(9,0,1)
5811-
thDollarIdx = 1
5812-
#else
5813-
thDollarIdx = 0
5814-
#endif
5799+
thDollarIdx | ghcVersion >= GHC90 = 1
5800+
| otherwise = 0

0 commit comments

Comments
 (0)