[GHC] #9795: Debug.Trace.trace is too strict

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Consider the following toy example: {{{#!hs import Debug.Trace f n = let res = g n in (trace $ unlines ["in: " ++ show n, "out: " ++ show res]) res where g n = if n <= 1000 then n+1 else g n main = print $ [f 500, f 302, f 2000, f 22] }}} When run it outputs: {{{ in: 500 out: 501 in: 302 out: 303 ^C }}} In a real example, for a program that hangs, where one only ''suspects'' that `f` may be the culprit, and where `f` is being called from various places with different values, this output is not very useful (and in fact, it is misleading). My mental model of the `trace` function is something along these lines: {{{#!hs myTrace :: String -> a -> a myTrace s a = unsafePerformIO $ do putStrLn s return a }}} and in fact, replacing `trace` by `myTrace` in the example above one gets the more useful: {{{ in: 500 out: 501 in: 302 out: 303 in: 2000 ^C }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by jcpetruzza): As another example of why `trace` shouldn't be strict, consider the following: {{{#!hs f xs = trace (show xs) $ g 0 xs where g n [] = n g n (x:xs) = g (n+1) xs main = print $ f [1..] }}} Because `trace` is strict, no output will be shown, which hides the fact that `f` is actually being called but with invalid input. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * differential: => Phab:D654 * milestone: => 7.12.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Comment (by ekmett): This probably belongs as an actual libraries@ discussion due to very broad impact and the fact that it silently changes semantics on code in surprising ways. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Changes (by rwbarton): * cc: thomie (added) Comment: The underlying problem has to do with how the strictness analyzer treats FFI calls (maybe just unsafe ones): `c_function >> y` is considered to be strict in `y`. I consider this to be a bug (as seen here: what if `c_function` has some externally visible effect?) but I'm concerned that fixing it might have bad effects on performance in other settings. I think it's effectively just luck that we don't see the same behavior with `hPutStrLn stderr s`: `hPutStrLn` is too complicated for the strictness analyser. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Comment (by rwbarton): Anyways I should add that this behavior of `trace` is very surprising and should definitely be fixed. But if we're going to work around the underlying bug with a hack (which seems reasonable to me) it should be a hack that is targeted to the actual issue. For example, I imagine that some use of magic functions like `lazy` would probably get the job done. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Comment (by thomie): My reasoning was: `withCString`, and in turn `debugBelch`, need the complete string to be present before printing can start. `hPutStrLn` on the other hand prints character for character. So it's not about `trace` being lazy or not, but how it handles (possibly infinite) lazy strings. There are some problems however: * with my patch, traceIO would handle lazy strings differently on non- Windows vs. Windows. * traceEventIO and traceMarkerIO still don't handle lazy strings. Both emit to the eventlog, for which (I'm guessing) the complete string needs to be ready as well . Maybe we should keep things the way they are. Although surprising, at least the story is consistent over all `trace` functions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Comment (by rwbarton): That's a separate issue to the one the original bug report was about, though. The surprising behavior is that `trace a b` can evaluate `b` before printing `a`, and if evaluation of `b` enters an infinite loop, `a` will never be printed at all. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Comment (by thomie): I'm confused. The examples from the description and from comment:1 print `a` before evaluating `b` in `trace a b`, when `a` is some fixed string. The problems arise when `a` can not be evaluated in full. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Comment (by simonpj): Thomie is right, and Reid is (very unusually) off the mark, unless I'm mistaken. `trace` really is defined (in `Debug.Trace` like this), just as the OP thought: {{{ trace :: String -> a -> a trace string expr = unsafePerformIO $ do traceIO string return expr }}} The call to `traceIO` really does happen before `expr` is evaluated. The culprit is `traceIO`: {{{ traceIO :: String -> IO () traceIO msg = do withCString "%s\n" $ \cfmt -> do -- NB: debugBelch can't deal with null bytes, so filter them -- out so we don't accidentally truncate the message. See Trac #9395 let (nulls, msg') = partition (=='\0') msg withCString msg' $ \cmsg -> debugBelch cfmt cmsg when (not (null nulls)) $ withCString "WARNING: previous trace message had null bytes" $ \cmsg -> debugBelch cfmt cmsg }}} I'm not quite sure what those calls to `withCString` are doing, but I think they are strict in the string. So if the message has bottoms in it (which is the case in this example) none of it will get printed. That is not really too bad; although it should be documented. After all, you can always write {{{ trace ("in: " ++ show n) $ trace ("out: " ++ show res) $ res }}} and now you should see the first message even if you get stuck on the second. My conclusion: fix the documentation. I'll add this to the documentation for `trace`: {{{ The 'trace' function evaluates the message (i.e. the first argument) completely before printing it; so if the message is not fully defined, none of it will be printed. }}} OK? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict
-------------------------------------+-------------------------------------
Reporter: jcpetruzza | Owner:
Type: bug | Status: patch
Priority: normal | Milestone: 7.12.1
Component: libraries/base | Version: 7.8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions: Phab:D654
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D654 -------------------------------------+------------------------------------- Changes (by simonpj): * status: patch => merge Comment: Let's merge the doc change to 7.10 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * differential: Phab:D654 => Comment:
I'll add this to the documentation for `trace`: {{{ The 'trace' function evaluates the message (i.e. the first argument) completely before printing it; so if the message is not fully defined, none of it will be printed. }}} OK?
Simon
Ok. Perhaps add that comment to the top of the module instead, since it applies to all the functions in the module equally. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict
-------------------------------------+-------------------------------------
Reporter: jcpetruzza | Owner:
Type: bug | Status: merge
Priority: normal | Milestone: 7.12.1
Component: libraries/base | Version: 7.8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by jcpetruzza): I still think that being strict on the string is the wrong default for a function whose only purpose is debugging pure functions, and I don't quite see what the benefit of the current behaviour is. Simon's workaround works after the fact, when you already know that the problem might be `res` being bottom. When starting a debugging session, one doesn't always have a clear suspicion of the culprit. A good part of the usefulness of `trace` is giving you an indication that certain expression is actually being evaluated, even if the full string fails to be printed in full. The way I see it, in order to avoid problems with a strict `trace`, one should be more defensive and start using it as Simon indicates in a systematical way. Consider for example the following excerpt from the [[https://wiki.haskell.org/Debugging|wiki entry on debugging]]: A common idiom to trace a function is: {{{ #!haskell myfun a b | trace ("myfun " ++ show a ++ " " ++ show b) False = undefined myfun a b = ... }}} With the current behaviour, I believe this should really be: {{{ #!haskell myfun a b | trace "myfun " $ trace (show a ++ " " ++ show b) False = undefined myfun a b = ... }}} and/or an explanation on `trace` being strict and what could happen if `show a` or `show b` loop or have an infinite output. With a lazy `trace` all this goes away, making `trace` more powerful and easier to use. Perhaps there are very good reasons to keep `trace` strict, but I'm not aware of them... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: merge => new Comment: (Both commits have been merged to `ghc-7.10`, so taking out of merge state - see d67b7842548209b5d0f6bc04afab84c84adbe70c and 35a0b67dc284f8dca47089538c9ee68b06dc6f39; a discussion here may cause something to change for 7.12 in the mean time.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Replying to [comment:14 jcpetruzza]:
Perhaps there are very good reasons to keep trace strict, but I'm not aware of them...
I see 3 reasons: * For Windows gui applications, the trace message is printed to something called the debug console (if it is enabled). It prepends the message with the current time or something. I think the way it works is, we have to collect the full message first, and then make some windows api call to print the message at once. Different messages should not get interleaved, and you don't want to split a single message over multiple lines (one for each character). So on Windows we can not simply make your proposed change. It would be confusing if `trace` were only lazy in the message on other platforms, but still strict on Windows. * Debug.Trace also exports `traceEvent` and `traceMarker`, which emit a message to the GHC eventlog. Again, this is a strict operation. It would be confusing if those functions had different laziness semantics from `trace`. This could be solved with documentation. * As Edward said in comment:3, it would be a user visible change, which is better handled on the libraries list. Perhaps make a library proposal to add a new `trace` like function to Debug.Trace, that is lazy in the message? The name would be the hardest part. `traceStderr` could be an option. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9795: Debug.Trace.trace is too strict -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * type: bug => feature request -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9795#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC