[GHC] #13104: runRW# ruins join points

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: JoinPoints | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Found this while poking around in the example for #12781. Suppose we have code like this: {{{ let loop :: Int -> State# RealWorld -> (State# RealWorld, Int) loop n = ... loop (n+1) {- tail call -} ... in runRW# @ 'PtrRepLifted @ Int (loop 0) }}} We would love for `loop` to be a join point, but it can't be because it's invoked in the argument to `runRW#`. In this situation, we're often rescued by Float In, which we might hope to give us this: {{{ runRW# @ 'PtrRepLifted @ Int ( let loop :: Int -> State# RealWorld -> (State# RealWorld, Int) loop n s = ... loop (n+1) s' {- tail call -} ... in loop 0 ) }}} Two problems: 1. Float In won't do this to begin with because `loop 0` is a partial application. 2. It's still not eligible to be a join point, again because `loop 0` is a partial application. What we would //like// to see is this: {{{ runRW# @ 'PtrRepLifted @ Int ( \s0 -> let loop :: Int -> State# RealWorld -> (State# RealWorld, Int) loop n s = ... loop (n+1) s' {- tail call -} ... in loop 0 s0 ) }}} Now we're golden. But someone has to have thought to eta-expand the argument to `runRW#` first. (Float In should then float `loop` into the lambda because, due to the state hack, the lambda is considered one-shot.) Perhaps the simplifier should //always// eta-expand the argument to `runRW#`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Where does this occurence of `runRW#` come from? Before adding hacks to the simplifier, it might be sufficient to eta- expand the argument there. For example, instead of {{{ runST (ST st_rep) = case runRW# st_rep of (# _, a #) -> a }}} write {{{ runST (ST st_rep) = case runRW# (\s. st_rep s) of (# _, a #) -> a }}} or, for good measure, {{{ runST (ST st_rep) = case runRW# (oneShot (\s. st_rep s)) of (# _, a #) -> a }}} Have you tried that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): What does the code for `loop` look like? Why isn't it eta-expaned anyway? What's the source code for the example to reproduce this? In #12781 you said that join points solved the example there... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * failure: None/Unknown => Runtime performance bug * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) Comment: Would it be possible to reimplement `runRW#` as a magic function with a compulsory unfolding, so that `runRW# f` expands to the following? {{{#!hs join $j s = f s {-# NOINLINE $j #-} in jump $j realWorld# }}} This would not only close this ticket but also allow other optimizations like pushing a `case` into the body of `f`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Just a warning: I am wary with exposing the `realWorld#` item here. I played with similar (less sophisticated) ideas three years ago, and found that all too easily different invocations of `runRW#` would end up getting mixed up, e.g. by CSE. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Cool idea though. See `Note [runRW magic]` in `MkId` for the main comment on this. I like the way that consumers correctly consume the result. We'd really like that NOINLINE to disapper right at the end somehow. One thing I like about `runRW#` is that it signals the magic very clearly; somehow a NOINLINE on a join point feels a bit too subtle. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dobenour): What about adding a new function `runRW##` and allowing -1 to be the phase argument to INLINE? Specifically: {{{#!hs {-# LANGAUGE MagicHash #-} import GHC.Prim runRW## :: forall (r1 :: RuntimeRep). (o :: TYPE r) => State# RealWorld -> (# State# RealWorld, o #) -> (# State# RealWorld, o#) runRW## f = f realWorld# {-# INLINE [-1] runRW## #-} }}} with `runRW# f` having the compulsory unfolding {{{#!hs join $j s = f s {-# INLINE [-1] $j #-} in runRW## @ 'PtrRepLifted @ _ ( \s0 -> $j s }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): This wouldn’t be a valid use of a join point, would it? You cannot pass join-points in lambdas to arguments. But maybe that points to a solution. Can we somehow tell GHC that the argument of `runRW#` is special in the sense that passing a join-point call there is ok? So to say, a promise that by the time we generate code, the argument will be passed `n` functions and be used in a join-point eligible way? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Can we somehow tell GHC that the argument of runRW# is special in the sense that passing a join-point call there is ok?
That would be horribly ad-hoc. We need a better way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
That would be horribly ad-hoc. We need a better way.
*shrug* no more than the the one-shot hack we had for `build` before we came up with a proper analysis that could figure out that information. I guess the difference here is that we don’t expect random user-defined functions to have this property. The discussion of eta-expanding the argument of `runRW#` has been interrupted by comment:4, we should consider that thought again. Maybe one of the variants in comment:1 nail it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See Trac #15127. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thinking about #13104 and #15127, I am gradually being driven to the conclusion that we should treat `runRW#` specially in the simplifier. And perhaps a few other primops (like `maskAsyncExceptions#` too). I just can't see a better way to deal with it. Here's my brain-dump: * Require that the argument of `runRW#` is always eta-expanded, with a one-shot lambda. Similar to the RHS of a join point. This would be an invariant of Core, and checked by Core Lint. * Make `Simplify` push the continuation into the body of the `runRW`, just as it does with join points. So, for example: {{{ case (runRW# (\s.e)) of blah ==> runRW# (\s. case e of blah) }}} * I think that `FloatIn` will do the right thing automatically, provided the lambda is marked one-shot. * Maybe, instead of doing mysterious inlining things in `CorePrep` (as we do now), we could just make the code generator do the Right Thing directly? Just as join bindings look like let-bindings, and in most ways behave like them, but have additional invariants that are checked by Core Lint, so similarly with `runRW# (\s.e)`. I have not yet thought through which other primops should particpate in this party. Certainly the `maskAsyncExceptions#` and unmask families. Probably not `catch#` becuase we have to be so careful about moving code into our out of the scope of an exception handler. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by chessai): * owner: (none) => chessai * milestone: => 8.8.1 Comment: I would like to work on this as a warm-up to my work on #15560. Reviewing the issue, I agree with Simon's last comment about `runRW#` being treated specially. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points
-------------------------------------+-------------------------------------
Reporter: lukemaurer | Owner: chessai
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.1
Resolution: | Keywords: JoinPoints
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by sgraf):
* cc: sgraf (added)
Comment:
I very much agree with what nomeata (comment:10) and simonpj (comment:14)
said. We should aim for `loop 0` to be eta-expanded by realising that
`runRW#` only calls its argument once.
I would begin by looking at how `runRW#` gets its demand signature. It's
not listed in primops.txt.pp, so it doesn't seem to be hard-coded into the
compiler. It gets 'inlined' in CorePrep and in `cpe_app` there's a test
for `runRWKey`.
The problem, I guess, is that `runRW#` isn't a recognized primop. On the
other hand, it doesn't seem to be a regular identifier, either: If the
demand analyser were to look into its definition, it would be given a
demand signature of `

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by chessai): Replying to [comment:16 sgraf]:
I very much agree with what nomeata (comment:10) and simonpj (comment:14) said. We should aim for `loop 0` to be eta-expanded by realising that `runRW#` only calls its argument once.
I would begin by looking at how `runRW#` gets its demand signature. It's not listed in primops.txt.pp, so it doesn't seem to be hard-coded into the compiler. It gets 'inlined' in CorePrep and in `cpe_app` there's a test for `runRWKey`.
The problem, I guess, is that `runRW#` isn't a recognized primop. On the other hand, it doesn't seem to be a regular identifier, either: If the demand analyser were to look into its definition, it would be given a demand signature of `
`, e.g. a signature saying that it calls its argument exactly once with one argument. We want the one-shot (i.e. usage demand) part, but apparently (see Note [runRW magic] in CorePrep) not the strictness part. So, I'd say `runRW#` should be handled as a regular primop like i.e. `catch#` and give it a `lazyApply1Dmd`. If this doesn't help, we could always fall back to more special cases.
This is pretty useful information, thanks!
When you say 'handle _like_ a regular primop', do you mean to say 'make it
a primop'?
To be clear, while currently the demand signature of `runRW#` is `

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Yes, I meant 'make runRW# a proper primop'. It's treated like one by Core anyway. This mostly entails adding it to primops.txt.pp, but I'd suggest grepping for mentions of another primop like `seq#` (lowered in STG, IIRC) and handle it the same way.
To be clear, while currently the demand signature of runRW# is
, and you'd rather it be < L, C1(U)>? Why? How is this laziness related to the problem related to the Note [runRW magic]?
I got the note wrong. I was referring to `Note [runRW arg]`, but that note
says that we ''should'' make `runRW#` strict and says that we do so in
`MkId`. I couldn't find any mention of runRW in there, so that may have
been a lie, not sure. So, it seems that `

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Primops are intended to reflect machine operations that simply cannot be expressed more simply in Haskell (at least not efficiently): e.g. add two `Int#` values. Things like `unsafeCoerce#`, `lazy`, and `runRW#` really are expressible in a functional style; and "lowering" them in `CoreToSTG` feels like the right place to deal with them. So yes, either known-key or wired-in `Id`. We need wired-in if we need IdInfo that won't be inferred; but actually I think the right strictness ''will'' be inferred from its definition, so maybe known-key is enough. The important thing is that we don't inline it until very very late; and (sadly) we may want the simplifier to treat it specially. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Replying to [comment:19 simonpj]:
So yes, either known-key or wired-in `Id`. We need wired-in if we need IdInfo that won't be inferred; but actually I think the right strictness ''will'' be inferred from its definition, so maybe known-key is enough.
Ah, right. I thought I checked this and expected `runRW#`'s strictness
signature to be present in the interface file for `GHC.Exts`, but it
wasn't, so I assumed it got special treatment, like wired-in things.
It turns out that `f` in the this program
{{{
{-# LANGUAGE MagicHash #-}
module Foo where
import GHC.Magic
f = runRW#
}}}
has the right strictness signature `

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: infoneeded Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * status: new => infoneeded Comment: Actually, I don't think this reproduces any longer. What's actually the regression test here? The argument to `runST` in #12781 is properly eta- expanded in GHC 8.4.3. Any attempt to manually reproduce the issue with similar code as in the OP, e.g. {{{ f = runST (loop (0 :: Int)) where loop 1000 = return 42 loop n = loop (n+1) }}} leads to this Core for `f`: {{{ Rec { -- RHS size: {terms: 14, types: 11, coercions: 0, joins: 0/0} $wloop $wloop = \ ww_s2DT w_s2DQ -> case ww_s2DT of wild_Xk { __DEFAULT -> $wloop (+# wild_Xk 1#) w_s2DQ; 1000# -> (# w_s2DQ, lvl_r2Eo #) } end Rec } -- RHS size: {terms: 4, types: 2, coercions: 0, joins: 0/0} f1 f1 = \ w_s2DQ -> $wloop 0# w_s2DQ -- RHS size: {terms: 5, types: 30, coercions: 0, joins: 0/0} f f = case runRW# f1 of { (# ipv_a2Bw, ipv1_a2Bx #) -> ipv1_a2Bx } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: chessai Type: bug | Status: infoneeded Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): whats the current state of play for this bug? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13104#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC