[GHC] #15167: DerivClause list is not populated for (TyConI (DataD ...))
GHC
ghc-devs at haskell.org
Sat May 19 22:32:06 UTC 2018
#15167: DerivClause list is not populated for (TyConI (DataD ...))
-------------------------------------+-------------------------------------
Reporter: 0xd34df00d | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Template | Version: 8.4.2
Haskell |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!haskell
% cat Test.hs
{-# LANGUAGE LambdaCase #-}
module Test where
import Language.Haskell.TH
test :: Name -> Q [Dec]
test name = reify name >>= \case
TyConI dec -> do
runIO $ print dec
pure []
_ -> pure []
% cat Run.hs
{-# LANGUAGE TemplateHaskell #-}
import Test
data Foo = Foo deriving (Eq, Ord, Show)
test ''Foo
% ghc Run.hs
[2 of 2] Compiling Main ( Run.hs, Run.o )
DataD [] Main.Foo [] Nothing [NormalC Main.Foo []] []
}}}
One might expect the `DataD` to mention `Eq, Ord, Show` in the
`DerivClause` list, but it doesn't.
This behavior manifests with every ghc version I tried: 8.0.2, 8.2.2,
8.4.2. I also asked a question whether it's intended behaviour on
#haskell, and I've been advised to open a bug report, so here it is.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15167>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list