
#15198: `Language.Haskell.TH.Syntax.reify` returns * rather than Constraint -------------------------------------+------------------------------------- Reporter: benzrf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Template | Version: 8.4.2 Haskell | Keywords: reify | Operating System: Linux constraint constraintkinds | Architecture: x86_64 | Type of failure: Incorrect result (amd64) | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This module is sufficient to demonstrate the mistake: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Data.Kind import Data.Proxy import Language.Haskell.TH foo :: forall (k :: Constraint). Proxy k foo = Proxy return [] -- delimit declaration groups main :: IO () main = putStrLn $(do VarI _ ty _ <- reify 'foo let p = pprint ty [| p |]) }}} Running this in GHC 8.0.2 correctly prints out `forall (k_0 :: Constraint) . Data.Proxy.Proxy k_0`, but GHC 8.2.2 and 8.4.2 both print `forall (k_0 :: *) . Data.Proxy.Proxy k_0`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15198 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler