[Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef] wrk: correctly cast to the pointer

doyougnu (@doyougnu) gitlab at gitlab.haskell.org
Wed Sep 11 17:45:28 UTC 2024



doyougnu pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
6b76535c by doyougnu at 2024-09-11T13:39:01-04:00
wrk: correctly cast to the pointer

- - - - -


5 changed files:

- rts/Linker.c
- rts/linker/elf_got.c
- + testsuite/tests/rts/T25240/FFI.hs
- + testsuite/tests/rts/T25240/TH.hs
- + testsuite/tests/rts/T25240/all.T


Changes:

=====================================
rts/Linker.c
=====================================
@@ -954,7 +954,7 @@ SymbolAddr* lookupSymbol( SymbolName* lbl )
         // if -link-unknown-symbols is passed into the RTS we allow the linker
         // to optimistically continue
         if (RtsFlags.MiscFlags.linkUnknownSymbols){
-            r = 0xDEADBEEF;
+            r = (void*) 0xDEADBEEF;
         }
 
     }


=====================================
rts/linker/elf_got.c
=====================================
@@ -104,7 +104,7 @@ fillGot(ObjectCode * oc) {
                                 // RTS we allow the linker to optimistically
                                 // continue
                                 if (RtsFlags.MiscFlags.linkUnknownSymbols) {
-                                    symbol->addr = 0xDEADBEEF;
+                                    symbol->addr = (void*) 0xDEADBEEF;
                                 } else {
                                 return EXIT_FAILURE;
                                 }


=====================================
testsuite/tests/rts/T25240/FFI.hs
=====================================
@@ -0,0 +1,24 @@
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+module T25240.FFI
+  ( D(..), D2(..), tabulate
+  ) where
+
+import GHC.Exts ( Double#, Double(D#) )
+import Language.Haskell.TH ( CodeQ )
+
+data D = D Double
+data D2 = D2 { x, y :: D }
+
+tabulate :: ( Word -> CodeQ D ) -> CodeQ ( D2 )
+tabulate f = [|| D2 $$( f 1 ) $$( f 2 ) ||]
+
+
+-- Now an unrelated "Num D" instance.
+instance Num D where
+  ( D ( D# x ) ) * ( D ( D# y ) ) = D ( D# ( func x y ) )
+foreign import prim "prim_func"
+  func :: Double# -> Double# -> Double#


=====================================
testsuite/tests/rts/T25240/TH.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module TH where
+import FFI
+
+th_bug :: D2
+th_bug = $$( tabulate $ \ _ -> [|| D 0 ||] )


=====================================
testsuite/tests/rts/T25240/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T25240',
+    [req_rts_linker, extra_files(['FFI.hs', 'TH.hs'])], compile, ['-flink-unknown-symbols'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6b76535c2067bdecec26830bc8077342dbd7776a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6b76535c2067bdecec26830bc8077342dbd7776a
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/20240911/05ba9bf4/attachment-0001.html>


More information about the ghc-commits mailing list