From 044a6e08c2aee23ef18c60a036e01d3b77168830 Mon Sep 17 00:00:00 2001
From: sheaf <sam.derbyshire@gmail.com>
Date: Thu, 20 Mar 2025 19:21:01 +0100
Subject: [PATCH] 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
---
 compiler/GHC/CmmToLlvm/Base.hs                |  2 +-
 testsuite/tests/llvm/should_run/T25770.hs     | 15 +++++++++++++++
 testsuite/tests/llvm/should_run/T25770.stdout |  1 +
 testsuite/tests/llvm/should_run/all.T         |  1 +
 4 files changed, 18 insertions(+), 1 deletion(-)
 create mode 100644 testsuite/tests/llvm/should_run/T25770.hs
 create mode 100644 testsuite/tests/llvm/should_run/T25770.stdout

diff --git a/compiler/GHC/CmmToLlvm/Base.hs b/compiler/GHC/CmmToLlvm/Base.hs
index b56d4ed9be5..4f9d854add4 100644
--- a/compiler/GHC/CmmToLlvm/Base.hs
+++ b/compiler/GHC/CmmToLlvm/Base.hs
@@ -237,7 +237,7 @@ padLiveArgs platform live =
                text ") both alive AND mapped to the same real register: " <> ppr real <>
                text ". This isn't currently supported by the LLVM backend."
          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
 
     fpr_ctor :: GlobalRegUse -> Int -> GlobalRegUse
diff --git a/testsuite/tests/llvm/should_run/T25770.hs b/testsuite/tests/llvm/should_run/T25770.hs
new file mode 100644
index 00000000000..5e1b1c72e9e
--- /dev/null
+++ b/testsuite/tests/llvm/should_run/T25770.hs
@@ -0,0 +1,15 @@
+{-# 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')
diff --git a/testsuite/tests/llvm/should_run/T25770.stdout b/testsuite/tests/llvm/should_run/T25770.stdout
new file mode 100644
index 00000000000..e0ea36feef6
--- /dev/null
+++ b/testsuite/tests/llvm/should_run/T25770.stdout
@@ -0,0 +1 @@
+6.0
diff --git a/testsuite/tests/llvm/should_run/all.T b/testsuite/tests/llvm/should_run/all.T
index 94c19fc6050..e6c6d84e2e3 100644
--- a/testsuite/tests/llvm/should_run/all.T
+++ b/testsuite/tests/llvm/should_run/all.T
@@ -12,6 +12,7 @@ setTestOpts(f)
 def ignore_llvm_and_vortex( 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('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'])
-- 
GitLab