[Git][ghc/ghc][master] RTS: expose closure_sizeW_ (#25252)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Sep 17 15:03:56 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)
C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:
ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_
Fix #25252
Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>
- - - - -
5 changed files:
- rts/RtsSymbols.c
- + testsuite/tests/th/T25252.hs
- + testsuite/tests/th/T25252B.hs
- + testsuite/tests/th/T25252_c.c
- testsuite/tests/th/all.T
Changes:
=====================================
rts/RtsSymbols.c
=====================================
@@ -954,6 +954,7 @@ extern char **environ;
SymI_HasDataProto(stg_castDoubleToWord64zh) \
SymI_HasDataProto(stg_castWord32ToFloatzh) \
SymI_HasDataProto(stg_castFloatToWord32zh) \
+ SymI_HasProto(closure_sizeW_) \
RTS_USER_SIGNALS_SYMBOLS \
RTS_INTCHAR_SYMBOLS
=====================================
testsuite/tests/th/T25252.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module Main where
+
+import Data.Word
+import Foreign.StablePtr
+import Control.Monad.IO.Class
+import T25252B
+
+main :: IO ()
+main = pure $(liftIO foo >> [| () |])
=====================================
testsuite/tests/th/T25252B.hs
=====================================
@@ -0,0 +1,15 @@
+module T25252B where
+
+import Data.Word
+import Foreign.StablePtr
+
+foreign import ccall "hs_custom_closureSize" closureSize :: StablePtr a -> Word64
+
+foo :: IO ()
+foo = do
+ let
+ x :: [Int]
+ x = cycle [10,20] -- segfaults without "cycle"...
+ sp <- newStablePtr x
+ print (closureSize sp /= 0)
+
=====================================
testsuite/tests/th/T25252_c.c
=====================================
@@ -0,0 +1,8 @@
+#include <Rts.h>
+
+ uint64_t hs_custom_closureSize(StgStablePtr const sp) {
+ StgPtr const root = deRefStablePtr(sp);
+ ASSERT(LOOKS_LIKE_CLOSURE_PTR(root));
+
+ return closure_sizeW((StgClosure*)root);
+}
=====================================
testsuite/tests/th/all.T
=====================================
@@ -624,3 +624,9 @@ test('T24572c', normal, compile_fail, [''])
test('T24572d', normal, compile, [''])
test('T25209', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('TH_MultilineStrings', normal, compile_and_run, [''])
+test('T25252',
+ [extra_files(['T25252B.hs', 'T25252_c.c']),
+ when(arch('i386'), expect_broken_for(25260,['ext-interp'])),
+ req_th,
+ req_c],
+ compile_and_run, ['-fPIC T25252_c.c'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d3b19851626411eeea35954ff745dfd7f663ac5c
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d3b19851626411eeea35954ff745dfd7f663ac5c
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/20240917/5977bf9f/attachment-0001.html>
More information about the ghc-commits
mailing list