[GHC] #16140: Cannot create type synonym for quantified constraint without ImpredicativeTypes

GHC ghc-devs at haskell.org
Mon Jan 7 02:28:10 UTC 2019


#16140: Cannot create type synonym for quantified constraint without
ImpredicativeTypes
-------------------------------------+-------------------------------------
           Reporter:  Ashley         |             Owner:  (none)
  Yakeley                            |
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.3
           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:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# 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?

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


More information about the ghc-tickets mailing list