[Git][ghc/ghc][master] 2 commits: testsuite: Add testcase for #16689
Marge Bot
gitlab at gitlab.haskell.org
Tue Jun 18 20:01:02 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
dbf9ca20 by Ben Gamari at 2019-06-18T20:00:56Z
testsuite: Add testcase for #16689
- - - - -
29ec33cd by Ben Gamari at 2019-06-18T20:00:56Z
SafeHaskell: Don't throw -Wsafe warning if module is declared Safe
Fixes #16689.
- - - - -
3 changed files:
- compiler/main/HscMain.hs
- + testsuite/tests/safeHaskell/safeInfered/T16689.hs
- testsuite/tests/safeHaskell/safeInfered/all.T
Changes:
=====================================
compiler/main/HscMain.hs
=====================================
@@ -520,7 +520,9 @@ tcRnModule' sum save_rn_syntax mod = do
safe <- liftIO $ fst <$> readIORef (tcg_safeInfer tcg_res')
when safe $ do
case wopt Opt_WarnSafe dflags of
- True -> (logWarnings $ unitBag $
+ True
+ | safeHaskell dflags == Sf_Safe -> return ()
+ | otherwise -> (logWarnings $ unitBag $
makeIntoWarning (Reason Opt_WarnSafe) $
mkPlainWarnMsg dflags (warnSafeOnLoc dflags) $
errSafe tcg_res')
=====================================
testsuite/tests/safeHaskell/safeInfered/T16689.hs
=====================================
@@ -0,0 +1,4 @@
+{-# LANGUAGE Safe #-}
+
+main = return ()
+
=====================================
testsuite/tests/safeHaskell/safeInfered/all.T
=====================================
@@ -64,3 +64,5 @@ test('UnsafeWarn07', normal, compile, [''])
# Chck -fwa-safe works
test('SafeWarn01', normal, compile, [''])
+test('T16689', normal, compile, ['-Wsafe'])
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/da33f2bb3965bacec25790548d1a9b6812dfeefc...29ec33cd3ee390e8006a88d34f5ea0ac236663d0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/da33f2bb3965bacec25790548d1a9b6812dfeefc...29ec33cd3ee390e8006a88d34f5ea0ac236663d0
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190618/ef844d46/attachment.html>
More information about the ghc-commits
mailing list