[GHC] #12583: Deriving standalone Ix instance for GADT leads to GHC panic

#12583: Deriving standalone Ix instance for GADT leads to GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- On GHC 8.0.1 and HEAD, the following code: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE StandaloneDeriving #-} module Bug where import Data.Ix data Foo a where MkFoo :: (Eq a, Ord a, Ix a) => Foo a deriving instance Ix (Foo a) }}} results in a GHC panic: {{{ $ /opt/ghc/head/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20160908 for x86_64-unknown-linux): Prelude.foldl1: empty list Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The culprit is [http://git.haskell.org/ghc.git/blob/1b5f9207a649a64a1bba20b0283253425f9208d7... here], in the code which generates an `inRange` implementation for a derived `Ix` instance for a datatype with exactly one constructor. Normally, this code wouldn't be reached for a datatype like `data Bar = MkBar`, since GHC would treat that as an enumeration and generate different code for `inRange`. That is, normally, the only time this `foldl1` would be reached is if we were dealing with exactly one constructor with one or more arguments (making the use of `foldl1` justified). However, there's a catch: the function which checks if a datatype is an enumeration (`isEnumerationTyCon`) will reject any GADT-like datatypes. `gen_Ix_binds` uses `isEnumerationTyCon` [http://git.haskell.org/ghc.git/blob/1b5f9207a649a64a1bba20b0283253425f9208d7... here] to determine whether to use the case that goes through `foldl1` or not, and since `Foo` as above is a GADT, it defaults to the case that uses `foldl1`. What's interesting is that this bug is //not// present in GHC 7.10.3 and earlier. Instead, it will simply error out with an appropriate error message: {{{ $ /opt/ghc/7.10.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:9:1: Can't make a derived instance of ‘Ix (Foo a)’: ‘Foo’ must be an enumeration type (an enumeration consists of one or more nullary, non-GADT constructors) or ‘Foo’ must have precisely one constructor In the stand-alone deriving instance for ‘Ix (Foo a)’ }}} That's because before `gen_Ix_binds` is reached, the `sideConditions` function [http://git.haskell.org/ghc.git/blob/1b5f9207a649a64a1bba20b0283253425f9208d7... checks] if the datatype meets the requirements imposed by `isEnumerationTyCon` or `isProductTyCon`. In GHC 7.10.3 and earlier, the implementation of `isProductTyCon` is: {{{#!hs isProductTyCon :: TyCon -> Bool -- True of datatypes or newtypes that have -- one, vanilla, data constructor isProductTyCon tc@(AlgTyCon {}) = case algTcRhs tc of DataTyCon{ data_cons = [data_con] } -> isVanillaDataCon data_con NewTyCon {} -> True _ -> False isProductTyCon (TupleTyCon {}) = True isProductTyCon _ = False }}} But as a result of [ this commit] of Simon's, the implementation of `isProductTyCon` in GHC 8.0.1 and later is: {{{#!hs isProductTyCon :: TyCon -> Bool -- True of datatypes or newtypes that have -- one, non-existential, data constructor -- See Note [Product types] isProductTyCon tc@(AlgTyCon {}) = case algTcRhs tc of DataTyCon{ data_cons = [data_con] } -> null (dataConExTyVars data_con) NewTyCon {} -> True _ -> False isProductTyCon (TupleTyCon {}) = True isProductTyCon _ = False }}} Before, `isProductTyCon` rejected all GADTs, but now, it only checks if there are no existentially quantified type variables, which allows `Foo` to slip through the cracks. ----- The question is: how should we fix this? Should we generate the code the same code as we do for enumerations in this case? i.e., {{{#!hs instance Ix (Foo a) where ... inRange (a_a27l, b_a27m) c_a27n = case ($con2tag_PPfAWSX7zu8vtuLB8bgeJ a_a27l) of { a#_a27o -> case ($con2tag_PPfAWSX7zu8vtuLB8bgeJ b_a27m) of { b#_a27p -> case ($con2tag_PPfAWSX7zu8vtuLB8bgeJ c_a27n) of { c#_a27q -> (&&) (tagToEnum# (c#_a27q >=# a#_a27o)) (tagToEnum# (c#_a27q <=# b#_a27p)) } } } }}} Or should we generate the even-simpler definition: {{{#!hs instance Ix (Foo a) where ... inRange (MkFoo, MkFoo) MkFoo = True }}} FWIW, I think the Haskell Report [https://www.haskell.org/onlinereport/haskell2010/haskellch19.html#x27-227000... doesn't specify exactly] how this kind of case should be handled, so we should have some leeway in picking a solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12583 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12583: Deriving standalone Ix instance for GADT leads to GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2521 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2521 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12583#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12583: Deriving standalone Ix instance for GADT leads to GHC panic
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2521
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12583: Deriving standalone Ix instance for GADT leads to GHC panic
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2521
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12583: Deriving standalone Ix instance for GADT leads to GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | deriving/should_compile/T12583 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2521 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => deriving/should_compile/T12583 Comment: The above two commits can be merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12583#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12583: Deriving standalone Ix instance for GADT leads to GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | deriving/should_compile/T12583 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2521 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.2 Comment: Merged to `ghc-8.0` as 706a7305415a8e22b7dc4e2b8406f5b660642d1c and 43149ea634a99e125bf7e1750953945d04df823b. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12583#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC