[GHC] #11708: Typechecker hangs when checking type families with -ddump-tc-trace turned on

GHC ghc-devs at haskell.org
Tue Mar 15 00:57:02 UTC 2016


#11708: Typechecker hangs when checking type families with -ddump-tc-trace turned
on
-------------------------------------+-------------------------------------
           Reporter:  kcsongor       |             Owner:  kcsongor
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
  (Type checker)                     |
           Keywords:  typefamilies   |  Operating System:  Unknown/Multiple
  trace hangs                        |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I have the following code, which is supposed to fail with a type error.
 However, when compiled with HEAD using the  -ddump-tc-trace flag, the type
 checker hangs.
 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE TypeOperators #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE DataKinds #-}

 module Test where

 import Data.Proxy

 test :: (IsElem a as ~ 'True) => Proxy a -> Proxy as -> Bool
 test _ _ = True

 x = test (Proxy :: Proxy Int) (Proxy :: Proxy '[])

 type family IsElem (x :: k) (xs :: [k]) where
     IsElem x '[] = 'False
     IsElem x (x ': xs) = 'True
     IsElem x (y ': xs) = IsElem x xs
 }}}

 The reason is that in typecheck/TcHsType.hs, the type family tycons are
 type-checked with knot-tying, however, they are being traced, forcing
 their evaluation which causes the typechecker to hang.

 My proposed fix is to only print the safe values that we know are
 constructed by the time of tracing.

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


More information about the ghc-tickets mailing list