[GHC] #11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances

GHC ghc-devs at haskell.org
Fri Jan 22 03:02:34 UTC 2016


#11480: UndecidableSuperClasses causes the compiler to spin with
UndecidableInstances
-------------------------------------+-------------------------------------
           Reporter:  ekmett         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.3
  (Type checker)                     |
           Keywords:  PolyKinds,     |  Operating System:  Unknown/Multiple
  UndecidableSuperClasses            |
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #10318
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Looks like I spoke too soon when I said all my examples worked in #10318
 -- it doesn't seem to work when the superclass cycle gets sufficiently
 interesting, possibly caused by the use of `PolyKinds` in the style
 mentioned in #9201.

 I took my `hask` code, and removed the shimming hacks above, and the
 following stripped down example sends the compiler into an infinite loop,
 which I believe should be able to work:

 {{{#!hs
 {-# language KindSignatures, PolyKinds, TypeFamilies,
   NoImplicitPrelude, FlexibleContexts,
   MultiParamTypeClasses, GADTs,
   ConstraintKinds, FlexibleInstances,
   FunctionalDependencies, UndecidableSuperClasses #-}

 import GHC.Types (Constraint)
 import qualified Prelude

 data Nat (c :: i -> i -> *) (d :: j -> j -> *) (f :: i -> j) (g :: i -> j)

 class Functor p (Nat p (->)) p => Category (p :: i -> i -> *)
 class (Category dom, Category cod) => Functor (dom :: i -> i -> *) (cod ::
 j -> j -> *) (f :: i -> j) | f -> dom cod

 instance (Category c, Category d) => Category (Nat c d)
 instance (Category c, Category d) => Functor (Nat c d) (Nat (Nat c d)
 (->)) (Nat c d)
 instance (Category c, Category d) => Functor (Nat c d) (->) (Nat c d f)

 instance Category (->)
 instance Functor (->) (->) ((->) e)
 instance Functor (->) (Nat (->) (->)) (->)
 }}}

 Sorry for the largish example, but I don't know how to strip it down
 smaller than the 6 instances that remain.

 One potentially telling observation is that without the instances it
 compiles, and produces what I expect, so the `UndecidableSuperClasses`
 part seems to be letting the classes compile, but there seems to be a bad
 interaction with the way the instances work.

 Also, in this stripped down form, I can remove the use of
 `UndecidableInstances` and that avoids the spinning problem, but once I
 flesh it out further I need `UndecidableInstances` in the "real" version
 of the problem.

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


More information about the ghc-tickets mailing list