[GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0#
GHC
ghc-devs at haskell.org
Thu Jul 23 19:00:35 UTC 2015
#10676: silly assembly for comparing the result of comparisons that return Int#
against 0#
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
(CodeGen) |
Keywords: | Operating System: Unknown/Multiple
Architecture: x86_64 | Type of failure: Runtime
(amd64) | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
Consider the module
{{{
{-# LANGUAGE MagicHash #-}
module Min where
import GHC.Exts
fgood :: Int# -> Int# -> Int
fgood x# y# = case isTrue# (x# <# y#) of
False -> I# y#
True -> I# x#
fbad :: Int# -> Int# -> Int
fbad x# y# = case x# <# y# of
0# -> I# y#
_ -> I# x#
}}}
The code for `fgood` looks fine:
{{{
0000000000000130 <Min_fgood_info>:
130: 49 83 c4 10 add $0x10,%r12
134: 4d 3b a5 58 03 00 00 cmp 0x358(%r13),%r12
13b: 77 1a ja 157 <Min_fgood_info+0x27>
13d: 49 39 f6 cmp %rsi,%r14
140: 7c 29 jl 16b <Min_fgood_info+0x3b>
142: 49 c7 44 24 f8 00 00 movq $0x0,-0x8(%r12)
149: 00 00
147: R_X86_64_32S
ghczmprim_GHCziTypes_Izh_con_info
14b: 49 89 34 24 mov %rsi,(%r12)
14f: 49 8d 5c 24 f9 lea -0x7(%r12),%rbx
154: ff 65 00 jmpq *0x0(%rbp)
157: 49 c7 85 88 03 00 00 movq $0x10,0x388(%r13)
15e: 10 00 00 00
162: bb 00 00 00 00 mov $0x0,%ebx
163: R_X86_64_32 Min_fgood_closure
167: 41 ff 65 f8 jmpq *-0x8(%r13)
16b: 49 c7 44 24 f8 00 00 movq $0x0,-0x8(%r12)
172: 00 00
170: R_X86_64_32S
ghczmprim_GHCziTypes_Izh_con_info
174: 4d 89 34 24 mov %r14,(%r12)
178: 49 8d 5c 24 f9 lea -0x7(%r12),%rbx
17d: ff 65 00 jmpq *0x0(%rbp)
}}}
But the code for `fbad` has several problems:
{{{
0000000000000018 <Min_fbad_info>:
18: 48 8d 45 f0 lea -0x10(%rbp),%rax
1c: 4c 39 f8 cmp %r15,%rax
1f: 72 3a jb 5b <Min_fbad_info+0x43>
21: 48 89 f0 mov %rsi,%rax
24: 4c 89 f3 mov %r14,%rbx
27: 49 39 f6 cmp %rsi,%r14
2a: 0f 9c c1 setl %cl
2d: 0f b6 c9 movzbl %cl,%ecx
30: 48 85 c9 test %rcx,%rcx
33: 75 51 jne 86 <c1Sm_info+0xe>
35: 49 83 c4 10 add $0x10,%r12
39: 4d 3b a5 58 03 00 00 cmp 0x358(%r13),%r12
40: 0f 87 aa 00 00 00 ja f0 <c1Su_info+0x10>
46: 49 c7 44 24 f8 00 00 movq $0x0,-0x8(%r12)
4d: 00 00
4b: R_X86_64_32S
ghczmprim_GHCziTypes_Izh_con_info
4f: 49 89 04 24 mov %rax,(%r12)
53: 49 8d 5c 24 f9 lea -0x7(%r12),%rbx
58: ff 65 00 jmpq *0x0(%rbp)
5b: bb 00 00 00 00 mov $0x0,%ebx
5c: R_X86_64_32 Min_fbad_closure
60: 41 ff 65 f8 jmpq *-0x8(%r13)
...
; c1Sm_info is the other case with its own heap check and GC entry code
; c1Su_info is another GC entry
; in total, another 160 bytes of code
}}}
For some reason, the heap checks were moved into the alternatives, which
was not a good decision in this case. But the silly thing here is the
`cmp/setl/movzbl/test/jne` sequence in `Min_fbad_info`, which should be
replaced by a `cmp/jl` as in `Min_fgood_info`.
Same behavior in 7.8 and HEAD.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10676>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list