[GHC] #13784: Infinite loop in compiler without undecidableXXX

GHC ghc-devs at haskell.org
Sat Jun 3 21:20:41 UTC 2017


#13784: Infinite loop in compiler without undecidableXXX
-------------------------------------+-------------------------------------
           Reporter:  tysonzero      |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code causes the compiler to loop.

 {{{#!hs
 {-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, GADTs #-}
 {-# LANGUAGE KindSignatures, MultiParamTypeClasses, TypeFamilies,
 TypeOperators #-}

 module Arithmetic where

 import Data.Monoid ((<>))

 data Product :: [*] -> * where
     (:*) :: a -> Product as -> Product (a : as)
     Unit :: Product '[]
 infixr 5 :*

 instance Show (Product '[]) where
     show Unit = "Unit"

 instance (Show a, Show (Product as)) => Show (Product (a : as)) where
     show (a :* as) = show a <> " :* " <> show as

 class Divideable a as where
     type Divide a as :: [*]
     divide :: Product as -> (a, Product (Divide a as))

 instance Divideable a (a : as) where
     -- type Divide a (a : as) = as
     -- Conflicting type family instances, seems like OVERLAPS isn't a
 thing for type families.
     divide (a :* as) = (a, as)

 instance Divideable b as => Divideable b (a : as) where
     type Divide b (a : as) = a : Divide b as
     divide (a :* as) = a :* divide as
 }}}

 Looks like it is because it is erroneously trying to solve `as ~ Product
 (Divide a as)` in order to type check `divide`.

 This bug has been fixed in more recent versions of GHC.

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


More information about the ghc-tickets mailing list