#3500: Type functions and recursive dictionaries
---------------------------------+------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.14.1
Component: Compiler | Version: 6.10.4
Keywords: | Testcase:
Blockedby: | Difficulty: Unknown
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Changes (by Saizan):
* failure: => None/Unknown
Comment:
found another case of this, i think, using ghc-6.12.3:
{{{
{-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-}
newtype Mu f = Mu (f (Mu f))
type family Id m
type instance Id m = m
instance Show (Id (f (Mu f))) => Show (Mu f) where
show (Mu f) = show f
showMu :: Mu (Either ()) -> String
showMu = show
}}}
loading the above code makes ghc loop, it works fine if we remove Id
instead.
this is a boiled down testcase, the motivating code is from [1] where it
seems impossible to write a Show instance for Fix.
[1] http://blog.sigfpe.com/2010/08/constraining-types-with-regular.html
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3500#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs