[commit: ghc] master: Turn "inaccessible code" error into a warning (08073e1)
git at git.haskell.org
git at git.haskell.org
Sun Jun 3 04:30:35 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/08073e16cf672d8009309e4e55d4566af1ecaff4/ghc
>---------------------------------------------------------------
commit 08073e16cf672d8009309e4e55d4566af1ecaff4
Author: Tobias Dammers <tdammers at gmail.com>
Date: Sat Jun 2 23:23:22 2018 -0400
Turn "inaccessible code" error into a warning
With GADTs, it is possible to write programs such that the type
constraints make some code branches inaccessible.
Take, for example, the following program ::
{-# LANGUAGE GADTs #-}
data Foo a where
Foo1 :: Foo Char
Foo2 :: Foo Int
data TyEquality a b where
Refl :: TyEquality a a
checkTEQ :: Foo t -> Foo u -> Maybe (TyEquality t u)
checkTEQ x y = error "unimportant"
step2 :: Bool
step2 = case checkTEQ Foo1 Foo2 of
Just Refl -> True -- Inaccessible code
Nothing -> False
Clearly, the `Just Refl` case cannot ever be reached, because the `Foo1`
and `Foo2` constructors say `t ~ Char` and `u ~ Int`, while the `Refl`
constructor essentially mandates `t ~ u`, and thus `Char ~ Int`.
Previously, GHC would reject such programs entirely; however, in
practice this is too harsh. Accepting such code does little harm, since
attempting to use the "impossible" code will still produce errors down
the chain, while rejecting it means we cannot legally write or generate
such code at all.
Hence, we turn the error into a warning, and provide
`-Winaccessible-code` to control GHC's behavior upon encountering this
situation.
Test Plan: ./validate
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #11066
Differential Revision: https://phabricator.haskell.org/D4744
>---------------------------------------------------------------
08073e16cf672d8009309e4e55d4566af1ecaff4
compiler/main/DynFlags.hs | 5 ++-
compiler/typecheck/TcErrors.hs | 2 +-
docs/users_guide/using-warnings.rst | 38 ++++++++++++++++++++++
testsuite/tests/gadt/T3651.stderr | 27 ++++++---------
testsuite/tests/gadt/T7293.stderr | 6 +++-
testsuite/tests/gadt/T7294.stderr | 2 +-
testsuite/tests/gadt/T7558.stderr | 13 ++++----
testsuite/tests/gadt/all.T | 2 +-
testsuite/tests/ghci/scripts/Defer02.stderr | 2 +-
.../typecheck/should_fail/FrozenErrorTests.stderr | 9 -----
testsuite/tests/typecheck/should_fail/all.T | 2 +-
.../tests/typecheck/should_fail/tcfail167.stderr | 6 +++-
.../tests/typecheck/should_run/Typeable1.stderr | 2 +-
testsuite/tests/typecheck/should_run/all.T | 2 +-
14 files changed, 75 insertions(+), 43 deletions(-)
Diff suppressed because of size. To see it, use:
git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 08073e16cf672d8009309e4e55d4566af1ecaff4
More information about the ghc-commits
mailing list