[GHC] #12820: Regression around pattern synonyms and higher-rank types
GHC
ghc-devs at haskell.org
Thu Nov 10 17:18:49 UTC 2016
#12820: Regression around pattern synonyms and higher-rank types
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
(Type checker) |
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:
-------------------------------------+-------------------------------------
GHC 8.0.1 accepts, but HEAD rejects:
{{{#!hs
{-# LANGUAGE PatternSynonyms, RankNTypes, ViewPatterns #-}
module Bug where
pattern P :: (forall a. a -> a) -> String
pattern P x <- (\ _ -> id -> x)
}}}
(Sidenote: kudos to the parser on figuring out my view pattern.)
HEAD gives this error:
{{{
Bug.hs:6:30: error:
• Couldn't match expected type ‘forall a. a -> a’
with actual type ‘a0 -> a0’
• In the declaration for pattern synonym ‘P’
• Relevant bindings include x :: a0 -> a0 (bound at Bug.hs:6:30)
}}}
The code looks correct to me.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12820>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list