
#13018: TH-spliced pattern synonym declaration fails to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * component: Template Haskell => Compiler (Type checker) Comment: It turns out this has nothing whatsoever to do with Template Haskell. The real culprit is `forall`. That is, while this program compiles without issue: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} module M where data T a where MkT :: Eq b => b -> T a pattern P :: b -> T a pattern P x <- MkT x }}} Changing the pattern signature to this: {{{#!hs pattern P :: forall b a. b -> T a }}} causes the error to appear: {{{ Bug.hs:10:20: error: • Couldn't match expected type ‘b’ with actual type ‘b1’ ‘b1’ is a rigid type variable bound by a pattern with constructor: MkT :: forall a b. Eq b => b -> T a, in a pattern synonym declaration at Bug.hs:10:16-20 ‘b’ is a rigid type variable bound by the signature for pattern synonym ‘P’ at Bug.hs:9:21 • In the declaration for pattern synonym ‘P’ • Relevant bindings include x :: b1 (bound at Bug.hs:10:20) }}} It turns out that when you quote a pattern synonym declaration with TH quotes, it implicitly adds the `forall` behind the scenes, triggering this bug when you try to splice it back in. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13018#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler