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

#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

#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 (Type | Version: 8.1 checker) | Keywords: typefamilies Resolution: | trace hangs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kcsongor): * Attachment "TypeFamilyErrors_4.hs" added. Relevant file to reproduce the issue -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11708 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.1 checker) | Keywords: typefamilies Resolution: | trace hangs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D2006 -------------------------------------+------------------------------------- Changes (by kcsongor): * differential: => https://phabricator.haskell.org/D2006 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11708#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11708: Typechecker hangs when checking type families with -ddump-tc-trace turned on -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: kcsongor Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: typefamilies Resolution: | trace hangs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2006 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => patch * differential: https://phabricator.haskell.org/D2006 => Phab:D2006 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11708#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11708: Typechecker hangs when checking type families with -ddump-tc-trace turned on -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: kcsongor Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: typefamilies Resolution: | trace hangs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2006 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I actually hit this bug locally and so merged @kcsongor's patch. Will push in due course. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11708#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11708: Typechecker hangs when checking type families with -ddump-tc-trace turned
on
-------------------------------------+-------------------------------------
Reporter: kcsongor | Owner: kcsongor
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.1
checker) | Keywords: typefamilies
Resolution: | trace hangs
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2006
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#11708: Typechecker hangs when checking type families with -ddump-tc-trace turned on -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: kcsongor Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: typefamilies Resolution: | trace hangs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2006 Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: patch => merge * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11708#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11708: Typechecker hangs when checking type families with -ddump-tc-trace turned on -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: kcsongor Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: typefamilies Resolution: fixed | trace hangs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2006 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged as f7eb12f72303cc2c6229b9d94da263ca17b5cf35. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11708#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC