Cannot create type synonym for quantified constraint without ImpredicativeTypes
{-# LANGUAGE KindSignatures, RankNTypes, ConstraintKinds, QuantifiedConstraints, FlexibleInstances, UndecidableInstances #-}
module Bug where
type F1 (f :: * -> *) = forall a. Eq (f a)
class (Functor f, F1 f) => C f
instance (Functor f, F1 f) => C f
type F2 f = (Functor f, F1 f)
Bug.hs:7:1: error:
• Illegal polymorphic type: F1 f
GHC doesn't yet support impredicative polymorphism
• In the type synonym declaration for ‘F2’
|
7 | type F2 f = (Functor f, F1 f)
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
(GHC accepts the program with ImpredicativeTypes.)
(Functor f, F1 f)
is allowed as a superclass constraint, and as an instance constraint, but a type synonym cannot be made for it.
Not sure if this really counts as a bug ("just switch on ImpredicativeTypes"), but I think it's worth discussing. I prefer to keep ImpredicativeTypes switched off, but if something can be a constraint, shouldn't I be able to create a type synonym of it?
Trac metadata
Trac field | Value |
---|---|
Version | 8.6.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |