[GHC] #16095: Infinite loop during error reporting (unkillable, OOM)

#16095: Infinite loop during error reporting (unkillable, OOM) -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Keywords: | Operating System: Linux Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compiling the repro snippet produces the following incomplete output and hangs GHC: {{{ $ ghc repro.hs [1 of 1] Compiling Main ( repro.hs, repro.o ) repro.hs:16:22: error: }}} The GHC process then ignores Ctrl-C -- so it must be killed with SIGKILL. This minimal snippet depends on `generics-sop` (tested with version `0.4.0.0`). Sadly I didn't find a constraint in `base` to cause this behavior.. {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} import Generics.SOP (HasDatatypeInfo) data family TF i a :: * data instance TF i a = R class C i a where method :: TF i a instance C i () where instance HasDatatypeInfo a => C i a where method = undefined function function :: C i a => TF i a function = method main = undefined }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16095 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16095: Infinite loop during error reporting (ignores SIGINT/SIGTERM, then OOMs) -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by _deepfire: Old description:
Compiling the repro snippet produces the following incomplete output and hangs GHC: {{{ $ ghc repro.hs [1 of 1] Compiling Main ( repro.hs, repro.o )
repro.hs:16:22: error: }}}
The GHC process then ignores Ctrl-C -- so it must be killed with SIGKILL.
This minimal snippet depends on `generics-sop` (tested with version `0.4.0.0`). Sadly I didn't find a constraint in `base` to cause this behavior..
{{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import Generics.SOP (HasDatatypeInfo)
data family TF i a :: * data instance TF i a = R
class C i a where method :: TF i a
instance C i () where
instance HasDatatypeInfo a => C i a where method = undefined function
function :: C i a => TF i a function = method
main = undefined }}}
New description: Compiling the repro snippet produces the following incomplete output and hangs GHC: {{{ $ ghc repro.hs [1 of 1] Compiling Main ( repro.hs, repro.o ) repro.hs:16:22: error: }}} The GHC process ignores SIGINT -- so it must be killed with SIGKILL. The memory usage grows, until it consumes all memory (~30G RAM + swap) and is terminated by the OOM killer. This minimal snippet depends on `generics-sop` (tested with version `0.4.0.0`). Sadly I didn't find a constraint in `base` to cause this behavior.. {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} import Generics.SOP (HasDatatypeInfo) data family TF i a :: * data instance TF i a = R class C i a where method :: TF i a instance C i () where instance HasDatatypeInfo a => C i a where method = undefined function function :: C i a => TF i a function = method main = undefined }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16095#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16095: Infinite loop during error reporting (ignores SIGINT/SIGTERM, then OOMs) -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by _deepfire: Old description:
Compiling the repro snippet produces the following incomplete output and hangs GHC: {{{ $ ghc repro.hs [1 of 1] Compiling Main ( repro.hs, repro.o )
repro.hs:16:22: error: }}}
The GHC process ignores SIGINT -- so it must be killed with SIGKILL. The memory usage grows, until it consumes all memory (~30G RAM + swap) and is terminated by the OOM killer.
This minimal snippet depends on `generics-sop` (tested with version `0.4.0.0`). Sadly I didn't find a constraint in `base` to cause this behavior..
{{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import Generics.SOP (HasDatatypeInfo)
data family TF i a :: * data instance TF i a = R
class C i a where method :: TF i a
instance C i () where
instance HasDatatypeInfo a => C i a where method = undefined function
function :: C i a => TF i a function = method
main = undefined }}}
New description: Compiling the repro snippet produces the following incomplete output and hangs GHC: {{{ $ ghc repro.hs [1 of 1] Compiling Main ( repro.hs, repro.o ) repro.hs:16:22: error: }}} The GHC process ignores SIGINT -- so it must be killed with SIGKILL. The memory usage grows, until it consumes all memory (~30G RAM + swap) and is terminated by the OOM killer. This minimal snippet depends on `generics-sop` (tested with version `0.4.0.0`). Sadly I didn't find a constraint in `base` to cause this behavior.. {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} import Generics.SOP (HasDatatypeInfo) data family TF i a :: * data instance TF i a = R class C i a where method :: TF i a instance C i () where instance HasDatatypeInfo a => C i a where method = undefined function function :: C i a => TF i a function = method main = undefined }}} Affects 8.4.3 and 8.6.1. Not tested on 8.6.2 & 8.6.3. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16095#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16095: Infinite loop during error reporting (ignores SIGINT/SIGTERM, then OOMs) -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): When the `HasDatatypeInfo` constraint is removed, the error in the code can be printed: {{{ Overlapping instances for C i0 a0 arising from a use of ‘function’ Matching instances: instance C i a -- Defined at doc/ghc-repro-16095.hs:15:10 instance C i () -- Defined at doc/ghc-repro-16095.hs:13:10 (The choice depends on the instantiation of ‘i0, a0’ To pick the first instance above, use IncoherentInstances when compiling the other instance declarations) In the first argument of ‘undefined’, namely ‘function’ In the expression: undefined function In an equation for ‘method’: method = undefined function }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16095#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16095: Infinite loop during error reporting (ignores SIGINT/SIGTERM, then OOMs) -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): Another, different repro for what seems to be a related problem: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeOperators #-} module Repro where import Generics.SOP recover :: forall a xs. (Code a ~ '[xs], HasDatatypeInfo a) => a recover = case datatypeInfo (Proxy @a) :: DatatypeInfo '[xs] of Newtype _ _ _ -> let sop :: NP [] xs = (undefined :: forall c xs . All c xs => NP [] xs) in undefined }}} ..once again, dependent on `generics-sop`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16095#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC