[GHC] #8740: Code conditionally compiles

#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

#8740: Deriving instance conditionally compiles ----------------------------------------------+---------------------------- Reporter: thomaseding | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8740#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8740: Deriving instance conditionally compiles -------------------------------------+------------------------------------- Reporter: | Owner: thomaseding | Status: new Type: bug | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #8128 Type of failure: GHC | rejects valid program | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * os: MacOS X => Unknown/Multiple * component: Compiler => Compiler (Type checker) * related: => #8128 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8740#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8740: Deriving instance conditionally compiles -------------------------------------+------------------------------------- Reporter: thomaseding | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.6.3 checker) | Keywords: GADTs, Resolution: | deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8128 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => GADTs, deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8740#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8740: Deriving instance conditionally compiles -------------------------------------+------------------------------------- Reporter: thomaseding | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.6.3 checker) | Keywords: GADTs, Resolution: | deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8128 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed I was bitten by this just now. This is quite an unfortunate behavior. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8740#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8740: Deriving instance conditionally compiles -------------------------------------+------------------------------------- Reporter: thomaseding | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.6.3 checker) | Keywords: GADTs, Resolution: | deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8128, #11066 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #8128 => #8128, #11066 Comment: Now that inaccessible code is a warning instead of an error (see #11066), the original program now typechecks. I'll whip up a test case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8740#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8740: Deriving instance conditionally compiles
-------------------------------------+-------------------------------------
Reporter: thomaseding | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.6.3
checker) | Keywords: GADTs,
Resolution: | deriving
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #8128, #11066 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#8740: Deriving instance conditionally compiles -------------------------------------+------------------------------------- Reporter: thomaseding | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 7.6.3 checker) | Keywords: GADTs, Resolution: fixed | deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T8740 Blocked By: | Blocking: Related Tickets: #8128, #11066 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => deriving/should_compile/T8740 * status: new => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8740#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8740: Deriving instance conditionally compiles
-------------------------------------+-------------------------------------
Reporter: thomaseding | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 7.6.3
checker) | Keywords: GADTs,
Resolution: fixed | deriving
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | deriving/should_compile/T8740
Blocked By: | Blocking:
Related Tickets: #8128, #11066 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Krzysztof Gogolewski
participants (1)
-
GHC