[GHC] #15473: GHC 8.6+ loops infinitely on an UndecidableInstances error message

GHC ghc-devs at haskell.org
Fri Aug 3 18:59:12 UTC 2018


#15473: GHC 8.6+ loops infinitely on an UndecidableInstances error message
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  highest        |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.5
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  performance bug
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This regression was introduced in commit
 e1b5a1174e42e390855b153015ce5227b3251d89 (`Fix a nasty bug in
 piResultTys`), which is present in the `ghc-8.6` and `master` branches. To
 observe the issue, try compiling the following program:

 {{{#!hs
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE TypeOperators #-}
 -- {-# LANGUAGE UndecidableInstances #-}
 module Bug where

 type family Undefined :: k where {}

 type family LetInterleave xs t ts is (a_ahkO :: [a]) (a_ahkP :: [[a]]) ::
 [[a]] where
   LetInterleave xs t ts is y z = Undefined y z
 }}}

 You'll get this far:

 {{{
 $ ~/Software/ghc4/inplace/bin/ghc-stage2 Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:11:3: error:
     • Variables ‘a, a’ occur more often
         in the type family application
 }}}

 Before GHC hangs. (I was unable to kill this with Ctrl+C; I had to resort
 to `kill -9`.)

 Interestingly, the commit f8618a9b15177ee8c84771b927cb3583c9cd8408
 (`Remove the type-checking knot.`) does not appear to have an effect on
 this.

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


More information about the ghc-tickets mailing list