
#12159: Record-like GADTs with repeated fields (of same type) rejected -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I came across a curious bug with record-like GADTs and repeated fields. Consider following code: {{{#!hs {-# LANGUAGE GADTs #-} data Foo p where Bar :: { quux' :: Bool } -> Foo Char Baz :: { quux'' :: Bool } -> Foo Int quux :: Foo p -> Bool quux (Bar q) = q quux (Baz q) = q quuxSetter :: Foo p -> Bool -> Foo p quuxSetter old@Bar{} q = old{quux' = q} quuxSetter old@Baz{} q = old{quux'' = q} }}} This compiles and all is fine. *But* GHC is supposed to create the nice `quux` and `quuxSetter` accessors for me, right? So, let's try: {{{#!hs data Foo p where Bar :: { quux :: Bool } -> Foo Char Baz :: { quux :: Bool } -> Foo Int }}} It does not compile! Instead I get: {{{ T12159.hs:3:1: error: Constructors Bar and Baz have a common field quux , but have different result types In the data type declaration for Foo Failed, modules loaded: none. }}} This is not very polite :-) It should simply create the accessors like I did above. It obviously can be done! Testcase is attached. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12159 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler