Regression around pattern synonyms and higher-rank types
GHC 8.0.1 accepts, but HEAD rejects:
{-# 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |