[GHC] #14060: TH-reified types can suffer from kind signature oversaturation
GHC
ghc-devs at haskell.org
Sun Jul 30 05:23:54 UTC 2017
#14060: TH-reified types can suffer from kind signature oversaturation
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.2.1
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:
-------------------------------------+-------------------------------------
I ran into this issue when attempting to fix #11785 in `TcSplice`. Here's
a simple Template Haskell program:
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Data.Proxy
import Language.Haskell.TH
newtype Foo = Foo (Proxy '[False, True, False])
$(return [])
main :: IO ()
main = putStrLn $(reify ''Foo >>= stringE . pprint)
}}}
The output of this program is unfortunately noisy:
{{{
$ runghc Bug.hs
newtype Bug.Foo
= Bug.Foo (Data.Proxy.Proxy ((':) 'GHC.Types.False
((':) 'GHC.Types.True
((':) 'GHC.Types.False
('[] :: [GHC.Types.Bool])
:: [GHC.Types.Bool]) :: [GHC.Types.Bool]) :: [GHC.Types.Bool]))
}}}
Somehow, we've ended up with four copies of a `[GHC.Types.Bool]` kind
annotation! It definitely feels like Template Haskell could be more
conservative here in choosing which types get explicit kind annotations -
at the most, I'd only expect `'[]` to get one.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14060>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list