Skip to content

Commit f97b557

Browse files
committed
tests: Ghc9 shows [Char] as String by default
This seems like an improvement, so just update the test-suite
1 parent 739c7ac commit f97b557

File tree

1 file changed

+18
-9
lines changed

1 file changed

+18
-9
lines changed

ghcide/test/exe/Main.hs

Lines changed: 18 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -2190,14 +2190,14 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
21902190
[ (DsWarning, (6, 8), "Defaulting the following constraint")
21912191
, (DsWarning, (6, 16), "Defaulting the following constraint")
21922192
]
2193-
"Add type annotation ‘[Char]’ to ‘\"debug\""
2193+
("Add type annotation ‘" <> listOfChar <> "’ to ‘\"debug\"")
21942194
(T.unlines [ "{-# OPTIONS_GHC -Wtype-defaults #-}"
21952195
, "{-# LANGUAGE OverloadedStrings #-}"
21962196
, "module A (f) where"
21972197
, ""
21982198
, "import Debug.Trace"
21992199
, ""
2200-
, "f = seq (\"debug\" :: [Char]) traceShow \"debug\""
2200+
, "f = seq (\"debug\" :: " <> listOfChar <> ") traceShow \"debug\""
22012201
])
22022202
, testSession "add default type to satisfy two contraints" $
22032203
testFor
@@ -2210,14 +2210,14 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
22102210
, "f a = traceShow \"debug\" a"
22112211
])
22122212
[ (DsWarning, (6, 6), "Defaulting the following constraint") ]
2213-
"Add type annotation ‘[Char]’ to ‘\"debug\""
2213+
("Add type annotation ‘" <> listOfChar <> "’ to ‘\"debug\"")
22142214
(T.unlines [ "{-# OPTIONS_GHC -Wtype-defaults #-}"
22152215
, "{-# LANGUAGE OverloadedStrings #-}"
22162216
, "module A (f) where"
22172217
, ""
22182218
, "import Debug.Trace"
22192219
, ""
2220-
, "f a = traceShow (\"debug\" :: [Char]) a"
2220+
, "f a = traceShow (\"debug\" :: " <> listOfChar <> ") a"
22212221
])
22222222
, testSession "add default type to satisfy two contraints with duplicate literals" $
22232223
testFor
@@ -2230,14 +2230,14 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
22302230
, "f = seq (\"debug\" :: [Char]) (seq (\"debug\" :: [Char]) (traceShow \"debug\"))"
22312231
])
22322232
[ (DsWarning, (6, 54), "Defaulting the following constraint") ]
2233-
"Add type annotation ‘[Char]’ to ‘\"debug\""
2233+
("Add type annotation ‘" <> listOfChar <> "’ to ‘\"debug\"")
22342234
(T.unlines [ "{-# OPTIONS_GHC -Wtype-defaults #-}"
22352235
, "{-# LANGUAGE OverloadedStrings #-}"
22362236
, "module A (f) where"
22372237
, ""
22382238
, "import Debug.Trace"
22392239
, ""
2240-
, "f = seq (\"debug\" :: [Char]) (seq (\"debug\" :: [Char]) (traceShow (\"debug\" :: [Char])))"
2240+
, "f = seq (\"debug\" :: [Char]) (seq (\"debug\" :: [Char]) (traceShow (\"debug\" :: " <> listOfChar <> ")))"
22412241
])
22422242
]
22432243
where
@@ -3222,7 +3222,7 @@ addSigLensesTests =
32223222
, ("pattern Some a = Just a", "pattern Some :: a -> Maybe a")
32233223
, ("qualifiedSigTest= C.realPart", "qualifiedSigTest :: C.Complex a -> a")
32243224
, ("head = 233", "head :: Integer")
3225-
, ("rank2Test (k :: forall a . a -> a) = (k 233 :: Int, k \"QAQ\")", "rank2Test :: (forall a. a -> a) -> (Int, [Char])")
3225+
, ("rank2Test (k :: forall a . a -> a) = (k 233 :: Int, k \"QAQ\")", "rank2Test :: (forall a. a -> a) -> (Int, " <> listOfChar <> ")")
32263226
, ("symbolKindTest = Proxy @\"qwq\"", "symbolKindTest :: Proxy \"qwq\"")
32273227
, ("promotedKindTest = Proxy @Nothing", "promotedKindTest :: Proxy 'Nothing")
32283228
, ("typeOperatorTest = Refl", "typeOperatorTest :: a :~: a")
@@ -4148,10 +4148,11 @@ highlightTests = testGroup "highlight"
41484148
highlights <- getHighlights doc (Position 4 15)
41494149
liftIO $ highlights @?= List
41504150
-- Span is just the .. on 8.10, but Rec{..} before
4151+
[
41514152
#if MIN_GHC_API_VERSION(8,10,0)
4152-
[ DocumentHighlight (R 4 8 4 10) (Just HkWrite)
4153+
DocumentHighlight (R 4 8 4 10) (Just HkWrite)
41534154
#else
4154-
[ DocumentHighlight (R 4 4 4 11) (Just HkWrite)
4155+
DocumentHighlight (R 4 4 4 11) (Just HkWrite)
41554156
#endif
41564157
, DocumentHighlight (R 4 14 4 20) (Just HkRead)
41574158
]
@@ -5506,3 +5507,11 @@ assertJust :: MonadIO m => String -> Maybe a -> m a
55065507
assertJust s = \case
55075508
Nothing -> liftIO $ assertFailure s
55085509
Just x -> pure x
5510+
5511+
-- | Before ghc9, lists of Char is displayed as [Char], but with ghc9 and up, it's displayed as String
5512+
listOfChar :: T.Text
5513+
#if MIN_GHC_API_VERSION(9,0,1)
5514+
listOfChar = "String"
5515+
#else
5516+
listOfChar = "[Char]"
5517+
#endif

0 commit comments

Comments
 (0)