
#13018: TH-spliced pattern synonym declaration fails to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Thank you Simon, that's very helpful. I forgot about the need for two `forall`s, and it turns out that as a workaround, you can fix the issue by specifying the `forall`s manually. As evidence, this compiles: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module M where data T a where MkT :: Eq b => b -> T a $([d| pattern P :: forall a. forall b. b -> T a pattern P x <- MkT x |]) }}} So the only issue to investigate is why this: {{{#!hs $([d| pattern P :: b -> T a pattern P x <- MkT x |]) }}} fails to infer the `forall`s correctly. Replying to [comment:5 simonpj]:
I wonder if we could just genertate TH syntax with an implicit forall?
TH is already coming up with an implicit `forall`, just in an incorrect way. Note that this: {{{#!hs $([d| pattern P :: b -> T a pattern P x <- MkT x |]) }}} gets turned into this (as reported by `-ddump-splices`): {{{#!hs [d| pattern P_a1iH :: b_a1iI -> T a_a1iJ pattern P_a1iH x_a1iK <- MkT x_a1iK |] ======> pattern P_a4tM :: forall b_a4tN a_a4tO. b_a4tN -> T a_a4tO pattern P_a4tM x_a4tP <- MkT x_a4tP }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13018#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler