[GHC] #14878: Can't witness transitivity ((.)) of isomorphism of Constraints
GHC
ghc-devs at haskell.org
Mon Mar 5 18:32:16 UTC 2018
#14878: Can't witness transitivity ((.)) of isomorphism of Constraints
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.5
Resolution: | Keywords:
| QuantifiedConstraints, wipT2893
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I don't think this is a bug. Consider this example:
{{{#!hs
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuantifiedConstraints #-}
data Dict c where
Dict :: c => Dict c
f :: ( c
, c => d
)
=> Dict d
f = Dict
}}}
This works, because there is exactly one matching local instance (`c =>
d`) for `d`. What about this example, which is closer to what you are
writing?
{{{#!hs
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuantifiedConstraints #-}
data Dict c where
Dict :: c => Dict c
f :: ( a, b
, a => c, b => c
, c => d
)
=> Dict d
f = Dict
}}}
There is one matching local instance (`c => d`) for `d`, so we try to
deduce `c`. But there are multiple matching local instances for `c`: `a =>
c` and `b => c`. Which one does GHC pick? As noted in the
[https://github.com/Gertjan423/ghc-
proposals/blob/e16828dbcd59d0ca58573c81fc6cea671875e6e2/proposals/0000
-quantified-constraints.rst#125overlap quantified constraints proposal],
if GHC is ever in doubt about which local instance to pick, it simply
rejects the code.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14878#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list