[GHC] #11463: Template Haskell applies too many arguments to kind synonym

#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

#11463: Template Haskell applies too many arguments to kind synonym -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType 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: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: TypeInType, TypeApplications => TypeInType * related: #11376 => Comment: No -- this is not #11376. I'll put this in my queue. My guess is that we just need a `filterInvisibles` somewhere in !TcSplice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11463#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11463: Template Haskell applies too many arguments to kind synonym -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2081 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2081 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11463#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11463: Template Haskell applies too many arguments to kind synonym -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2081 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Hooray! Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11463#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11463: Template Haskell applies too many arguments to kind synonym -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2081 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11463#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11463: Template Haskell applies too many arguments to kind synonym
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: merge
Priority: normal | Milestone: 8.0.1
Component: Template Haskell | Version: 8.0.1-rc1
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2081
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11463: Template Haskell applies too many arguments to kind synonym -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 8.0.1-rc1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2081 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as a1fa34ced8f317dcaa63babaf50040a7d8c68827. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11463#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC