[GHC] #11710: Fusion of a simple listArray call is very fragile

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | 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: -------------------------------------+------------------------------------- Consider the following (taken from ticket:11707#comment:2), {{{#!hs module Test where import Data.Array arr, arr2 :: Array Int Int arr = listArray (0,10) [ 1,1,1,1,1,1,1,1,1,1 ] arr2 = listArray (0,10) [ 1,1,1,1,1,1,1,1,1,-1 ] }}} Given that these are a small array, one might suspect it would be worthwhile for GHC to fuse the lists with `listArray`, giving rise to two nicely unrolled construction procedures. However, if you look at the Core produced by `-O1` this you'll find that this only happens in the case of `arr2`. `arr` on the other handle, is mysteriously not fused. The fact that these expressions are so similar and yet produce entirely different code is quite worrying. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: 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 bgamari): And here's a quick quiz for those playing along at home: How much unrolling would you expect to happen in this case? {{{#!hs arr :: Array Int Int arr = listArray (0,10) [ 1,1,1,-1,1,1,1,1,1,1 ] }}} **Answer**: The first four elements will be unrolled; the remaining will be constructed by recursive pattern matching against a CAF `[Int]` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: 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 bgamari): For the record, the case in comment:1 results in this Core, {{{#!hs Test2.arr10 = GHC.Types.I# 1 Test2.arr11 = GHC.Types.I# (-1) Test2.arr1 = \ (@ s) (s1# :: GHC.Prim.State# s) -> case GHC.Prim.newArray# @Int @s 11 (GHC.Arr.arrEleBottom @Int) s1# of _ { (# ipv, ipv1 #) -> case GHC.Prim.writeArray# @s @Int ipv1 0 Test2.arr10 ipv of s4# { __DEFAULT -> case GHC.Prim.writeArray# @s @Int ipv1 1 Test2.arr10 s4# of s4#1 { __DEFAULT -> case GHC.Prim.writeArray# @s @Int ipv1 2 Test2.arr10 s4#1 of s4#2 { __DEFAULT -> case GHC.Prim.writeArray# @s @Int ipv1 3 Test2.arr11 s4#2 of s4#3 { __DEFAULT -> letrec { go :: [Int] -> GHC.Prim.Int# -> GHC.Prim.State# s -> GHC.Prim.State# s go = \ (ds :: [Int]) (eta :: GHC.Prim.Int#) (eta1 :: GHC.Prim.State# s) -> case ds of _ { [] -> eta1; : y ys -> case GHC.Prim.writeArray# @s @Int ipv1 eta y eta1 of s4#4 { __DEFAULT -> case eta of wild1 { __DEFAULT -> go ys (GHC.Prim.+# wild1 1) s4#4; 10 -> s4#4 } } }; } in case go Test2.arr4 4 s4#3 of wild4 { __DEFAULT -> case GHC.Prim.unsafeFreezeArray# @s @Int ipv1 wild4 of _ { (# ipv2, ipv3 #) -> (# ipv2, GHC.Arr.Array @Int @Int Test2.arr3 Test2.arr2 11 ipv3 #) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: 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 bgamari): The reason for this inconsistency appears to be the dynamic prefix log in `dsExplicitList`. Let's look at the desugared output that gave rise to comment:2, {{{#!hs arr = listArray GHC.Arr.$fIxInt (GHC.Types.I# 0, GHC.Types.I# 10) (GHC.Base.build (\ (@ a) (c [OS=OneShot] :: Int -> a -> a) (n [OS=OneShot] :: a) -> c (GHC.Types.I# 1) (c (GHC.Types.I# 1) (c (GHC.Types.I# 1) (c (negate GHC.Num.$fNumInt (GHC.Types.I# 1)) (GHC.Base.foldr c n (GHC.Types.: (GHC.Types.I# 1) (GHC.Types.: (GHC.Types.I# 1) (GHC.Types.: (GHC.Types.I# 1) (GHC.Types.: (GHC.Types.I# 1) (GHC.Types.: (GHC.Types.I# 1) (GHC.Types.: (GHC.Types.I# 1) (GHC.Types.[]))))))))))))) }}} We see that the desugarer took everything up to and including the `-1` element as the dynamic prefix. The dynamic prefix is defined in `dsExplicitList` as, {{{#!hs is_static :: CoreExpr -> Bool is_static e = all is_static_var (varSetElems (exprFreeVars e)) is_static_var :: Var -> Bool is_static_var v | isId v = isExternalName (idName v) -- Top-level things are given external names | otherwise = False -- Type variables (dynamic_prefix, static_suffix) = spanTail is_static xs' }}} That is, anything expression having a free variable with an external name (e.g. `negate` in the current example) is considered to be non-static, even if it will eventually be resolved to something static during simplification. If we consider that `foldr`/`build` is an optimization, the above behavior seems reasonable, preserving potential optimization opportunities by liberally applying `build` desugaring. This does, however, lead to slightly longer compilation times even in the case where fusion didn't fire as we need to rewrite `build` to a plain list during simplification. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: 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): Yes, see `Note [Desugaring explicit lists]` in `DsExpr`, about the "static tail" of a list. For `listArray (1,100) [1,2` we get {{{ let { $dIx_aHr :: Ix Integer [LclId, Str=DmdType] $dIx_aHr = GHC.Arr.$fIxInteger } in let { $dNum_aSd :: Num Integer [LclId, Str=DmdType] $dNum_aSd = GHC.Num.$fNumInteger } in let { $dNum_aSh :: Num Integer [LclId, Str=DmdType] $dNum_aSh = $dNum_aSd } in let { $dNum_aSj :: Num Integer [LclId, Str=DmdType] $dNum_aSj = $dNum_aSh } in let { $dNum_aSf :: Num Integer [LclId, Str=DmdType] $dNum_aSf = $dNum_aSd } in letrec { alex_table_aSk :: Array Integer Integer [LclId, Str=DmdType] alex_table_aSk = listArray @ Integer @ Integer $dIx_aHr (0, 100) (GHC.Types.: @ Integer 1 (GHC.Types.: @ Integer 2 (GHC.Types.[] @ Integer))); } }}} (The dead `Num` dictionaries happen because the desugarer short-circuits the calls to `fromInteger @ Integer`.) Notice that the list has no free vars, so via the "static tail" trick in `DsExpr` we generate an explicit list. But for `listArray (0,100) [-1,2]` we get {{{ let { $dIx_aHs :: Ix Integer [LclId, Str=DmdType] $dIx_aHs = GHC.Arr.$fIxInteger } in let { $dNum_aSe :: Num Integer [LclId, Str=DmdType] $dNum_aSe = GHC.Num.$fNumInteger } in let { $dNum_aSi :: Num Integer [LclId, Str=DmdType] $dNum_aSi = $dNum_aSe } in let { $dNum_aSm :: Num Integer [LclId, Str=DmdType] $dNum_aSm = $dNum_aSi } in let { $dNum_aSk :: Num Integer [LclId, Str=DmdType] $dNum_aSk = $dNum_aSi } in let { $dNum_aSg :: Num Integer [LclId, Str=DmdType] $dNum_aSg = $dNum_aSe } in letrec { alex_table_aSn :: Array Integer Integer [LclId, Str=DmdType] alex_table_aSn = listArray @ Integer @ Integer $dIx_aHs (0, 100) (GHC.Base.build @ Integer (\ (@ a_d22o) (c_d22p :: Integer -> a_d22o -> a_d22o) (n_d22q :: a_d22o) -> c_d22p (negate @ Integer $dNum_aSi 1) (GHC.Base.foldr @ Integer @ a_d22o c_d22p n_d22q (GHC.Types.: @ Integer 2 (GHC.Types.[] @ Integer))))); } in }}} Now the calls to `negate` have a dictionary `$dNum_asi` which isn't top- level, so the "static tail" stuff fails and we generate a `build`. **This is obviously far too fragile. I think we should just drop the "static tail" idea entirely.** It's never bad to generate the build form, except for generating bloated code; see #11707. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: 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): Then we can also get rid of `-fsimple-list-literals`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2023 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2023 * milestone: => 8.0.1 Comment: The fix from #11707, Phab:D2007, has been merged. Phab:D2023 removes the static tail business, as suggested by Simon in comment:4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: bug | Status: patch
Priority: normal | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2023
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2023 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11710: Fusion of a simple listArray call is very fragile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2023 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 193fdec1a4ad9a979974b21864ba026b35633170. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11710#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC