LLVM type error when using vector types with FFI
Summary
When a foreign function has a different vector types for parameter and return types, the LLVM IR emitted by GHC contains type errors.
Steps to reproduce
Consider the following code:
-- Main.hs
{-# LANGUAGE MagicHash, UnboxedTuples, ExtendedLiterals #-}
import GHC.Exts
import GHC.Int
import MyLib
main :: IO ()
main = do
let a = broadcastInt32X4# 100#Int32
b = broadcastInt32X4# 200#Int32
c = packsi32 a b
(# x0, x1, x2, x3, x4, x5, x6, x7 #) = unpackInt16X8# c
print (I16# x0, I16# x1, I16# x2, I16# x3, I16# x4, I16# x5, I16# x6, I16# x7)
-- MyLib.hs
{-# LANGUAGE MagicHash, UnliftedFFITypes #-}
module MyLib where
import GHC.Exts
foreign import ccall unsafe
packsi32 :: Int32X4# -> Int32X4# -> Int16X8#
// packs.c
#include <emmintrin.h>
#include <stdio.h>
__m128i packsi32(__m128i a, __m128i b)
{
return _mm_packs_epi32(a, b);
}
$ ghc -fforce-recomp -fllvm Main.hs packs.c
[1 of 3] Compiling MyLib ( MyLib.hs, MyLib.o )
opt-15: /tmp/ghc242850_tmp_0/ghc_tmp_7_0.ll:103:20: error: '%XMM1_Arg' defined with type '<4 x i32>' but expected '<8 x i16>'
store <8 x i16> %XMM1_Arg, <8 x i16>* %XMM1_Var
^
<no location info>: error:
`opt-15' failed in phase `LLVM Optimiser'. (Exit code: 1)
Expected behavior
The program should compile and output:
$ ./Main
(100,100,100,100,200,200,200,200)
Environment
- GHC version used: 9.12.1, 9.13.20250206 (5622a14a)
- Operating System: Ubuntu 22.04
- System Architecture: x86_64