[GHC] #15792: TH reification prints invisible arguments to rank-2-kinded type as visible

#15792: TH reification prints invisible arguments to rank-2-kinded type as visible -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template | Version: 8.6.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: -------------------------------------+------------------------------------- If you run the following program: {{{#!hs {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Data.Kind import Language.Haskell.TH hiding (Type) newtype T (f :: forall a. a -> Type) = MkT (f Bool) $(pure []) main :: IO () main = do putStrLn $(reify ''T >>= stringE . pprint) putStrLn $(reify ''T >>= stringE . show) }}} You'll get: {{{ $ /opt/ghc/8.6.1/bin/runghc Bug.hs newtype Bug.T (f_0 :: forall (a_1 :: *) . a_1 -> *) = Bug.MkT (f_0 * GHC.Types.Bool) TyConI (NewtypeD [] Bug.T [KindedTV f_6989586621679016168 (ForallT [KindedTV a_6989586621679016167 StarT] [] (AppT (AppT ArrowT (VarT a_6989586621679016167)) StarT))] Nothing (NormalC Bug.MkT [(Bang NoSourceUnpackedness NoSourceStrictness,AppT (AppT (VarT f_6989586621679016168) StarT) (ConT GHC.Types.Bool))]) []) }}} These are the parts that are suspect: * `f_0 * GHC.Types.Bool` * `AppT (AppT (VarT f_6989586621679016168) StarT) (ConT GHC.Types.Bool)` Notice how `f`/`VarT f` accepts `*`/`StarT` as a visible argument, despite the fact that its kind `forall a. a -> Type` indicates that this should be invisible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15792 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15792: TH reification prints invisible arguments to rank-2-kinded type as visible -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5252 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5252 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15792#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15792: TH reification prints invisible arguments to rank-2-kinded type as visible
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.8.1
Component: Template Haskell | Version: 8.6.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D5252
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15792: TH reification prints invisible arguments to rank-2-kinded type as visible -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.6.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T15792 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5252 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => th/T15792 * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15792#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC