{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
module Debug.Trace.Binary
(
traceBinaryEvent
, traceBinaryEventIO
) where
import Control.Monad (when)
import GHC.Exts (Ptr(..), Int(..), traceBinaryEvent#)
import GHC.IO (IO(..))
import qualified System.IO.Unsafe as Unsafe
import qualified Data.ByteString as B
import qualified Data.ByteString.Unsafe as BU
import Debug.Trace.Flags (userTracingEnabled)
traceBinaryEvent :: B.ByteString -> a -> a
traceBinaryEvent :: forall a. ByteString -> a -> a
traceBinaryEvent ByteString
bytes a
a
| Bool
userTracingEnabled = forall a. ByteString -> a -> a
traceBinaryEvent' ByteString
bytes a
a
| Bool
otherwise = a
a
traceBinaryEvent' :: B.ByteString -> a -> a
traceBinaryEvent' :: forall a. ByteString -> a -> a
traceBinaryEvent' ByteString
bytes a
a = forall a. IO a -> a
Unsafe.unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$ do
ByteString -> IO ()
traceBinaryEventIO' ByteString
bytes
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
{-# NOINLINE traceBinaryEvent' #-}
traceBinaryEventIO :: B.ByteString -> IO ()
traceBinaryEventIO :: ByteString -> IO ()
traceBinaryEventIO ByteString
bytes = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
userTracingEnabled forall a b. (a -> b) -> a -> b
$ ByteString -> IO ()
traceBinaryEventIO' ByteString
bytes
traceBinaryEventIO' :: B.ByteString -> IO ()
traceBinaryEventIO' :: ByteString -> IO ()
traceBinaryEventIO' ByteString
bytes =
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BU.unsafeUseAsCStringLen ByteString
bytes forall a b. (a -> b) -> a -> b
$ \(Ptr Addr#
p, I# Int#
n) -> forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case forall d. Addr# -> Int# -> State# d -> State# d
traceBinaryEvent# Addr#
p Int#
n State# RealWorld
s of
State# RealWorld
s' -> (# State# RealWorld
s', () #)