#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):

 You didn't put all the flags.  I used
 {{{
 {-# LANGUAGE TypeFamilies, RankNTypes, FlexibleContexts #-}

 module T4494 where

 type family H s a b

 class D (G v) => C v where
    type G v
    type F v
    foo :: v -> H (F v) (G v) v

 class D s where
    bar :: (forall t. Maybe t -> a) -> s -> H a s r -> r

 call :: forall v. C v => F v -> v
 call x = bar (\_ -> x)
               (undefined :: G v)
               (foo (undefined :: v))

 bar' :: C v => (forall t. Maybe t -> F v) -> G v -> H (F v) (G v) v -> v
 bar' = bar
 }}}
 When I compile with HEAD I get
 {{{
 T4494.hs:16:10:
     Could not deduce (D (G v)) from the context (C v2)
       arising from a use of `bar'
     Possible fix:
       add (D (G v)) to the context of the type signature for `call'
       or add an instance declaration for (D (G v))
     In the expression:
       bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
     In an equation for `call':
         call x = bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))

 T4494.hs:18:16:
     Could not deduce (H (F v1) (G v1) v1 ~ H (F v2) (G v) v2)
       from the context (C v2)
     NB: `H' is a type function, and may not be injective
     In the third argument of `bar', namely `(foo (undefined :: v))'
     In the expression:
       bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
     In an equation for `call':
         call x = bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
 }}}
 With 6.12.3 I get
 {{{
 T4494.hs:16:9:
     No instance for (D (G v))
       arising from a use of `bar' at T4494.hs:(16,9)-(18,35)
     Possible fix: add an instance declaration for (D (G v))
     In the expression:
         bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
     In the definition of `call':
         call x = bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))

 T4494.hs:18:15:
     Couldn't match expected type `H (F v2) (G v) v2'
            against inferred type `H (F v1) (G v1) v1'
       NB: `H' is a type function, and may not be injective
     In the third argument of `bar', namely `(foo (undefined :: v))'
     In the expression:
         bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
     In the definition of `call':
         call x = bar (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
 }}}
 This look similar to me.

 If I change `bar` to `bar'` in the rhs of `call` yields
 {{{
 T4494.hs:17:16:
     Could not deduce (G v ~ G v2) from the context (C v2)
     NB: `G' is a type function, and may not be injective
     In the second argument of `bar'', namely `(undefined :: G v)'
     In the expression:
       bar' (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
     In an equation for `call':
         call x = bar' (\ _ -> x) (undefined :: G v) (foo (undefined :: v))

 T4494.hs:18:16:
     Could not deduce (H (F v2) (G v2) v2 ~ H (F v1) (G v1) v1)
       from the context (C v2)
     NB: `H' is a type function, and may not be injective
     In the third argument of `bar'', namely `(foo (undefined :: v))'
     In the expression:
       bar' (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
     In an equation for `call':
         call x = bar' (\ _ -> x) (undefined :: G v) (foo (undefined :: v))
 }}}
 I have not puzzled out whether these error messages are right, but so far
 I see no regression.

 Simon

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