[GHC] #8740: Code conditionally compiles

GHC ghc-devs at haskell.org
Wed Feb 5 20:44:03 UTC 2014


#8740: Code conditionally compiles
----------------------------+----------------------------------------------
       Reporter:            |             Owner:
  thomaseding               |            Status:  new
           Type:  bug       |         Milestone:
       Priority:  normal    |           Version:  7.6.3
      Component:  Compiler  |  Operating System:  MacOS X
       Keywords:            |   Type of failure:  GHC rejects valid program
   Architecture:            |         Test Case:
  Unknown/Multiple          |          Blocking:
     Difficulty:  Unknown   |
     Blocked By:            |
Related Tickets:            |
----------------------------+----------------------------------------------
 {{{
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE StandaloneDeriving #-}

 data Abstract
 data Reified
 data Player

 data Elect p a where
     ElectRefAsTypeOf :: Int -> Elect Abstract a -> Elect Abstract a
     ElectHandle :: a -> Elect Reified a
     Controller :: Elect Abstract Player
     Owner :: Elect Abstract Player
     You :: Elect Abstract Player

 deriving instance (Eq a) => Eq (Elect p a)
 deriving instance (Ord a) => Ord (Elect p a)
 }}}

 As is, the above code fails to compile. But if I move `ElectRefAsTypeOf`
 to be the last constructor for the GADT, the code does compile. If I
 remove one of the `Elect Abstract Player` constructors, the code still
 won't compile even if the `ElectRefAsTypeOf` is moved.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8740>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list