[GHC] #16095: Infinite loop during error reporting (ignores SIGINT/SIGTERM, then OOMs)
GHC
ghc-devs at haskell.org
Wed Dec 26 02:31:10 UTC 2018
#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
More information about the ghc-tickets
mailing list