[GHC] #8131: T7571 with WAY=llvm fails, but not WAY=optllvm
GHC
ghc-devs at haskell.org
Tue Sep 10 04:43:24 CEST 2013
#8131: T7571 with WAY=llvm fails, but not WAY=optllvm
----------------------------------------------+----------------------------
Reporter: thoughtpolice | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: llvm/should_compile/T8131 | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
----------------------------------------------+----------------------------
Comment (by rwbarton):
Can also trigger this from Haskell.
{{{
{-# LANGUAGE MagicHash, UnboxedTuples #-}
import GHC.Prim
import GHC.IO
main = IO $ \s ->
let (# s1, p0 #) = newByteArray# 10# s
(# s2, p #) = unsafeFreezeByteArray# p0 s1
(# s3, q #) = newByteArray# 10# s2
in (# copyByteArray# p 0# q 0# 10# s, () #)
}}}
{{{
rwbarton at adjunction:/tmp$ ~/ghc-head/bin/ghc m -fllvm -fforce-recomp
[1 of 1] Compiling Main ( m.hs, m.o )
WARNING: Non constant alignment value given for memcpy! Please report to
GHC developers
Linking m ...
}}}
The `llvm.memcpy` intrinsic requires that its `align` argument be a
literal. With `-fllvm` but not `-O`, somewhere along the way the alignment
argument to the `MO_Memcpy` gets stored in a Cmm register and the register
gets used for the `llvm.memcpy` call, which isn't good enough. With
(`-fllvm` and) `-O`, the store to a register gets eliminated and the
`llvm.memcpy` call does use a literal alignment argument. That's why T7571
and the Haskell program above work with `-O` but not without. (It doesn't
have anything to do with the `if (1)` in T7571.) Fragile.
Your T8131 is expected to not compile, I think, because there the
alignment argument really is nonconstant.
Given that the alignment for `MO_Memcpy` is only used in the LLVM backend,
and there it is required to be constant, I would be inclined to move it
from a MachOp argument to a parameter of the MachOp constructor, like
{{{
data CallishMachOp = ...
| MO_Memcpy Alignment -- or would another type be more appropriate?
}}}
I have a half-finished patch that implements this. Besides eliminating the
requirement of ensuring the alignment argument is a literal, it also
removes some special cases in the other backends that have to throw away
the alignment argument before generating a `memcpy` function call.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8131#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list