[GHC] #15570: Core transformations generate bad indexCharOffAddr# call

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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: -------------------------------------+------------------------------------- Consider the following functions, which only differ in a bang pattern on the local binding `q` in the inner loop: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} module Bug where import GHC.Prim import GHC.Types f :: Int -> String f n_ = go n_ "" where go n cs | n < 62 = let !c = chooseChar62 n in c : cs | otherwise = go q (c : cs) where (q, r) = quotRem n 62 !c = chooseChar62 r chooseChar62 :: Int -> Char {-# INLINE chooseChar62 #-} chooseChar62 (I# n) = C# (indexCharOffAddr# chars62 n) chars62 = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"# g :: Int -> String g n_ = go n_ "" where go n cs | n < 62 = let !c = chooseChar62 n in c : cs | otherwise = go q (c : cs) where (!q, r) = quotRem n 62 -- !!! Note the bang on q !c = chooseChar62 r chooseChar62 :: Int -> Char {-# INLINE chooseChar62 #-} chooseChar62 (I# n) = C# (indexCharOffAddr# chars62 n) chars62 = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"# }}} When building with `-O -fPIC -dynamic -ddump-simpl`, this is the Core I see, with a HEAD checkout from earlier this week built by hadrian: {{{#!hs -- chararacter array, used by both chars62_r30r :: Addr# chars62_r30r = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"# -- Used at the end of Bug.$wgo, in the -9223372036854775808# branch, -- therefore only used by generated Core for f, but not g! lvl_r30s :: Char lvl_r30s = case indexCharOffAddr# chars62_r30r -9223372036854775808# of v_B2 { __DEFAULT -> GHC.Types.C# v_B2 } -- Core for f Rec { Bug.$wgo :: Int# -> [Char] -> (# Char, [Char] #) Bug.$wgo = \ (ww_s2WU :: Int#) (w_s2WR :: [Char]) -> case GHC.Real.even3 of { I# y_a2QI -> -- GHC.Real.even3 == -1 case y_a2QI of { __DEFAULT -> case quotRemInt# ww_s2WU 62# of { (# ipv_a2QN, ipv1_a2QO #) -> case indexCharOffAddr# chars62_r30r ipv1_a2QO of wild2_X4 { __DEFAULT -> case <# ww_s2WU 62# of { __DEFAULT -> Bug.$wgo ipv_a2QN (GHC.Types.: @ Char (GHC.Types.C# wild2_X4) w_s2WR); 1# -> case indexCharOffAddr# chars62_r30r ww_s2WU of wild3_X1G { __DEFAULT -> (# GHC.Types.C# wild3_X1G, w_s2WR #) } } } }; 62# -> case ww_s2WU of wild2_a2QQ { __DEFAULT -> case quotRemInt# wild2_a2QQ 62# of { (# ipv_a2QT, ipv1_a2QU #) -> case indexCharOffAddr# chars62_r30r ipv1_a2QU of wild4_X4 { __DEFAULT -> case <# wild2_a2QQ 62# of { __DEFAULT -> Bug.$wgo ipv_a2QT (GHC.Types.: @ Char (GHC.Types.C# wild4_X4) w_s2WR); 1# -> case indexCharOffAddr# chars62_r30r wild2_a2QQ of wild5_X1G { __DEFAULT -> (# GHC.Types.C# wild5_X1G, w_s2WR #) } } } }; -9223372036854775808# -> case lvl_r30s of { C# v1_B2 -> (# GHC.Types.C# v1_B2, w_s2WR #) } } } } end Rec } Bug.f_go :: Int -> [Char] -> [Char] Bug.f_go = \ (w_s2WQ :: Int) (w1_s2WR :: [Char]) -> case w_s2WQ of { I# ww1_s2WU -> case Bug.$wgo ww1_s2WU w1_s2WR of { (# ww3_s2Xa, ww4_s2Xb #) -> GHC.Types.: @ Char ww3_s2Xa ww4_s2Xb } } f :: Int -> String f = \ (n__aXG :: Int) -> case n__aXG of { I# ww1_s2WU -> case Bug.$wgo ww1_s2WU (GHC.Types.[] @ Char) of { (# ww3_s2Xa, ww4_s2Xb #) -> GHC.Types.: @ Char ww3_s2Xa ww4_s2Xb } } -- Core for g Rec { Bug.$wgo1 :: Int# -> [Char] -> (# Char, [Char] #) Bug.$wgo1 = \ (ww_s2X4 :: Int#) (w_s2X1 :: [Char]) -> case GHC.Real.even3 of { I# y_a2QI -> case y_a2QI of { __DEFAULT -> case quotRemInt# ww_s2X4 62# of { (# ipv_a2QN, ipv1_a2QO #) -> case indexCharOffAddr# chars62_r30r ipv1_a2QO of wild2_X4 { __DEFAULT -> case <# ww_s2X4 62# of { __DEFAULT -> Bug.$wgo1 ipv_a2QN (GHC.Types.: @ Char (GHC.Types.C# wild2_X4) w_s2X1); 1# -> case indexCharOffAddr# chars62_r30r ww_s2X4 of wild3_XY { __DEFAULT -> (# GHC.Types.C# wild3_XY, w_s2X1 #) } } } }; 62# -> case ww_s2X4 of wild2_a2QQ { __DEFAULT -> case quotRemInt# wild2_a2QQ 62# of { (# ipv_a2QT, ipv1_a2QU #) -> case indexCharOffAddr# chars62_r30r ipv1_a2QU of wild4_X4 { __DEFAULT -> case <# wild2_a2QQ 62# of { __DEFAULT -> Bug.$wgo1 ipv_a2QT (GHC.Types.: @ Char (GHC.Types.C# wild4_X4) w_s2X1); 1# -> case indexCharOffAddr# chars62_r30r wild2_a2QQ of wild5_XY { __DEFAULT -> (# GHC.Types.C# wild5_XY, w_s2X1 #) } } } }; -9223372036854775808# -> case GHC.Real.overflowError of wild4_00 { } } } } end Rec } Bug.g_go :: Int -> [Char] -> [Char] Bug.g_go = \ (w_s2X0 :: Int) (w1_s2X1 :: [Char]) -> case w_s2X0 of { I# ww1_s2X4 -> case Bug.$wgo1 ww1_s2X4 w1_s2X1 of { (# ww3_s2Xd, ww4_s2Xe #) -> GHC.Types.: @ Char ww3_s2Xd ww4_s2Xe } } g :: Int -> String g = \ (n__a29X :: Int) -> case n__a29X of { I# ww1_s2X4 -> case Bug.$wgo1 ww1_s2X4 (GHC.Types.[] @ Char) of { (# ww3_s2Xd, ww4_s2Xe #) -> GHC.Types.: @ Char ww3_s2Xd ww4_s2Xe } } }}} Of particular interest is: {{{#!hs -- chararacter array, used by both chars62_r30r :: Addr# chars62_r30r = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"# lvl_r30s :: Char lvl_r30s = case indexCharOffAddr# chars62_r30r -9223372036854775808# of v_B2 { __DEFAULT -> GHC.Types.C# v_B2 } }}} which is only used in the Core for `f`, not `g`! We're trying to access index `minBound :: Int` of that array of chars. While this is only used when we pass `minBound` to our function, it is still wrong I think. Moreover, as [https://github.com/snowleopard/hadrian/issues/861 hadrian issue 861] showed, this can lead to... linker errors! Which got fixed by changing the implementation of `iToBase62` in Unique.hs from `f` to `g` :-) Note that when I build the same commit with the make build system, then GHC generates Core close to `g`'s above for _both functions_. I tried describing some of the transformations that occur in [https://github.com/snowleopard/hadrian/issues/641#issuecomment-415881512 this comment] on hadrian's issue tracker. The gist of it is that the lack of strictness in `q` leads GHC to not spotting it early and when we inline `quotRem`/`quotRemInt` and start floating things in/out and distributing `case ... of` branches around, we end up with a dedicated branch in the inner loop for `minBound` which actually makes use of the result of `indexAddrOffAddr#`, as you can see here: {{{#!hs -9223372036854775808# -> -- lvl_r30s is our bad value case lvl_r30s of { C# v1_B2 -> (# GHC.Types.C# v1_B2, w_s2WR #) } }}} whereas this is what this branch looks like for `g`: {{{#!hs -9223372036854775808# -> case GHC.Real.overflowError of wild4_00 { } }}} The `overflowError` is still there and GHC therefore realised that there's no point in computing anything since we always raise an overflow error in that branch. This `overflowError` just disappears in `f`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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: | -------------------------------------+------------------------------------- Changes (by alpmestan): * owner: (none) => alpmestan * milestone: => 8.6.1 Comment: I'm going to try and characterise where both builds differ, using `-dverbose-core2core`. The best theory at this point is that libraries are built with different enough options that this affects the optimisation pipeline on this example. This won't be the end of the story though, as we simply ''never'' want to end up with the Core for `f` mentionned above. But at that point we will also have a lot more information about how the Core evolves. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call
-------------------------------------+-------------------------------------
Reporter: alpmestan | Owner: alpmestan
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
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):
This is all very mysterious. What I get from HEAD (for `f`) is this:
{{{
Rec {
-- RHS size: {terms: 33, types: 19, coercions: 0, joins: 0/0}
Bug.$wgo [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker]
:: Int# -> [Char] -> (# Char, [Char] #)
[GblId, Arity=2, Caf=NoCafRefs, Str=m2,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
Tmpl= \ (n__aXh [Occ=Once] :: Int) ->
Bug.f_go n__aXh (GHC.Types.[] @ Char)}]
f = \ (n__aXh :: Int) ->
case n__aXh of { I# ww1_s2QZ ->
case Bug.$wgo ww1_s2QZ (GHC.Types.[] @ Char) of
{ (# ww3_s2R5, ww4_s2R6 #) ->
GHC.Types.: @ Char ww3_s2R5 ww4_s2R6
}
}
}}}
which looks very plausible.
You are getting something quite different with your Hadrian build. Can
you give precise repro instructions? (Including `build.mk` etc.)
I'm very puzzled about this mysterious case of `GHC.Real.even3`. Where on
earth does that come from? And if it is equal to `-1` why doesn't the
case get eliminated?
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 alpmestan): Here are the instructions: {{{#!sh # will likely also work with HEAD, as this commit isn't old $ git checkout c523525b0e434d848f6e47ea3f9a37485965fa79 $ curl -O https://phabricator- files.haskell.org/file/data/mgom5atdizvefddx4ax2/PHID-FILE- tbprgcge7cciumnotpbj/D5106.diff $ git apply D5106.diff # build ghc $ hadrian/build.sh -c -j4 --flavour=quick # compile test program, assuming it's in ./bug.hs $ _build/stage1/bin/ghc -O -fPIC -dynamic -ddump-simpl bug.hs -o bug.o }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 alpmestan): Hm, actually you're on Windows right? In which case you'll want to use `hadrian/build.bat` I think. [https://github.com/snowleopard/hadrian/blob/master/doc/windows.md This page] documents pre-requisites. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 alpmestan): ed789516e201e4fad771e5588da47a62e53b42b8 has been merged, it shows how I got GHC to generate correct code for `iToBase62`'s inner loop, fixing this particular instance of the problem in hadrian's case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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): A small repro case for the original bug would be super-helpful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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): I completed comment:3, but then fell over immediately: {{{ simonpj@cam-05-unx:~/tmp$ ~/code/HEAD-3/_build/stage0/bin/ghc -O -fPIC -dynamic -ddump-simpl T15570.hs [1 of 1] Compiling Bug ( T15570.hs, T15570.o ) T15570.hs:3:8: error: Bad interface file: /usr/local/lib/ghc-8.2.2/base-4.10.1.0/Prelude.dyn_hi mismatched interface file versions (wanted "80720180825", got "8022") | 3 | module Bug where | ^^^ T15570.hs:6:1: error: Bad interface file: /usr/local/lib/ghc-8.2.2/ghc- prim-0.5.1.1/GHC/Types.dyn_hi mismatched interface file versions (wanted "80720180825", got "8022") | 6 | import GHC.Types | ^^^^^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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): New fact: the stage1 compiler works, however. But the stage0 version does not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call
-------------------------------------+-------------------------------------
Reporter: alpmestan | Owner: alpmestan
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
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):
No I can repro, I can return to the OP.
I'm deeply puzzled about the case-match on `GHC.Real.even3`. But leaving
that aside,
I'm not so sure that the Core shown in the Description is wrong. After
all, suppose
we made the call
{{{
f -9223372036854775808
}}}
Then we'd get into the `n<62` branch, so we'd call `chooseChar62` of that
ridiculous number.
So semantically, while the code is very strange, it's not actually wrong.
'''So why do you get a link error'''? I think that is a bug all by
itself.
If I write
{{{
x = C# (indexCharOffAddr# "foo"# -9223372036854775808#)
}}}
that might seg-fault at runtime, but it should not cause a link error.
-------------------
How can stupid code like this arise? Consider
{{{
h :: Int# -> Int#
h x = let !t = case x of
-1000# -> 4#
_ -> x
in
t +# indexIntOffAddr# "foo"# x)
}}}
Notice that `h` unconditionally indexes the string with `x` (just like `f`
does in the
Description); presumably the caller is going to guaranteed that `x` is in
bounds.
That turns into
{{{
h x = case (case x of { -1000 -> 4#; _ -> x }) of
t -> t +# indexIntOffAddr# "foo"# x
}}}
Now case-of-case produces
{{{
h x = case x of
-1000 -> 4# +# indexIntOffAddr# "foo#" x
_ -> x +# indexIntOffAddr# "foo#" x
}}}
But in the top branch we know that `x` is `-1000`, so we finally get
{{{
h x = case x of
-1000 -> 4# +# indexIntOffAddr# "foo#" -1000
_ -> x +# indexIntOffAddr# "foo#" x
}}}
This is, in essence, what is happening in the Description. And it should
jolly well
be fine.
Of course, if the caller never calls the function with `-1000` as the
argument,
the top branch will never be executed.
------------------
So my claim so far is: the code is correct; and it's a bug that we get a
linker error.
However the code, while correct, is TERRIBLE. For this function (similar
to Description, slightly simplified)
{{{
go :: Int -> [Char] -> [Char]
go n cs | n < 62
= let !c = chooseChar62 n in c : cs
| otherwise
= go q cs
where
!(q, _) = quotRem n 62
}}}
HEAD produces the very civilised result
{{{
Bug.$wgo [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker]
:: Int# -> [Char] -> (# Char, [Char] #)
[GblId, Arity=2, Caf=NoCafRefs, Str=

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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): OK, with some help from Andrey I added to `hadrian/src/UserSettings.hs` {{{ verboseCommand :: Predicate verboseCommand = input "//*.hs" }}} Now if I touch `GHC/Real.hs` I get its command line, which is super- helpful; so I can compile with changing flags. Turns out that the reason for the strange `GHC.Real.even3` is that we have {{{ GHC.Real.even4 :: Int GHC.Real.even4 = GHC.Types.I# 1# -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0} GHC.Real.even3 :: Int GHC.Real.even3 = negate @ Int GHC.Num.$fNumInt GHC.Real.even4 }}} Wny aren't we negating that constant? '''Turns out that it's because we aren't optimising `GHC.Num`'''!!! It's not surprising that we get terrible code. Here are the command lines printed by Hadrian for `GHC.Num` and `GHC.Real` {{{ -- GHC.Real. Notice that it finishes with -O _build/stage0/bin/ghc -Wall -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -hide-all-packages -no-user-package-db '-package-db _build/stage1/lib/package.conf.d' '-this-unit-id base-4.12.0.0' '-package- id ghc-prim-0.5.3' '-package-id integer-gmp-1.0.2.0' '-package-id rts-1.0' -i -i_build/stage1/libraries/base/build -i_build/stage1/libraries/base/build/autogen -ilibraries/base/. -Iincludes -I_build/generated -I_build/stage1/libraries/base/build -I_build/stage1/libraries/base/build/include -Ilibraries/base/include -I/home/simonpj/code/HEAD-3/_build/stage1/lib/x86_64-linux- ghc-8.7.20180825/integer-gmp-1.0.2.0/include -I/home/simonpj/code/HEAD-3/_build/stage1/lib/x86_64-linux- ghc-8.7.20180825/rts-1.0/include -I_build/generated -optc- I_build/generated -optP-include -optP_build/stage1/libraries/base/build/autogen/cabal_macros.h -optc-fno- stack-protector -optP-DOPTIMISE_INTEGER_GCD_LCM -odir _build/stage1/libraries/base/build -hidir _build/stage1/libraries/base/build -stubdir _build/stage1/libraries/base/build -Wnoncanonical-monad-instances -optc- Werror=unused-but-set-variable -optc-Wno-error=inline -c libraries/base/GHC/Real.hs -o _build/stage1/libraries/base/build/GHC/Real.dyn_o -O0 -H64m -this-unit-id base -Wcompat -Wnoncanonical-monad-instances -XHaskell2010 -ghcversion- file=/home/simonpj/code/HEAD-3/_build/generated/ghcversion.h -O -Wno- deprecated-flags -Wno-trustworthy-safe -- GHC.Num. The -O is there but it's overridden with -O0 _build/stage0/bin/ghc -Wall -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -hide-all-packages -no-user-package-db '-package-db _build/stage1/lib/package.conf.d' '-this-unit-id base-4.12.0.0' '-package- id ghc-prim-0.5.3' '-package-id integer-gmp-1.0.2.0' '-package-id rts-1.0' -i -i_build/stage1/libraries/base/build -i_build/stage1/libraries/base/build/autogen -ilibraries/base/. -Iincludes -I_build/generated -I_build/stage1/libraries/base/build -I_build/stage1/libraries/base/build/include -Ilibraries/base/include -I/home/simonpj/code/HEAD-3/_build/stage1/lib/x86_64-linux- ghc-8.7.20180825/integer-gmp-1.0.2.0/include -I/home/simonpj/code/HEAD-3/_build/stage1/lib/x86_64-linux- ghc-8.7.20180825/rts-1.0/include -I_build/generated -optc- I_build/generated -optP-include -optP_build/stage1/libraries/base/build/autogen/cabal_macros.h -optc-fno- stack-protector -optP-DOPTIMISE_INTEGER_GCD_LCM -odir _build/stage1/libraries/base/build -hidir _build/stage1/libraries/base/build -stubdir _build/stage1/libraries/base/build -Wnoncanonical-monad-instances -optc- Werror=unused-but-set-variable -optc-Wno-error=inline -c libraries/base/GHC/Num.hs -o _build/stage1/libraries/base/build/GHC/Num.dyn_o -O0 -H64m -this-unit-id base -Wcompat -Wnoncanonical-monad-instances -XHaskell2010 -ghcversion- file=/home/simonpj/code/HEAD-3/_build/generated/ghcversion.h -O -O0 -fno- ignore-interface-pragmas -Wno-deprecated-flags -Wno-trustworthy-safe }}} Blimey. With `make` we'd be stuck: who is adding that `-O0`? But with Hadrian and it's provenance tracking, it should be easy. But I have no idea where to start: Andrey, Alp, over to you. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15286 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: snowleopard (added) * related: => #15286 Comment: We explicitly ask for `Num.hs` to be built with `-O0`, [https://github.com/snowleopard/hadrian/blob/a820566c16e1945b02632e68bd54cc35... here]. This is due to #15286. We quite likely want to solve the root of the issue there instead of just building some modules here and there without optimisations. Even more so now that we're seeing that building some important modules with `-O0` can make all sorts of things go wrong. Thanks a lot for the investigation! I'm glad you got hadrian to work properly. #15286 is now standing in the way of really addressing the present ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15286 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
#15286 is now standing in the way of really addressing the present ticket.
Well #15286 ''must'' be solved; compiling `Num` with `-00` is not acceptable. But there's another bug: there should not be a linker error with the code above. Let's fix that too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15286 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): @[comment:11 alpmestan]: the [https://github.com/snowleopard/hadrian/blob/a820566c16e1945b02632e68bd54cc35... workaround in Hadrian] for #15286 is a bit wrong: you should only have to pass `-fno-omit-interface-pragmas` and `-fno-ignore-interface-pragmas`, not `-O0`. Last time I checked (cf Phab:D4880), it was enough to fix the "quickest" build. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15286 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): But it's a workaround NOT a fix. Let's fix it properly too please! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15286 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Yes, let's! I'm wrapping up some other work for hadrian right now, I will pick this up right after and look into removing those `-O0`s while still avoiding the problem from #15286. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15570: Core transformations generate bad indexCharOffAddr# call -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: alpmestan Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15286 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): I wrote https://ghc.haskell.org/trac/ghc/ticket/15286#comment:7 to report that I have a PR up to get rid of those `-O0`s, implementing hsyl20's recommendation, and that it works! (It even fixes some failing tests.) I'm about to turn off my computer, but I guess I can try building our little example from the ticket description tomorrow, using GHC&libs built by hadrian without those `-O0`s, reporting back on the generated Core here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15570#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC