[GHC] #13018: TH-spliced pattern synonym declaration fails to typecheck

GHC ghc-devs at haskell.org
Wed Dec 21 04:14:57 UTC 2016


#13018: TH-spliced pattern synonym declaration fails to typecheck
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Template       |           Version:  8.1
  Haskell                            |
           Keywords:                 |  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:
-------------------------------------+-------------------------------------
 This pattern synonyms typechecks without issue:

 {{{#!hs
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE PatternSynonyms #-}
 module Works where

 data T a where
   MkT :: Eq b => b -> T a

 pattern P :: b -> T a
 pattern P x <- MkT x
 }}}

 But if you try to create `P` from a Template Haskell splice, it will fail
 to typecheck:

 {{{#!hs
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE PatternSynonyms #-}
 {-# LANGUAGE TemplateHaskell #-}
 module Bug where

 data T a where
   MkT :: Eq b => b -> T a

 $([d| pattern P :: b -> T a; pattern P x <- MkT x |])
 }}}
 {{{
 $ /opt/ghc/head/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:9:3: error:
     • Couldn't match expected type ‘b0’ with actual type ‘b’
       ‘b’ 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:9:3-52
       ‘b0’ is a rigid type variable bound by
         the signature for pattern synonym ‘P’ at Bug.hs:9:3-52
     • In the declaration for pattern synonym ‘P’
     • Relevant bindings include x_a4tP :: b (bound at Bug.hs:9:3)
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13018>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list