#7123: Dictionary method should be applicable even in existential context
---------------------------------+------------------------------------------
    Reporter:  heisenbug         |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Milestone:                  
   Component:  Compiler          |     Version:  7.4.1           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------
Changes (by igloo):

  * difficulty:  => Unknown


Old description:

> {{{
> {-# LANGUAGE GADTs, TypeFamilies #-}
>
> class Foo a where
>   type Bar a
>   baz :: Bar a -> Int
>

> instance Foo Int where
>   type Bar Int = (Int, Int)
>   baz (i, _) = i
>

> data Quux where
>   Quux :: Foo a => a -> Bar a -> Quux
>
> q = Quux (42 :: Int) (1, 2)
>
> i = case q of Quux _ b -> baz b
> }}}
>

>   repro.hs:18:31:
>     Could not deduce (Bar a0 ~ Bar a)
>     from the context (Foo a)
>       bound by a pattern with constructor
>                  Quux :: forall a. Foo a => a -> Bar a -> Quux,
>                in a case alternative
>       at repro.hs:18:15-22
>     NB: `Bar' is a type function, and may not be injective
>     The type variable `a0' is ambiguous
>     Possible fix: add a type signature that fixes these type variable(s)
>     In the first argument of `baz', namely `b'
>     In the expression: baz b
>     In a case alternative: Quux _ b -> baz b
>   Failed, modules loaded: none.

New description:

 {{{
 {-# LANGUAGE GADTs, TypeFamilies #-}

 class Foo a where
   type Bar a
   baz :: Bar a -> Int


 instance Foo Int where
   type Bar Int = (Int, Int)
   baz (i, _) = i


 data Quux where
   Quux :: Foo a => a -> Bar a -> Quux

 q = Quux (42 :: Int) (1, 2)

 i = case q of Quux _ b -> baz b
 }}}

 {{{
   repro.hs:18:31:
     Could not deduce (Bar a0 ~ Bar a)
     from the context (Foo a)
       bound by a pattern with constructor
                  Quux :: forall a. Foo a => a -> Bar a -> Quux,
                in a case alternative
       at repro.hs:18:15-22
     NB: `Bar' is a type function, and may not be injective
     The type variable `a0' is ambiguous
     Possible fix: add a type signature that fixes these type variable(s)
     In the first argument of `baz', namely `b'
     In the expression: baz b
     In a case alternative: Quux _ b -> baz b
   Failed, modules loaded: none.
 }}}

--

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