[Git][ghc/ghc][wip/T17949] 4 commits: T17949 rename withEventlog/whenEventlog

Daneel S. Yaitskov gitlab at gitlab.haskell.org
Fri May 22 20:39:47 UTC 2020



Daneel S. Yaitskov pushed to branch wip/T17949 at Glasgow Haskell Compiler / GHC


Commits:
ca7fa6b1 by Daneel Yaitskov at 2020-05-22T13:29:59-07:00
T17949 rename withEventlog/whenEventlog

- - - - -
88c1d3cb by Daneel Yaitskov at 2020-05-22T13:30:58-07:00
T17949 inline whenEventlog

- - - - -
3730961d by Daneel Yaitskov at 2020-05-22T13:35:12-07:00
T17949 remove whenEventlog from traceIO

- - - - -
fca165f0 by Daneel Yaitskov at 2020-05-22T13:35:48-07:00
T17949 remove double whenEventlog

- - - - -


1 changed file:

- libraries/base/Debug/Trace.hs


Changes:

=====================================
libraries/base/Debug/Trace.hs
=====================================
@@ -77,12 +77,13 @@ import Data.List (null, partition)
 
 foreign import ccall "&eventlog_enabled" eventlog_enabled :: Ptr CBool
 
--- | The 'withEventlog' function evals argument action
+-- | The 'whenEventlog' function evals argument action
 -- if RTS eventlog (+RTS -l) is enabled.
 --
 -- @since 4.14.0.0
-withEventlog :: IO () -> IO ()
-withEventlog logAction = do
+{-# INLINE whenEventlog #-}
+whenEventlog :: IO () -> IO ()
+whenEventlog logAction = do
   ee <- peek eventlog_enabled
   if toBool ee
   then logAction
@@ -93,7 +94,7 @@ withEventlog logAction = do
 --
 -- @since 4.5.0.0
 traceIO :: String -> IO ()
-traceIO msg = withEventlog $ do
+traceIO msg =
     withCString "%s\n" $ \cfmt -> do
      -- NB: debugBelch can't deal with null bytes, so filter them
      -- out so we don't accidentally truncate the message.  See #9395
@@ -270,7 +271,7 @@ traceStack str expr = unsafePerformIO $ do
 -- @since 4.5.0.0
 traceEvent :: String -> a -> a
 traceEvent msg expr = unsafeDupablePerformIO $ do
-    withEventlog $ traceEventIO msg
+    traceEventIO msg
     return expr
 
 -- | The 'traceEventIO' function emits a message to the eventlog, if eventlog
@@ -282,7 +283,7 @@ traceEvent msg expr = unsafeDupablePerformIO $ do
 -- @since 4.5.0.0
 traceEventIO :: String -> IO ()
 traceEventIO msg =
-  withEventlog $ GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+  whenEventlog $ GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
     case traceEvent# p s of s' -> (# s', () #)
 
 -- $markers
@@ -320,7 +321,7 @@ traceEventIO msg =
 -- @since 4.7.0.0
 traceMarker :: String -> a -> a
 traceMarker msg expr = unsafeDupablePerformIO $ do
-    withEventlog $ traceMarkerIO msg
+    traceMarkerIO msg
     return expr
 
 -- | The 'traceMarkerIO' function emits a marker to the eventlog, if eventlog
@@ -332,5 +333,5 @@ traceMarker msg expr = unsafeDupablePerformIO $ do
 -- @since 4.7.0.0
 traceMarkerIO :: String -> IO ()
 traceMarkerIO msg =
-  withEventlog $ GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+  whenEventlog $ GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
     case traceMarker# p s of s' -> (# s', () #)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d833b98b15d51d0ec67d283cd2749d03e70ca3c1...fca165f00d97179a91c2b95d86a8e5c2400c9c75

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d833b98b15d51d0ec67d283cd2749d03e70ca3c1...fca165f00d97179a91c2b95d86a8e5c2400c9c75
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/20200522/7849e281/attachment-0001.html>


More information about the ghc-commits mailing list