[GHC] #11463: Template Haskell applies too many arguments to kind synonym
GHC
ghc-devs at haskell.org
Wed Jan 20 04:52:54 UTC 2016
#11463: Template Haskell applies too many arguments to kind synonym
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.0.1-rc1
Haskell |
Keywords: TypeInType, | Operating System: Unknown/Multiple
TypeApplications |
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: | Blocked By:
Blocking: | Related Tickets: #11376
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Running the following code:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeInType #-}
module IdStarK where
import Data.Kind
import Language.Haskell.TH
type Id a = a
data Proxy (a :: Id k) = Proxy
$(return [])
main :: IO ()
main = do
putStrLn $(reify ''Proxy >>= stringE . pprint)
putStrLn $(reify ''Proxy >>= stringE . show)
}}}
Gives a result I wouldn't have expected:
{{{
$ /opt/ghc/head/bin/runghc IdStarK.hs
data IdStarK.Proxy (a_0 :: IdStarK.Id * k_1) = IdStarK.Proxy
TyConI (DataD [] IdStarK.Proxy [KindedTV a_1627394516 (AppT (AppT (ConT
IdStarK.Id) StarT) (VarT k_1627394515))] Nothing [NormalC IdStarK.Proxy
[]] [])
}}}
From the output, it appears that `Id` is being applied to ''two''
arguments, both `*` and `k`! Perhaps this indirectly (or directly) a
consequence of #11376?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11463>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list