#3038: Associated type use triggers a bogus error message
------------------------------------+---------------------------------------
Reporter:  conal                    |          Owner:                  
    Type:  bug                      |         Status:  new             
Priority:  normal                   |      Component:  Compiler        
 Version:  6.11                     |       Severity:  normal          
Keywords:  associated type synonym  |       Testcase:                  
      Os:  Unknown/Multiple         |   Architecture:  Unknown/Multiple
------------------------------------+---------------------------------------
 In GHCi, version 6.11.20090115 built from HEAD

 {{{

 {-# LANGUAGE TypeOperators, TypeFamilies #-}
 {-# OPTIONS_GHC -Wall #-}

 -- With associate type synonym, the ch' definition leads to
 --
 --       Couldn't match expected type `Basis u1'
 --              against inferred type `Basis u'
 --         Expected type: u1 :-* v
 --         Inferred type: u :-* v
 --       In the expression: ch
 --       In the definition of `ch'': ch' = ch
 --
 -- With associated data type, no problem.


 class HasBasis u where type Basis u :: *

 -- class HasBasis u where data Basis u :: *


 type u :-* v = Basis u -> v

 ch :: (HasBasis u, HasBasis v) =>
       (v :-* w) -> (u :-* v) -> (u :-* w)
 ch = undefined

 ch' :: (HasBasis u, HasBasis v) =>
        (v :-* w) -> (u :-* v) -> (u :-* w)
 ch' = ch

 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3038>
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

Reply via email to