#3422: No match in record selector Var.tcTyVarDetails
--------------------------------------------+-------------------------------
 Reporter:  guest                           |          Owner:  chak  
     Type:  bug                             |         Status:  new   
 Priority:  normal                          |      Milestone:        
Component:  Compiler                        |        Version:  6.10.4
 Severity:  normal                          |     Resolution:        
 Keywords:  deriving instance, type family  |       Testcase:        
       Os:  Linux                           |   Architecture:  x86   
--------------------------------------------+-------------------------------
Changes (by chak):

  * owner:  => chak

Comment:

 {{{
 {-# OPTIONS_GHC -fglasgow-exts #-}
 {-# LANGUAGE UndecidableInstances #-}

 module GHCBug where

 newtype Trie m k a = Trie (Maybe a, m (SubKey k) (Trie m k a))

 type family SubKey k
 type instance SubKey [k] = k

 deriving instance (Eq (m k (Trie m [k] a))
                   ,Eq a) => Eq (Trie m [k] a)

 {-
 [...@monire ~]$ ghc -O2 -c --make GHCBug.hs
 [1 of 1] Compiling GHCBug           ( GHCBug.hs, GHCBug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 6.10.3 for x86_64-unknown-linux):
   No match in record selector Var.tcTyVarDetails

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 -}
 }}}

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