[GHC] #14511: indexArray# getting poorly deferred

#14511: indexArray# getting poorly deferred -------------------------------------+------------------------------------- Reporter: reinerp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In both of the following functions I am attempting to execute a read from an `Array# a` and then write the result to a `MutableArray# s a`, and I would like the following evaluation properties: * the `a` value is not forced, i.e. the value stored in the `MutableArray# s a` will remain a thunk if the original value in the `Array# a` was; and * the new `MutableArray#` does not maintain any references to the original `Array#`, so that the original can be GCed. The singleton-unboxed-tuple return type of `indexArray#` appears to be there to allow specifically this use case, but sadly it only succeeds for the first of these functions. The second function ends up storing a thunk in the `MutableArray#` which contains a reference to the `Array#`. Haskell: {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} module IndexThenWrite where import GHC.Prim indexThenWrite :: Array# a -> MutableArray# s a -> State# s -> State# s indexThenWrite arr marr s = case indexArray# arr 123# of (# a #) -> writeArray# marr 234# a s indexThenWriteF :: (a -> b) -> Array# a -> MutableArray# s b -> State# s -> State# s indexThenWriteF f arr marr s = case indexArray# arr 123# of (# a #) -> writeArray# marr 234# (f a) s }}} Core: {{{#!hs -- RHS size: {terms: 15, types: 18, coercions: 0, joins: 0/0} indexThenWrite indexThenWrite = \ @ a_aq9 @ s_aqa arr_apa marr_apb s1_apc -> case indexArray# arr_apa 123# of { (# ipv_sUH #) -> writeArray# marr_apb 234# ipv_sUH s1_apc } -- RHS size: {terms: 18, types: 22, coercions: 0, joins: 0/0} indexThenWriteF indexThenWriteF = \ @ a_aq0 @ b_aq1 @ s_aq2 f_ape arr_apf marr_apg s1_aph -> writeArray# marr_apg 234# (case indexArray# arr_apf 123# of { (# ipv_sUK #) -> f_ape ipv_sUK }) s1_aph }}} I'd like the second function to generate code similar to the first. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14511 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14511: indexArray# getting poorly deferred
-------------------------------------+-------------------------------------
Reporter: reinerp | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
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):
Good point. Works fine in HEAD, as a result of this (post-8.2) patch
{{{
commit 751996e90a964026a3f86853338f10c82db6b610
Author: Simon Peyton Jones

#14511: indexArray# getting poorly deferred -------------------------------------+------------------------------------- Reporter: reinerp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: 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 reinerp): Thanks Simon. I've worked around this with `{-# OPTIONS_GHC -fno-float-in #-}` on the relevant modules. Not important for 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14511#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14511: indexArray# getting poorly deferred -------------------------------------+------------------------------------- Reporter: reinerp | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14511#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14511: indexArray# getting poorly deferred
-------------------------------------+-------------------------------------
Reporter: reinerp | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.4.1
Component: Compiler | Version: 8.2.1
Resolution: fixed | Keywords:
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 Simon Peyton Jones
participants (1)
-
GHC