#4356: type instance doesn't work when the type is (->)
----------------------------------------+-----------------------------------
    Reporter:  sjoerd_visscher          |        Owner:  simonpj                
  
        Type:  bug                      |       Status:  new                    
  
    Priority:  high                     |    Milestone:  7.0.1                  
  
   Component:  Compiler (Type checker)  |      Version:  7.1                    
  
    Keywords:                           |     Testcase:                         
  
   Blockedby:                           |   Difficulty:                         
  
          Os:  MacOS X                  |     Blocking:                         
  
Architecture:  x86_64 (amd64)           |      Failure:  GHC rejects valid 
program
----------------------------------------+-----------------------------------
Changes (by igloo):

  * owner:  => simonpj
  * priority:  normal => high
  * milestone:  => 7.0.1


Old description:

> This doesn't work in 7.0.0.20100924.
> It works fine in 6.12.3.
>
> {-# LANGUAGE TypeFamilies #-}
> type family T t :: * -> * -> *
> type instance T Bool = (->)
> f :: T Bool Bool Bool
> f = not
>
> This is the error:
>
>     Couldn't match type `T Bool' with `(->)'
>     Expected type: T Bool Bool Bool
>       Actual type: Bool -> Bool
>     In the expression: not
>     In an equation for `f': f = not

New description:

 This doesn't work in 7.0.0.20100924.
 It works fine in 6.12.3.

 {{{
 {-# LANGUAGE TypeFamilies #-}
 type family T t :: * -> * -> *
 type instance T Bool = (->)
 f :: T Bool Bool Bool
 f = not
 }}}

 This is the error:

 {{{
     Couldn't match type `T Bool' with `(->)'
     Expected type: T Bool Bool Bool
       Actual type: Bool -> Bool
     In the expression: not
     In an equation for `f': f = not
 }}}

--

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