[GHC] #10183: Warning for redundant constraints: interaction with pattern matching
GHC
ghc-devs at haskell.org
Sun Jan 24 10:10:43 UTC 2016
#10183: Warning for redundant constraints: interaction with pattern matching
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords: redundant-
| constraints, GADTs
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by thomie):
* keywords: => redundant-constraints, GADTs
* failure: None/Unknown => Incorrect warning at compile-time
@@ -23,1 +23,1 @@
- Here's an example that doesn't depend on `TypeLits`:
+ Here's an example that only depends on `GADTs`:
@@ -25,0 +25,1 @@
+ {-# LANGUAGE GADTs #-}
@@ -26,2 +27,2 @@
- TT :: T True
- TF :: T False
+ TT :: T Bool
+ TF :: T Int
@@ -29,1 +30,1 @@
- f :: T True -> Bool
+ f :: T Bool -> Bool
@@ -32,1 +33,1 @@
- g :: (a ~ True) => T a -> Bool
+ g :: (a ~ Bool) => T a -> Bool
@@ -37,1 +38,1 @@
- `(a~True)` is not used in the code for `g`. But that evidence is used to
+ `(a~Bool)` is not used in the code for `g`. But that evidence is used to
New description:
Herbert gives this example:
{{{
{-# LANGUAGE GADTs, DataKinds, TypeOperators, UnicodeSyntax #-}
import GHC.TypeLits
data List l t where
Nil ∷ List 0 t
(:-) ∷ t → List l t → List (l+1) t
head' ∷ (1<=l) ⇒ List l t → t
head' (x :- _) = x
}}}
We get the warning
{{{
typelits1.hs:9:9: Warning:
Redundant constraint: 1 <= l
In the type signature for: head' ∷ (1 <= l) ⇒ List l t → t
}}}
But of course the warning is not redundant if we want to exclude the
`(head' Nil)` case.
Here's an example that only depends on `GADTs`:
{{{
{-# LANGUAGE GADTs #-}
data T a where
TT :: T Bool
TF :: T Int
f :: T Bool -> Bool
f TT = True
g :: (a ~ Bool) => T a -> Bool
g TT = True
}}}
Here `f` compiles fine, but `g` warns about a redundant constraint, even
though the two types are isomorphic! And indeed the evidence for
`(a~Bool)` is not used in the code for `g`. But that evidence is used to
prove that the un-matched pattern `(g TF)` is unreachable.
I'm not sure how to fix this. Bother.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10183#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list