Re: [GHC] #1713: type synonym families are treated as being able to be instance of a class

2007-09-19 Thread GHC
#1713: type synonym families are treated as being able to be instance of a class
---+
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug |   Status:  closed 
Priority:  normal  |Milestone: 
   Component:  Compiler|  Version:  6.8
Severity:  normal  |   Resolution:  fixed  
Keywords:  |   Difficulty:  Unknown
  Os:  Linux   | Testcase: 
Architecture:  x86 |  
---+
Changes (by chak):

  * resolution:  = fixed
  * status:  new = closed

Comment:

 Fixed in the HEAD will propagate to 6.8 in due course.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1713
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #1713: type synonym families are treated as being able to be instance of a class

2007-09-18 Thread GHC
#1713: type synonym families are treated as being able to be instance of a class
-+--
  Reporter:  [EMAIL PROTECTED]  |  Owner:   
  Type:  bug | Status:  new  
  Priority:  normal  |  Milestone:   
 Component:  Compiler|Version:  6.8  
  Severity:  normal  |   Keywords:   
Difficulty:  Unknown | Os:  Linux
  Testcase:  |   Architecture:  x86  
-+--
The following code doesn’t compile:
 {{{
 {-# LANGUAGE TypeFamilies #-}
 module TypeFamilyBug where
 type family TestFamily a :: *

 type instance TestFamily () = [()]

 testFunction :: value - TestFamily value - ()
 testFunction = const (const ())

 testApplication :: ()
 testApplication = testFunction () (return ())
 }}}
 GHC 6.8.20070916 complains about {{{TestFamily}}} not being an instance
 of {{{Monad}}}.  Obviously, GHC recognizes that the second argument in the
 application of {{{testApplication}}} has to be of type {{{TestFamily ()}}}
 and tries to unify this type with {{{m ()}}} from the type of
 {{{return}}}.  However, in my opinion, GHC should reduce {{{TestFamily
 ()}}} to {{{[()]}}} and then see that the {{{[]}}} is the type which has
 to be an instance of {{{Monad}}}.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1713
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs