[GHC] #13458: Panic with unsafeCoerce and -dcore-lint

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE MagicHash, TypeInType, ScopedTypeVariables #-} module UIOST where import GHC.Exts import Data.Kind import Unsafe.Coerce unsafeCoerce' :: forall (r :: RuntimeRep) (a :: TYPE r) (b :: TYPE r). a -> b unsafeCoerce' = unsafeCoerce unsafeCoerce }}} Compiling this with optimization and `-dcore-lint` produces a panic: {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20170308 for x86_64-unknown-linux): runtimeRepPrimRep typePrimRep (a_aW7 :: TYPE r_aW6) r_aW6 Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1191:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:360:5 in ghc:RepType }}} Using `unsafeCoerce# unsafeCoerce` produces the panic without optimization. I have not been able to reproduce the problem without `-dcore-lint`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | 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 dfeuer: Old description:
{{{#!hs {-# LANGUAGE MagicHash, TypeInType, ScopedTypeVariables #-} module UIOST where import GHC.Exts import Data.Kind import Unsafe.Coerce
unsafeCoerce' :: forall (r :: RuntimeRep) (a :: TYPE r) (b :: TYPE r). a -> b unsafeCoerce' = unsafeCoerce unsafeCoerce }}}
Compiling this with optimization and `-dcore-lint` produces a panic:
{{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20170308 for x86_64-unknown-linux): runtimeRepPrimRep typePrimRep (a_aW7 :: TYPE r_aW6) r_aW6 Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1191:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:360:5 in ghc:RepType }}}
Using `unsafeCoerce# unsafeCoerce` produces the panic without optimization. I have not been able to reproduce the problem without `-dcore-lint`.
New description: {{{#!hs {-# LANGUAGE MagicHash, TypeInType, ScopedTypeVariables #-} module UIOST where import GHC.Exts import Data.Kind import Unsafe.Coerce unsafeCoerce' :: forall (r :: RuntimeRep) (a :: TYPE r) (b :: TYPE r). a -> b unsafeCoerce' = unsafeCoerce id }}} Compiling this with optimization and `-dcore-lint` produces a panic: {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20170308 for x86_64-unknown-linux): runtimeRepPrimRep typePrimRep (a_aW7 :: TYPE r_aW6) r_aW6 Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1191:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:360:5 in ghc:RepType }}} Using `unsafeCoerce# id` produces the panic without optimization. I have not been able to reproduce the problem without `-dcore-lint`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | 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 dfeuer): I think the trouble here is that the (properly uninhabited) type {{{#!hs forall (r :: RuntimeRep) (a :: TYPE r) (b :: TYPE r). a -> b }}} has kind `*`, so `unsafeCoerce` happily accepts it as a target. But then when `unsafeCoerce` inlines, core lint sees `unsafeCoerce#` being used in a bogus fashion. Question: do representation-polymorphic functions need to get non-`*` kinds? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | 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 dfeuer): Another possible approach would be to find a way to avoid the crash and just compile the bogus code like the fool said.... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => goldfire Comment: It looks like this is squarely in Richard's territory. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | 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 dfeuer): One thought: we currently have a rule that no variable can have a levity- polymorphic type, but that doesn't seem quite strong enough in the presence of `unsafeCoerce`. One option might be to decree that a levity- polymorphic type can't occur in negative position in the signature of a binding. That is, I think we should likely reject the ''signature'' of `unsafeCoerce'` altogether. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | 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 dfeuer): Reid thinks we should compile fine and just crash and burn at runtime. I'm fine with that too, but Richard will have to decide. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | 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 rwbarton): If you change the type signature to `unsafeCoerce' :: Int# -> Int#` then the generated core is {{{ unsafeCoerce' = (id @ Any) `cast` (UnsafeCo representational Any Int# -> UnsafeCo representational Any Int# :: ((Any -> Any) :: *) ~R# ((Int# -> Int#) :: *)) }}} Optimizing the coercion like this seems dubious when the new coercions are ill-kinded. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => LevityPolymorphism -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | 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 goldfire): I'm on it. Indeed, I believe I've fixed this, but need to rebuild to be sure. The problem is the checks from #9122 that try to make sure we're not `unsafeCoerce`ing between types with incompatible representations. But when we look to see about the representations involved here, the types don't have representations, so GHC falls over. What's annoying is that the user-written program is safe in this regard. It's the coercion optimizer that rewrites an `unsafeCoerce` from a lifted type to a lifted type (`Any -> Any` to `a -> b`) to two `unsafeCoerce`s involving `a` and `b` separately. Thus, an alternate fix would be to have the coercion optimizer look for precisely this scenario and avoid pushing the unsafe coercion through the `->`. I haven't done this for two reasons: 1. Failing the checks from #9122 (which I've never fully agreed with) is a sometimes-unavoidable consequence of a sketchy `unsafeCoerce`. The workaround if you're in this scenario is not to use `-dcore-lint`. The original program is pretty sketchy here, and so requiring that user to avoid `-dcore-lint` may be reasonable. 2. It's quite annoying (and potentially computationally expensive) to do this check in the coercion optimizer. The check is necessary only when the user is willfully misbehaving, and the better citizens shouldn't have to pay for it every time. Regardless, GHC shouldn't panic. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | 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 simonpj): Another thought. The current `unsafeCoerce#` (defined in `MkId`) has type {{{ -- unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) -- (a :: TYPE r1) (b :: TYPE r2). -- a -> b }}}` But it's super-dangerous to coerce from (say) a pointer type to a `Word#` and back. Perhaps the slightly more restrictive type {{{ -- unsafeCoerce# :: forall (r :: RuntimeRep) -- (a :: TYPE r) (b :: TYPE r). -- a -> b }}} would correctly capture many the "rule" specified in the documentation for `unsafeCoerce`? Regardless, a crash is bad. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | 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 goldfire): I'm uncomfortable with restricting the type of `unsafeCoerce#`. What if someone wants to do something really dirty, like cast a `Float#` into a `Word#` just to see the bits? This would be prohibited by comment:10. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: goldfire
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.1
checker) | Keywords:
Resolution: | LevityPolymorphism
Operating System: Unknown/Multiple | 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 Richard Eisenberg

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge * testcase: => typecheck/should_compile/T13458 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): This is causing a large number of warnings to be printed while building GHC, of the form {{{ <no location info>: warning: In the expression: byteArrayContents# (ipv3_s9ST `cast` (UnsafeCo representational (MutableByteArray# RealWorld) ByteArray# :: (MutableByteArray# RealWorld :: TYPE 'UnliftedRep) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: left-hand type is levity-polymorphic From: MutableByteArray# RealWorld To: ByteArray# <no location info>: warning: In the expression: byteArrayContents# (ipv3_s9ST `cast` (UnsafeCo representational (MutableByteArray# RealWorld) ByteArray# :: (MutableByteArray# RealWorld :: TYPE 'UnliftedRep) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: right-hand type is levity-polymorphic From: MutableByteArray# RealWorld To: ByteArray# }}} and these statements do not appear to be correct. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: fixed | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged comment:12 to `ghc-8.2` as 662c64226e302009175abfa7ed196ac905990486. I'll look into the warnings. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * owner: goldfire => (none) * priority: normal => highest * status: closed => new * resolution: fixed => Comment: This cure is worse than the disease was--Core Lint now seems to warn about *every* unsafe coercion; and the volume of warnings produced during the build of ghc somehow broke https://perf.haskell.org/ghc/. Can we revert this for now? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Richard, it's your commit. Might you look? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, the lint checks where reverted in 03c7dd0941fb4974be54026ef3e4bb97451c3b1f. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I have reverted comment:12 in `ghc-8.2` in 3ebbc387e3207dc7b5743a1dc6e20df6d4152282. We'll need to re-assess this situation prior to the release. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13458: Panic with unsafeCoerce and -dcore-lint -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: fixed | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13458 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: The lint check from comment:12 was fixed and reenabled in f3af0463c81002a64a3b3e9a01351e64460c490f. `T13458` now passes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13458#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC