[Git][ghc/ghc][master] LLVM: When emitting a vector literal with ppTypeLit, include the type information
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Sun Dec 15 23:35:54 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00
LLVM: When emitting a vector literal with ppTypeLit, include the type information
Fixes #25561
- - - - -
4 changed files:
- compiler/GHC/Llvm/Ppr.hs
- + testsuite/tests/simd/should_run/T25561.hs
- + testsuite/tests/simd/should_run/T25561.stdout
- testsuite/tests/simd/should_run/all.T
Changes:
=====================================
compiler/GHC/Llvm/Ppr.hs
=====================================
@@ -669,9 +669,7 @@ ppTypeLit = ppTypeLit' []
{-# SPECIALIZE ppTypeLit :: LlvmCgConfig -> LlvmLit -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
ppTypeLit' :: IsLine doc => [LlvmParamAttr] -> LlvmCgConfig -> LlvmLit -> doc
-ppTypeLit' attrs opts l = case l of
- LMVectorLit {} -> ppLit opts l
- _ -> ppLlvmType (getLitType l) <+> ppSpaceJoin ppLlvmParamAttr attrs <+> ppLit opts l
+ppTypeLit' attrs opts l = ppLlvmType (getLitType l) <+> ppSpaceJoin ppLlvmParamAttr attrs <+> ppLit opts l
{-# SPECIALIZE ppTypeLit' :: [LlvmParamAttr] -> LlvmCgConfig -> LlvmLit -> SDoc #-}
{-# SPECIALIZE ppTypeLit' :: [LlvmParamAttr] -> LlvmCgConfig -> LlvmLit -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
=====================================
testsuite/tests/simd/should_run/T25561.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+import Data.Array.Base
+import Data.Array.IO.Internals
+import GHC.Exts
+import GHC.IO
+
+main :: IO ()
+main = do
+ ma@(IOUArray (STUArray l _ _ mba)) <- newListArray (0, 10) ([0..10] :: [Float])
+ IO $ \s -> (# writeFloatArrayAsFloatX4# mba 1# (broadcastFloatX4# 3.0#) s, () #)
+ print =<< getElems ma
=====================================
testsuite/tests/simd/should_run/T25561.stdout
=====================================
@@ -0,0 +1 @@
+[0.0,3.0,3.0,3.0,3.0,5.0,6.0,7.0,8.0,9.0,10.0]
=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -66,6 +66,7 @@ test('simd_insert_array', [], compile_and_run, [''])
test('T22187', [],compile,[''])
test('T22187_run', [],compile_and_run,[''])
test('T25062_V16', [], compile_and_run, [''])
+test('T25561', [], compile_and_run, [''])
# Even if the CPU we run on doesn't support *executing* those tests we should try to
# compile them.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2d3a0a70def8a2044f2954b29df1a186b3f08dcc
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2d3a0a70def8a2044f2954b29df1a186b3f08dcc
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241215/3675f364/attachment-0001.html>
More information about the ghc-commits
mailing list