[GHC] #14692: Deriving Show with -XEmptyDataDeriving cases on the wrong argument
GHC
ghc-devs at haskell.org
Sat Jan 20 14:48:18 UTC 2018
#14692: Deriving Show with -XEmptyDataDeriving cases on the wrong argument
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 8.4.1-alpha1
Keywords: deriving | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Running this program in GHC 8.4.1-alpha:
{{{#!hs
{-# LANGUAGE EmptyDataDeriving #-}
{-# OPTIONS_GHC -ddump-deriv #-}
module Main (main) where
data Empty deriving Show
loop :: Empty
loop = let x = x in x
main :: IO ()
main = print loop
}}}
One would expect this to loop infinitely at runtime, but in practice, that
is not the case:
{{{
$ /opt/ghc/8.4.1/bin/runghc Bug.hs
==================== Derived instances ====================
Derived class instances:
instance GHC.Show.Show Main.Empty where
GHC.Show.showsPrec z_a1Iu = case z_a1Iu of
Derived type family instances:
==================== Filling in method body ====================
GHC.Show.Show [Main.Empty]
GHC.Show.show = GHC.Show.$dmshow @(Main.Empty)
==================== Filling in method body ====================
GHC.Show.Show [Main.Empty]
GHC.Show.showList = GHC.Show.$dmshowList @(Main.Empty)
Bug.hs: Bug.hs:5:21-24: Non-exhaustive patterns in case
}}}
The `-ddump-deriv` output reveals why: the `showsPrec` implementation for
`Empty` is casing on the //precedence// argument, not the actual value of
type `Empty`! This results in the non-exhaustive patterns error.
This is my fault, so I'll prepare a fix :)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14692>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list