
What do you call these functions? I'll put them all into a patch and open a
feature request for them all in one go.
Chris
On 21 January 2013 22:40, Roman Cheplyaka
While we're at it, the trace functions I miss are
\x -> trace x x
and
\x -> trace (show x) x
Roman
* Andreas Abel
[2013-01-21 23:31:24+0100] +1. I also had to define traceM for the same purposes. --Andreas
On 21.01.13 6:41 PM, Chris Seaton wrote:
Yes, I suppose that traceIO does not have the semantics I assumed. Still, I think it is useful to have a trace that one can easily insert into an arbitrary monad. Here's how I use it:
--------
import Debug.Trace
main :: IO () main = putStrLn $ show foo
foo :: Maybe Int foo = do x <- bar 14 traceM $ show x y <- bar 2 traceM $ show y return $ x + y
bar :: Int -> Maybe Int bar x = Just $ 2*x
traceM :: (Monad m) => String -> m () traceM message = trace message $ return ()
----------
I think it is cleaner and more obvious than without the abstraction. Plus it is very easy to comment out. It is really good for list comprehensions written in do notation, as I often want to peek at intermediate values of those. I know I always add it to my projects, so I thought it may be wanted in base.
As Henning Thielemann said, you can use printf or whatever with it, but I think that is an orthogonal issue.
Regards,
Chris
On 21 January 2013 17:09, Herbert Valerio Riedel
mailto:hvr@gnu.org> wrote: Chris Seaton
mailto:chris@chrisseaton.com> writes: > I use printf-style debugging a lot, so I am always adding and removing > applications of trace. There is the Debug.Trace.traceIO function that makes > this easy to do in the IO monad (it just applies hPutStrLn stderr), but is > that specialisation to IO unnecessary? > > I find myself always using this utility function: > > traceM :: (Monad m) => String -> m () > traceM message = trace message $ return () > > Which can be used to implement traceIO. > > traceIO :: String -> IO () > traceIO = traceM
btw, that wouldn't have the same semantics as the existing `Debug.Trace.traceIO` which is more or less something similiar to a `hPutStrLn stderr` whose side-effect gets triggered at monad-execution time, whereas the side-effect of `traceM` occurs at monad-construction time; consider the following program:
--8<---------------cut here---------------start------------->8--- import Control.Monad import Debug.Trace
traceM :: (Monad m) => String -> m () traceM message = trace message $ return ()
traceIO' :: String -> IO () traceIO' = traceM
main = replicateM_ 5 $ do trace1 trace2 where trace1 = traceIO' "trace1" trace2 = traceIO "trace2" --8<---------------cut here---------------end--------------->8---
when run via runghc (or compiled with -O0) for GHC 7.6, this emits
--8<---------------cut here---------------start------------->8--- trace1 trace2 trace2 trace2 trace2 trace2 --8<---------------cut here---------------end--------------->8---
only when using -O1 or -O2 the output results in
--8<---------------cut here---------------start------------->8--- trace1 trace2 trace1 trace2 trace1 trace2 trace1 trace2 trace1 trace2 --8<---------------cut here---------------end--------------->8---
(I'm guessing this due to `trace1` being inlined for -O1/-O2 -- but I haven't checked)
cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries