[GHC] #13705: Failure of improvement for type-family dependencies
GHC
ghc-devs at haskell.org
Tue May 16 11:59:41 UTC 2017
#13705: Failure of improvement for type-family dependencies
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider
{{{
{-# LANGUAGE TypeFamilyDependencies #-}
data D x
type family F t = s | s -> t
type instance F (D t) = D (F t)
f :: F s -> ()
f _ = ()
g :: D (F t) -> ()
g x = f x
}}}
which was presented in [https://mail.haskell.org/pipermail/haskell-
cafe/2016-October/125375.html this email] from Clinton Mead.
It yields
{{{
Tx.hs:14:9: error:
• Couldn't match expected type ‘F s0’ with actual type ‘D (F t)’
The type variable ‘s0’ is ambiguous
}}}
But it should work fine
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13705>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list