Skip to content
Snippets Groups Projects
Commit 044a6e08 authored by sheaf's avatar sheaf Committed by Marge Bot
Browse files

LLVM: fix typo in padLiveArgs

This commit fixes a serious bug in the padLiveArgs function, which
was incorrectly computing too many padding registers. This caused
segfaults, e.g. in the UnboxedTuples test.

Fixes #25770
Fixes #25773
parent 2e4e15ed
No related branches found
No related tags found
No related merge requests found
...@@ -237,7 +237,7 @@ padLiveArgs platform live = ...@@ -237,7 +237,7 @@ padLiveArgs platform live =
text ") both alive AND mapped to the same real register: " <> ppr real <> text ") both alive AND mapped to the same real register: " <> ppr real <>
text ". This isn't currently supported by the LLVM backend." text ". This isn't currently supported by the LLVM backend."
go (cu@(GlobalRegUse c _):cs) f go (cu@(GlobalRegUse c _):cs) f
| fpr_num c == f = go cs f -- already covered by a real register | fpr_num c == f = go cs (f+1) -- already covered by a real register
| otherwise = ctor f : go (cu:cs) (f + 1) -- add padding register | otherwise = ctor f : go (cu:cs) (f + 1) -- add padding register
fpr_ctor :: GlobalRegUse -> Int -> GlobalRegUse fpr_ctor :: GlobalRegUse -> Int -> GlobalRegUse
......
{-# LANGUAGE UnboxedTuples, MagicHash #-}
module Main where
import GHC.Exts
tuple6 :: () -> (# Float#, Double#, Float#, Double#, Float#, Double# #)
tuple6 _ = (# 1.0#, 2.0##, 3.0#, 4.0##, 5.0#, 6.0## #)
{-# NOINLINE tuple6 #-}
main :: IO ()
main =
case tuple6 () of
(# _, _, _, _, _, d' #) ->
print (D# d')
6.0
...@@ -12,6 +12,7 @@ setTestOpts(f) ...@@ -12,6 +12,7 @@ setTestOpts(f)
def ignore_llvm_and_vortex( msg ): def ignore_llvm_and_vortex( msg ):
return re.sub(r".* is not a recognized processor for this target.*\n",r"",msg) return re.sub(r".* is not a recognized processor for this target.*\n",r"",msg)
test('T25770', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, [''])
test('T22487', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, ['']) test('T22487', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, [''])
test('T22033', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, ['']) test('T22033', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, [''])
test('T25730', [req_c, unless(arch('x86_64'), skip), normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, ['T25730C.c']) test('T25730', [req_c, unless(arch('x86_64'), skip), normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, ['T25730C.c'])
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment