add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Debug / Trace.hs
1 {-# LANGUAGE CPP, ForeignFunctionInterface #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Debug.Trace
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  portable
12 --
13 -- The 'trace' function.
14 --
15 -----------------------------------------------------------------------------
16
17 module Debug.Trace (
18         -- * Tracing
19         putTraceMsg,      -- :: String -> IO ()
20         trace,            -- :: String -> a -> a
21         traceShow
22   ) where
23
24 import Prelude
25 import System.IO.Unsafe
26
27 #ifdef __GLASGOW_HASKELL__
28 import Foreign.C.String
29 #else
30 import System.IO (hPutStrLn,stderr)
31 #endif
32
33 -- | 'putTraceMsg' function outputs the trace message from IO monad.
34 -- Usually the output stream is 'System.IO.stderr' but if the function is called
35 -- from Windows GUI application then the output will be directed to the Windows
36 -- debug console.
37 putTraceMsg :: String -> IO ()
38 putTraceMsg msg = do
39 #ifndef __GLASGOW_HASKELL__
40     hPutStrLn stderr msg
41 #else
42     withCString "%s\n" $ \cfmt ->
43      withCString msg  $ \cmsg ->
44       debugBelch cfmt cmsg
45
46 -- don't use debugBelch() directly, because we cannot call varargs functions
47 -- using the FFI.
48 foreign import ccall unsafe "HsBase.h debugBelch2"
49    debugBelch :: CString -> CString -> IO ()
50 #endif
51
52 {-# NOINLINE trace #-}
53 {-|
54 When called, 'trace' outputs the string in its first argument, before 
55 returning the second argument as its result. The 'trace' function is not 
56 referentially transparent, and should only be used for debugging, or for 
57 monitoring execution. Some implementations of 'trace' may decorate the string 
58 that\'s output to indicate that you\'re tracing. The function is implemented on
59 top of 'putTraceMsg'.
60 -}
61 trace :: String -> a -> a
62 trace string expr = unsafePerformIO $ do
63     putTraceMsg string
64     return expr
65
66 {-|
67 Like 'trace', but uses 'show' on the argument to convert it to a 'String'.
68
69 > traceShow = trace . show
70 -}
71 traceShow :: (Show a) => a -> b -> b
72 traceShow = trace . show