{-# LANGUAGE MagicHash #-}{-# LANGUAGE UnboxedTuples #-}{-|
'T.Text' variant of the tracing functions in "Debug.Trace".
-}moduleDebug.Trace.Text(-- * Eventlog tracing-- $eventlog_tracingtraceEvent ,traceEventIO -- * Execution phase markers-- $markers,traceMarker ,traceMarkerIO )whereimportControl.Monad(when)importForeign.C.String(CString)importGHC.Exts(Ptr(..),traceEvent#,traceMarker#)importGHC.IO(IO(..))importqualifiedSystem.IO.UnsafeasUnsafeimportqualifiedData.ByteStringasBimportqualifiedData.TextasTimportqualifiedData.Text.EncodingasTEimportDebug.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.-- | 'T.Text' variant of 'Debug.Trace.traceEvent'.---- \(O(n)\) This function marshals the 'T.Text' into a 'B.ByteString' and-- convert it into a null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'T.Text' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceEvent ::T.Text->a ->a traceEvent :: forall a. Text -> a -> a
traceEvent Text
message a
a |Bool
userTracingEnabled =Text -> a -> a
forall a. Text -> a -> a
traceEvent' Text
message a
a |Bool
otherwise=a
a traceEvent' ::T.Text->a ->a traceEvent' :: forall a. Text -> a -> a
traceEvent' Text
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
$doText -> IO ()
traceEventIO' Text
message a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
a {-# NOINLINEtraceEvent' #-}-- | 'T.Text' variant of 'Debug.Trace.traceEventIO'.---- \(O(n)\) This function marshals the 'T.Text' into a 'B.ByteString' and-- convert it into a null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'T.Text' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceEventIO ::T.Text->IO()traceEventIO :: Text -> IO ()
traceEventIO Text
message =Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenBool
userTracingEnabled (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$Text -> IO ()
traceEventIO' Text
message traceEventIO' ::T.Text->IO()traceEventIO' :: Text -> IO ()
traceEventIO' Text
message =Text -> (CString -> IO ()) -> IO ()
forall a. Text -> (CString -> IO a) -> IO a
withCString Text
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.-- | 'T.Text' variant of 'Debug.Trace.traceMarker'.---- \(O(n)\) This function marshals the 'T.Text' into a 'B.ByteString' and-- convert it into a null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'T.Text' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceMarker ::T.Text->a ->a traceMarker :: forall a. Text -> a -> a
traceMarker Text
message a
a |Bool
userTracingEnabled =Text -> a -> a
forall a. Text -> a -> a
traceMarker' Text
message a
a |Bool
otherwise=a
a traceMarker' ::T.Text->a ->a traceMarker' :: forall a. Text -> a -> a
traceMarker' Text
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
$doText -> IO ()
traceMarkerIO' Text
message a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
a {-# NOINLINEtraceMarker' #-}-- | 'T.Text' variant of 'Debug.Trace.traceMarkerIO'.---- \(O(n)\) This function marshals the 'T.Text' into a 'B.ByteString' and-- convert it into a null-terminated 'Foreign.C.Types.CString'.---- Note that this function doesn't evaluate the 'T.Text' if user tracing-- in eventlog is disabled.---- The input should be shorter than \(2^{16}\) bytes. Otherwise the RTS-- generates a broken eventlog.traceMarkerIO ::T.Text->IO()traceMarkerIO :: Text -> IO ()
traceMarkerIO Text
message =Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenBool
userTracingEnabled (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$Text -> IO ()
traceMarkerIO' Text
message traceMarkerIO' ::T.Text->IO()traceMarkerIO' :: Text -> IO ()
traceMarkerIO' Text
message =Text -> (CString -> IO ()) -> IO ()
forall a. Text -> (CString -> IO a) -> IO a
withCString Text
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' ,()#)withCString ::T.Text->(CString->IOa )->IOa withCString :: forall a. Text -> (CString -> IO a) -> IO a
withCString Text
text =ByteString -> (CString -> IO a) -> IO a
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCString(Text -> ByteString
TE.encodeUtf8Text
text )

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