#4028: Derived Data instance requires Data instances for unused type parameters
----------------------------------------+-----------------------------------
    Reporter:  igloo                    |        Owner:              
        Type:  bug                      |       Status:  new         
    Priority:  normal                   |    Milestone:  Not GHC     
   Component:  Compiler (Type checker)  |      Version:  6.12.2      
    Keywords:                           |   Difficulty:              
          Os:  Unknown/Multiple         |     Testcase:              
Architecture:  Unknown/Multiple         |      Failure:  None/Unknown
----------------------------------------+-----------------------------------

Comment(by dreixel):

 Consider the following different choices of Data instances for FSVec:


 {{{
 newtype FSVec s a = FSVec {unFSVec :: [a]} deriving (Eq, Typeable)
 instance (Typeable s, Data a) => Data (FSVec s a)

 newtype FSVec1 s a = FSVec1 {unFSVec1 :: [a]} deriving (Eq, Typeable)
 instance (Typeable s, Data a) => Data (FSVec1 s a) where
     dataCast1 f            = Data.Typeable.gcast1 f

 newtype FSVec2 s a = FSVec2 {unFSVec2 :: [a]} deriving (Eq, Typeable)
 instance (Data s, Data a) => Data (FSVec2 s a) where
     dataCast2 f            = Data.Typeable.gcast2 f
 }}}


 Let's now test their behavior when extending a generic function with an
 adhoc case:


 {{{
 -- We need to define ext2Q, which uses dataCast2.
 -- ext1Q, which is defined in the library, uses dataCast1.
 newtype Q r a = Q { unQ :: a -> r }
 ext2Q :: (Data d, Typeable2 t)
       => (d -> q) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> q) ->
 d -> q
 ext2Q def ext arg =
   case dataCast2 (Q ext) of
     Just (Q ext') -> ext' arg
     Nothing       -> def arg


 test, test1, test2 :: Char
 test  = (const 'p') `ext2Q` (\(FSVec  _) -> 'q') $ (FSVec  "" :: FSVec  ()
 Char)
 test1 = (const 'p') `ext2Q` (\(FSVec1 _) -> 'q') $ (FSVec1 "" :: FSVec1 ()
 Char)
 test2 = (const 'p') `ext2Q` (\(FSVec2 _) -> 'q') $ (FSVec2 "" :: FSVec2 ()
 Char)

 main = print (test, test1, test2)
 }}}


 From my perspective, only test3 behaves correctly, and hence we should
 define dataCast2 for FSVec as ghc 6.12 does. Note also that FSVec is an
 instance of Typeable2, so it's only sensible to use dataCast2 for it.

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