#4494: Another regression with type families
----------------------------------------+-----------------------------------
    Reporter:  rl                       |        Owner:                         
  
        Type:  bug                      |       Status:  new                    
  
    Priority:  normal                   |    Milestone:                         
  
   Component:  Compiler (Type checker)  |      Version:  7.1                    
  
    Keywords:                           |     Testcase:                         
  
   Blockedby:                           |   Difficulty:                         
  
          Os:  Unknown/Multiple         |     Blocking:                         
  
Architecture:  Unknown/Multiple         |      Failure:  GHC rejects valid 
program
----------------------------------------+-----------------------------------

Comment(by simonpj):

 OK now I can reproduce it.  Here's a cut down program.
 {{{
 {-# LANGUAGE TypeFamilies, RankNTypes, FlexibleContexts,
 ScopedTypeVariables #-}

 module T4494 where

 type family H s
 type family F v

 bar :: (forall t. Maybe t -> a) -> H a -> Int
 bar = error "urk"

 call :: F Bool -> Int
 call x = bar (\_ -> x) (undefined :: H (F Bool))
 }}}
 My compiler is build with DEBUG so it gives a more helpful error
 {{{
 T4494.hs:1:1:
     TERRIBLE ERROR: double set of meta type variable
     uf_ac3 := F Bool
     Old value = (uf_ac3, a)
 }}}
 Great catch, thanks.

 Simon

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

Reply via email to