[GHC] #11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case --------------------------------------+---------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Keywords: | Operating System: Linux Architecture: arm | Type of failure: Runtime crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+---------------------------------- The body of `stg_ap_pp_fast` looks like {{{ arity = TO_W_(StgFunInfoExtra_arity(%GET_FUN_INFO(R1))); ASSERT(arity > 0); if (arity == 1) { Sp_adj(-2); W_[Sp+WDS(1)] = R3; W_[Sp+WDS(0)] = stg_ap_p_info; R1 = R1 + 1; jump_SAVE_CCCS(%GET_ENTRY(UNTAG(R1))); } if (arity == 2) { Sp_adj(0); R1 = R1 + 2; jump %GET_ENTRY(UNTAG(R1)) [R1,R2,R3]; } else { Sp_adj(-3); W_[Sp+WDS(2)] = R3; W_[Sp+WDS(1)] = R2; if (arity < 4) { R1 = R1 + arity; } BUILD_PAP(2,2,stg_ap_pp_info,FUN); } }}} where {{{ // Jump to target, saving CCCS and restoring it on return #if defined(PROFILING) #define jump_SAVE_CCCS(target) \ Sp(-1) = CCCS; \ Sp(-2) = stg_restore_cccs_info; \ Sp_adj(-2); \ jump (target) [R1] #else #define jump_SAVE_CCCS(target) jump (target) [R1] #endif }}} So in the arity=1 case the jump amounts to {{{ jump (%GET_ENTRY(UNTAG(R1))) [R1] }}} R1 is the function to apply, but we don't pass its argument, R2! Now, possibly by design, the calling convention of `stg_ap_pp_fast` is such that the first argument to apply is in R2, which is the same register that the function R1 will expect to find its argument in. So if nothing happens to disturb R2 (and possibly this is always the case with the NCG), then everything is fine. However, it's definitely not fine for the LLVM backend, which quite reasonably passes `undef` for the R2, R3, and R4 arguments when doing the jump. On arm/Android, LLVM decided to clobber `r8` (the physical register for R2) in the body of `stg_ap_pp_fast`. This caused a crash for the following program: {{{ main = print (read "3"::Int) }}} This appears to have been broken by commit f9265dd369b9e269349930012c25e670248f2a09 which changed the argument list for `jump_SAVE_CCCS` from `[*]` to `[R1]`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Description changed by rwbarton: @@ -53,1 +53,2 @@ - `r8` (the physical register for R2) in the body of `stg_ap_pp_fast`. + `r8` (the physical register for R2) in the body of `stg_ap_ppp_fast` + (which has the same problems as `stg_ap_pp_fast`). New description: The body of `stg_ap_pp_fast` looks like {{{ arity = TO_W_(StgFunInfoExtra_arity(%GET_FUN_INFO(R1))); ASSERT(arity > 0); if (arity == 1) { Sp_adj(-2); W_[Sp+WDS(1)] = R3; W_[Sp+WDS(0)] = stg_ap_p_info; R1 = R1 + 1; jump_SAVE_CCCS(%GET_ENTRY(UNTAG(R1))); } if (arity == 2) { Sp_adj(0); R1 = R1 + 2; jump %GET_ENTRY(UNTAG(R1)) [R1,R2,R3]; } else { Sp_adj(-3); W_[Sp+WDS(2)] = R3; W_[Sp+WDS(1)] = R2; if (arity < 4) { R1 = R1 + arity; } BUILD_PAP(2,2,stg_ap_pp_info,FUN); } }}} where {{{ // Jump to target, saving CCCS and restoring it on return #if defined(PROFILING) #define jump_SAVE_CCCS(target) \ Sp(-1) = CCCS; \ Sp(-2) = stg_restore_cccs_info; \ Sp_adj(-2); \ jump (target) [R1] #else #define jump_SAVE_CCCS(target) jump (target) [R1] #endif }}} So in the arity=1 case the jump amounts to {{{ jump (%GET_ENTRY(UNTAG(R1))) [R1] }}} R1 is the function to apply, but we don't pass its argument, R2! Now, possibly by design, the calling convention of `stg_ap_pp_fast` is such that the first argument to apply is in R2, which is the same register that the function R1 will expect to find its argument in. So if nothing happens to disturb R2 (and possibly this is always the case with the NCG), then everything is fine. However, it's definitely not fine for the LLVM backend, which quite reasonably passes `undef` for the R2, R3, and R4 arguments when doing the jump. On arm/Android, LLVM decided to clobber `r8` (the physical register for R2) in the body of `stg_ap_ppp_fast` (which has the same problems as `stg_ap_pp_fast`). This caused a crash for the following program: {{{ main = print (read "3"::Int) }}} This appears to have been broken by commit f9265dd369b9e269349930012c25e670248f2a09 which changed the argument list for `jump_SAVE_CCCS` from `[*]` to `[R1]`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Description changed by rwbarton: @@ -60,0 +60,1 @@ + when built with `-debug`. New description: The body of `stg_ap_pp_fast` looks like {{{ arity = TO_W_(StgFunInfoExtra_arity(%GET_FUN_INFO(R1))); ASSERT(arity > 0); if (arity == 1) { Sp_adj(-2); W_[Sp+WDS(1)] = R3; W_[Sp+WDS(0)] = stg_ap_p_info; R1 = R1 + 1; jump_SAVE_CCCS(%GET_ENTRY(UNTAG(R1))); } if (arity == 2) { Sp_adj(0); R1 = R1 + 2; jump %GET_ENTRY(UNTAG(R1)) [R1,R2,R3]; } else { Sp_adj(-3); W_[Sp+WDS(2)] = R3; W_[Sp+WDS(1)] = R2; if (arity < 4) { R1 = R1 + arity; } BUILD_PAP(2,2,stg_ap_pp_info,FUN); } }}} where {{{ // Jump to target, saving CCCS and restoring it on return #if defined(PROFILING) #define jump_SAVE_CCCS(target) \ Sp(-1) = CCCS; \ Sp(-2) = stg_restore_cccs_info; \ Sp_adj(-2); \ jump (target) [R1] #else #define jump_SAVE_CCCS(target) jump (target) [R1] #endif }}} So in the arity=1 case the jump amounts to {{{ jump (%GET_ENTRY(UNTAG(R1))) [R1] }}} R1 is the function to apply, but we don't pass its argument, R2! Now, possibly by design, the calling convention of `stg_ap_pp_fast` is such that the first argument to apply is in R2, which is the same register that the function R1 will expect to find its argument in. So if nothing happens to disturb R2 (and possibly this is always the case with the NCG), then everything is fine. However, it's definitely not fine for the LLVM backend, which quite reasonably passes `undef` for the R2, R3, and R4 arguments when doing the jump. On arm/Android, LLVM decided to clobber `r8` (the physical register for R2) in the body of `stg_ap_ppp_fast` (which has the same problems as `stg_ap_pp_fast`). This caused a crash for the following program: {{{ main = print (read "3"::Int) }}} when built with `-debug`. This appears to have been broken by commit f9265dd369b9e269349930012c25e670248f2a09 which changed the argument list for `jump_SAVE_CCCS` from `[*]` to `[R1]`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Changes (by simonpj): * cc: gmainland (added) Comment: Sounds bad to me. Geoff, can you comment as the author of the commit Reid identifies? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Changes (by bgamari): * priority: high => highest Comment: Seems like this should really be highest priority given this has the potential to cause crashes and is working by mere chance at the moment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by rwbarton): The commit in question does produce the correct argument list for the arity=2 case. So this is probably just a matter of going through all the other cases and making sure the argument lists are right. genapply is a bit large though... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by gmainland): My recollection is that we were saving too many registers and therefore taking a notable performance hit on LLVM. Now we are apparently saving too few, but only when saving the current cost centre stack :) If nobody else gets to it, I will put a patch on Phab within a week. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by simonmar): Good catch! It looks wrong to me. You probably need to pass the list of argument registers to `jump_SAVE_CCS` and attach them to the final jump. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Changes (by simonpj): * owner: => gmainland -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by gmainland): Perhaps someone can volunteer to at least test? This appears to only manifest on ARM, and I don't have access to an ARM system. Would validate --slow on ARM catch this bug? From the bug report, it seems that perhaps the answer is "no." That should be fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by bgamari): I have an ARM box which I can test with. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by gmainland): Great, can you also get a test into the testsuite that will detect this bug? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by bgamari): Although sadly it seems I can't reproduce the issue on said machine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by bgamari): I've proposed a testcase in Phab:D1851. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by gmainland): I guess it will be difficult for you to test any proposed fix then :) Reid, can you help? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by rwbarton): I think the reason that I only saw this bug with `-debug` is that the debug version of `stg_ap_ppp_fast` has extra code to print logging information when some debug flags are activated. This created enough register pressure that LLVM decided to rearrange some registers including `r8`, the ARM register that holds R2. Because `stg_ap_ppp_fast` invokes the function it calls with the R2 argument `undef`, once `r8` was clobbered, the invoked function saw the wrong value for R2, and a crash was inevitable. So here is a plan for testing for this bug, and others like it. * Add a flag `-fllvm-fill-undef-with-garbage`, and pass it when running validate. * In `Llvm.Types.ppLit`, if this flag is enabled, output `0xbbbbbbbb...` (of whatever size is needed) rather than `undef`. Then all LLVM builds should catch issues like this one. I can implement this if it sounds reasonable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -----------------------------------+--------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+--------------------------------- Comment (by gmainland): Sounds reasonable to me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1858 Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * differential: => Phab:D1858 * os: Linux => Unknown/Multiple * architecture: arm => Unknown/Multiple -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: gmainland
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Runtime System | Version: 8.0.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1858
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1864 Wiki Page: | -------------------------------------+------------------------------------- Changes (by gmainland): * differential: Phab:D1858 => Phab:D1864 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: gmainland
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Runtime System | Version: 8.0.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1864
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Geoffrey Mainland

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: gmainland
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Runtime System | Version: 8.0.1-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1864
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Geoffrey Mainland

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1864 Wiki Page: | -------------------------------------+------------------------------------- Changes (by gmainland): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1864 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thank you Geoff! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1864 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11487: stg_ap_pp_fast doesn't pass the argument in the arity=1 case -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: gmainland Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1864 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged to `ghc-8.0` as c1f8f7da4bbff2f2093fa084811d790b78576d08, 3591a6fe7b2ad5b2ca013548e9267ad1783bc7a5, and 675b4467d21e39eb89d1537eb1e60cafcdc49c38. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11487#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC