[GHC] #12522: GHC 8.0.1 hangs, looping forever in type-checker

GHC ghc-devs at haskell.org
Mon Aug 22 17:39:43 UTC 2016


#12522: GHC 8.0.1 hangs, looping forever in type-checker
-------------------------------------+-------------------------------------
           Reporter:  clinton        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Other
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I'm not sure if this is a bug or hanging the compiler is expected here.
 This was the minimal example that causes GHC to hang:

 {{{#!hs
 {-# LANGUAGE TypeFamilyDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE AllowAmbiguousTypes #-}

 main = return $ f (Just 'c')

 data D1 x
 data D2

 type family TF x = t | t -> x
 type instance TF (D1 x, a) = Maybe (TF (x, a))
 type instance TF (D2, ()) = Char

 class C p where
   f :: TF (x, a) -> ()
 }}}

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


More information about the ghc-tickets mailing list