1{-# LANGUAGE Unsafe #-}
2{-# LANGUAGE MagicHash #-}
3{-# LANGUAGE NoImplicitPrelude #-}
4{-# LANGUAGE UnboxedTuples #-}
5
6-- This boot file is necessary to allow GHC developers to
7-- use trace facilities in those (relatively few) modules that Debug.Trace
8-- itself depends on. It is also necessary to make DsMonad.pprRuntimeTrace
9-- trace injections work in those modules.
10
11-----------------------------------------------------------------------------
12-- |
13-- Module      :  Debug.Trace
14-- Copyright   :  (c) The University of Glasgow 2001
15-- License     :  BSD-style (see the file libraries/base/LICENSE)
16--
17-- Maintainer  :  libraries@haskell.org
18-- Stability   :  provisional
19-- Portability :  portable
20--
21-- Functions for tracing and monitoring execution.
22--
23-- These can be useful for investigating bugs or performance problems.
24-- They should /not/ be used in production code.
25--
26-----------------------------------------------------------------------------
27
28module Debug.Trace (
29        -- * Tracing
30        -- $tracing
31        trace,
32        traceId,
33        traceShow,
34        traceShowId,
35        traceStack,
36        traceIO,
37        traceM,
38        traceShowM,
39
40        -- * Eventlog tracing
41        -- $eventlog_tracing
42        traceEvent,
43        traceEventIO,
44
45        -- * Execution phase markers
46        -- $markers
47        traceMarker,
48        traceMarkerIO,
49  ) where
50
51import GHC.Base
52import GHC.Show
53
54traceIO :: String -> IO ()
55
56trace :: String -> a -> a
57
58traceId :: String -> String
59
60traceShow :: Show a => a -> b -> b
61
62traceShowId :: Show a => a -> a
63
64traceM :: Applicative f => String -> f ()
65
66traceShowM :: (Show a, Applicative f) => a -> f ()
67
68traceStack :: String -> a -> a
69
70traceEvent :: String -> a -> a
71
72traceEventIO :: String -> IO ()
73
74traceMarker :: String -> a -> a
75
76traceMarkerIO :: String -> IO ()
77