#2914: RecordWildCards doesn't work with associated datatypes inside class
instances
-----------------------------+----------------------------------------------
Reporter:  ganesh            |          Owner:                  
    Type:  bug               |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  6.11              |       Severity:  normal          
Keywords:                    |       Testcase:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-----------------------------+----------------------------------------------
 It seems like record wildcards (the ".." notation) don't work in the
 following scenario.

 I tried with a standalone associated datatype and it works fine.

 Tested with 6.10.1 and 6.11.20090103.

 {{{
 {-# LANGUAGE TypeFamilies, RecordWildCards #-}
 module AssocWildCards where

 class FooClass a where
    data FooType a

 instance FooClass Int where
    data FooType Int = FooInt { fooIntVal :: Int }

 fooInt :: Int -> FooType Int
 fooInt fooIntVal = FooInt{..}

 fromFooInt :: FooType Int -> Int
 fromFooInt FooInt{..} = fooIntVal
 }}}

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