{-# LANGUAGE CPP #-}{-# LANGUAGE MagicHash #-}{-# LANGUAGE UnboxedTuples #-}{-|
'B.ByteString' variant of the tracing functions in "Debug.Trace".
-}moduleDebug.Trace.ByteString(-- * Eventlog tracing-- $eventlog_tracingtraceEvent ,traceEventIO ,unsafeTraceEvent ,unsafeTraceEventIO -- * Execution phase markers-- $markers,traceMarker ,traceMarkerIO ,unsafeTraceMarker ,unsafeTraceMarkerIO )whereimportControl.Monad(when)importGHC.Exts(Ptr(..),traceEvent#,traceMarker#)importGHC.IO(IO(..))importqualifiedSystem.IO.UnsafeasUnsafeimportqualifiedData.ByteStringasBimportqualifiedData.ByteString.UnsafeasBUimportDebug.Trace.Flags (userTracingEnabled )-- $eventlog_tracing---- Eventlog tracing is a performance profiling system. These functions emit-- extra events into the eventlog. In combination with eventlog profiling-- tools these functions can be used for monitoring execution and-- investigating performance problems.-- | 'B.ByteString' variant of 'Debug.Trace.traceEvent'.---- \(O(n)\) This function copies the 'B.ByteString' to convert it to a-- null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceEvent ::B.ByteString->a ->a traceEvent :: forall a. ByteString -> a -> a
traceEvent ByteString
message a
a |Bool
userTracingEnabled =ByteString -> a -> a
forall a. ByteString -> a -> a
traceEvent' ByteString
message a
a |Bool
otherwise=a
a traceEvent' ::B.ByteString->a ->a traceEvent' :: forall a. ByteString -> a -> a
traceEvent' ByteString
message a
a =IO a -> a
forall a. IO a -> a
Unsafe.unsafeDupablePerformIO(IO a -> a) -> IO a -> a
forall a b. (a -> b) -> a -> b
$doByteString -> IO ()
traceEventIO' ByteString
message a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
a {-# NOINLINEtraceEvent' #-}-- | 'B.ByteString' variant of 'Debug.Trace.traceEventIO'.---- \(O(n)\) This function copies the 'B.ByteString' to convert it to a-- null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceEventIO ::B.ByteString->IO()traceEventIO :: ByteString -> IO ()
traceEventIO ByteString
message =Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenBool
userTracingEnabled (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ByteString -> IO ()
traceEventIO' ByteString
message traceEventIO' ::B.ByteString->IO()traceEventIO' :: ByteString -> IO ()
traceEventIO' ByteString
message =ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCStringByteString
message ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\(PtrAddr#
p )->(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$\State# RealWorld
s ->caseAddr# -> State# RealWorld -> State# RealWorld
forall d. Addr# -> State# d -> State# d
traceEvent#Addr#
p State# RealWorld
s ofState# RealWorld
s' ->(#State# RealWorld
s' ,()#)-- | 'B.ByteString' variant of 'Debug.Trace.traceEvent'.---- \(O(1)\) This function is unsafe in the way that it doesn't ensure the input-- string to be null-terminated. It is user's responsibility to null-terminate-- the input.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.unsafeTraceEvent ::B.ByteString->a ->a unsafeTraceEvent :: forall a. ByteString -> a -> a
unsafeTraceEvent ByteString
message a
a |Bool
userTracingEnabled =ByteString -> a -> a
forall a. ByteString -> a -> a
unsafeTraceEvent' ByteString
message a
a |Bool
otherwise=a
a unsafeTraceEvent' ::B.ByteString->a ->a unsafeTraceEvent' :: forall a. ByteString -> a -> a
unsafeTraceEvent' ByteString
message a
a =IO a -> a
forall a. IO a -> a
Unsafe.unsafeDupablePerformIO(IO a -> a) -> IO a -> a
forall a b. (a -> b) -> a -> b
$doByteString -> IO ()
unsafeTraceEventIO' ByteString
message a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
a {-# NOINLINEunsafeTraceEvent' #-}-- | 'B.ByteString' variant of 'Debug.Trace.traceEventIO'.---- \(O(1)\) This function is unsafe in the way that it doesn't ensure the input-- string to be null-terminated. It is user's responsibility to null-terminate-- the input.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.unsafeTraceEventIO ::B.ByteString->IO()unsafeTraceEventIO :: ByteString -> IO ()
unsafeTraceEventIO ByteString
message =Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenBool
userTracingEnabled (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ByteString -> IO ()
unsafeTraceEventIO' ByteString
message unsafeTraceEventIO' ::B.ByteString->IO()unsafeTraceEventIO' :: ByteString -> IO ()
unsafeTraceEventIO' ByteString
message =ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
BU.unsafeUseAsCStringByteString
message ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\(PtrAddr#
p )->(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$\State# RealWorld
s ->caseAddr# -> State# RealWorld -> State# RealWorld
forall d. Addr# -> State# d -> State# d
traceEvent#Addr#
p State# RealWorld
s ofState# RealWorld
s' ->(#State# RealWorld
s' ,()#)-- $markers---- When looking at a profile for the execution of a program we often want to-- be able to mark certain points or phases in the execution and see that-- visually in the profile.---- For example, a program might have several distinct phases with different-- performance or resource behaviour in each phase. To properly interpret the-- profile graph we really want to see when each phase starts and ends.---- Markers let us do this: we can annotate the program to emit a marker at-- an appropriate point during execution and then see that in a profile.-- | 'B.ByteString' variant of 'Debug.Trace.traceMarker'.---- \(O(n)\) This function copies the 'B.ByteString' to convert it to a-- null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceMarker ::B.ByteString->a ->a traceMarker :: forall a. ByteString -> a -> a
traceMarker ByteString
message a
a |Bool
userTracingEnabled =ByteString -> a -> a
forall a. ByteString -> a -> a
traceMarker' ByteString
message a
a |Bool
otherwise=a
a traceMarker' ::B.ByteString->a ->a traceMarker' :: forall a. ByteString -> a -> a
traceMarker' ByteString
message a
a =IO a -> a
forall a. IO a -> a
Unsafe.unsafeDupablePerformIO(IO a -> a) -> IO a -> a
forall a b. (a -> b) -> a -> b
$doByteString -> IO ()
traceMarkerIO' ByteString
message a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
a {-# NOINLINEtraceMarker' #-}-- | 'B.ByteString' variant of 'Debug.Trace.traceMarkerIO'.---- \(O(n)\) This function copies the 'B.ByteString' to convert it to a-- null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceMarkerIO ::B.ByteString->IO()traceMarkerIO :: ByteString -> IO ()
traceMarkerIO ByteString
message =Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenBool
userTracingEnabled (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ByteString -> IO ()
traceMarkerIO' ByteString
message traceMarkerIO' ::B.ByteString->IO()traceMarkerIO' :: ByteString -> IO ()
traceMarkerIO' ByteString
message =ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCStringByteString
message ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\(PtrAddr#
p )->(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$\State# RealWorld
s ->caseAddr# -> State# RealWorld -> State# RealWorld
forall d. Addr# -> State# d -> State# d
traceMarker#Addr#
p State# RealWorld
s ofState# RealWorld
s' ->(#State# RealWorld
s' ,()#)-- | 'B.ByteString' variant of 'Debug.Trace.traceMarker'.---- \(O(1)\) This function is unsafe in the way that it doesn't ensure the input-- string to be null-terminated. It is user's responsibility to null-terminate-- the input.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.unsafeTraceMarker ::B.ByteString->a ->a unsafeTraceMarker :: forall a. ByteString -> a -> a
unsafeTraceMarker ByteString
message a
a |Bool
userTracingEnabled =ByteString -> a -> a
forall a. ByteString -> a -> a
unsafeTraceMarker' ByteString
message a
a |Bool
otherwise=a
a unsafeTraceMarker' ::B.ByteString->a ->a unsafeTraceMarker' :: forall a. ByteString -> a -> a
unsafeTraceMarker' ByteString
message a
a =IO a -> a
forall a. IO a -> a
Unsafe.unsafeDupablePerformIO(IO a -> a) -> IO a -> a
forall a b. (a -> b) -> a -> b
$doByteString -> IO ()
unsafeTraceMarkerIO' ByteString
message a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
a {-# NOINLINEunsafeTraceMarker' #-}-- | 'B.ByteString' variant of 'Debug.Trace.traceMarkerIO'.---- \(O(1)\) This function is unsafe in the way that it doesn't ensure the input-- string to be null-terminated. It is user's responsibility to null-terminate-- the input.---- Note that this function doesn't evaluate the 'B.ByteString' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.unsafeTraceMarkerIO ::B.ByteString->IO()unsafeTraceMarkerIO :: ByteString -> IO ()
unsafeTraceMarkerIO ByteString
message =Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenBool
userTracingEnabled (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ByteString -> IO ()
unsafeTraceMarkerIO' ByteString
message unsafeTraceMarkerIO' ::B.ByteString->IO()unsafeTraceMarkerIO' :: ByteString -> IO ()
unsafeTraceMarkerIO' ByteString
message =ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
BU.unsafeUseAsCStringByteString
message ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\(PtrAddr#
p )->(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$\State# RealWorld
s ->caseAddr# -> State# RealWorld -> State# RealWorld
forall d. Addr# -> State# d -> State# d
traceMarker#Addr#
p State# RealWorld
s ofState# RealWorld
s' ->(#State# RealWorld
s' ,()#)

AltStyle によって変換されたページ (->オリジナル) /