[GHC] #8154: Possible bug in open type familes: Conflicting (a->a) and (a->a->a) instances
GHC
ghc-devs at haskell.org
Thu Aug 22 01:28:43 UTC 2013
#8154: Possible bug in open type familes: Conflicting (a->a) and (a->a->a)
instances
----------------------------+----------------------------------------------
Reporter: nh2 | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.8.1
Component: Template | Version: 7.7
Haskell | Operating System: Unknown/Multiple
Keywords: type | Type of failure: GHC rejects valid program
families | Test Case:
Architecture: | Blocking:
Unknown/Multiple |
Difficulty: Unknown |
Blocked By: |
Related Tickets: |
----------------------------+----------------------------------------------
{{{
{-# LANGUAGE TypeFamilies #-}
module Test where
type family BoundsOf x
type instance BoundsOf (a->a) = Int
type instance BoundsOf (a->a->a) = (Int,Int)
}}}
This worked with GHC 7.6, but not with 7.8 HEAD (currently at 6cc7d3f).
To check:
{{{
wget
https://gist.github.com/nh2/6302087/raw/8167e7a1c8613aa384c2e8ca2f4ea9ade8745dc1/ghc-7.7-type-a-a-a-families.hs
ghci ghc-7.7-type-a-a-a-families.hs # 7.6, all fine
ghci ghc-7.7-type-a-a-a-families.hs # 7.7, breaks
}}}
On #ghc, we don't really understand whether this is the right thing to
happen or not.
{{{
<rwbarton> see
http://comments.gmane.org/gmane.comp.lang.haskell.glasgow.user/23734
<carter> c_wraith: im not sure why thats NOT working for open type familes
too though
<carter> a->a and a->a->a don't overlap...
<rwbarton> ah it's in that thread. "Open (normal, old-fashioned) type
families are essentially unchanged. In particular, coincident overlap and
non-linear patterns *are* allowed. The overlap check between open type
family instances now does a unification without an "occurs check" to mark
(x, x) and ([y], y) as overlapping, as necessary for type soundness."
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8154>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list