[Git][ghc/ghc][master] FFI: don't ppr Id/Var symbols with debug info (#25255)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Wed Sep 18 11:57:23 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)
Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.
- - - - -
3 changed files:
- compiler/GHC/Types/Var.hs
- + testsuite/tests/ffi/should_compile/T25255.hs
- testsuite/tests/ffi/should_compile/all.T
Changes:
=====================================
compiler/GHC/Types/Var.hs
=====================================
@@ -343,9 +343,12 @@ arbitrary value which will (and must!) be ignored.
-}
instance Outputable Var where
- ppr var = sdocOption sdocSuppressVarKinds $ \supp_var_kinds ->
+ ppr var = docWithStyle ppr_code ppr_normal
+ where
+ -- don't display debug info with Code style (#25255)
+ ppr_code = ppr (varName var)
+ ppr_normal sty = sdocOption sdocSuppressVarKinds $ \supp_var_kinds ->
getPprDebug $ \debug ->
- getPprStyle $ \sty ->
let
ppr_var = case var of
(TyVar {})
=====================================
testsuite/tests/ffi/should_compile/T25255.hs
=====================================
@@ -0,0 +1,6 @@
+module T25255 where
+
+foreign export ccall foo :: Int -> Int
+
+foo :: Int -> Int
+foo x = x + 10
=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -42,3 +42,4 @@ test('T22043', normal, compile, [''])
test('T22774', unless(js_arch() or arch('wasm32'), expect_fail), compile, [''])
test('T24034', normal, compile, [''])
+test('T25255', normal, compile, ['-dppr-debug'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35eb4f428ab72b712ea78d6ef86b956e321c3bb2
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35eb4f428ab72b712ea78d6ef86b956e321c3bb2
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/20240918/8e2c56b2/attachment-0001.html>
More information about the ghc-commits
mailing list