Clinton
Clinton

Reputation: 23135

Making "trace" optimise away like "assert"?

GHC rewrites asserts when optimising as just id. Or alternatively, it's behaviour can be changed with a compiler flag. However, I noticed the same doesn't happen with trace. Is there a version of trace which just ends up as id if a flag isn't or is set?

More generally speaking, is there a way to alter the behaviour of a function based on the compiler flags used to compile the calling module (not the flags used to compile itself). Much like assert does. Or is this GHC magic that can only happen with assert?

Upvotes: 5

Views: 136

Answers (3)

Michael Snoyman
Michael Snoyman

Reputation: 31305

OK, back at my computer and finally remembered I wanted to demonstrate this. Here goes:

import Control.Exception
import Debug.Trace
import Control.Monad

traceDebug :: String -> a -> a
traceDebug msg = assert (trace msg True)

main :: IO ()
main = replicateM_ 2 $ do
    print $ traceDebug "here1" ()
    print $ traceDebug "here2" ()
    print $ traceDebug "here3" ()

When compiled without optimizations, the output is:

here1
()
here2
()
here3
()
()
()
()

With optimizations:

()
()
()
()
()
()

So I think this addresses the request, with the standard caveat around trace that once the thunk has been evaluated, it won't be evaluated a second time (which is why the messages only happen the first time through the do-block).

Upvotes: 5

Cirdec
Cirdec

Reputation: 24156

Warning: I haven't tried this ...

You can replace the Debug.Trace module completely with compiler flags. Make another module with trivial implementations of the functions in Debug.Trace:

module NoTrace (trace) where:

trace :: String -> a -> a
{-# INLINE trace #-}
trace _message = id

...

Put this module in another package named no-trace.

Hide the Debug.Trace module in the arguments to ghc by including every module from the base package except Debug.Trace. Replace Debug.Trace with NoTrace from the no-trace package.

ghc -package="base (Control, Control.Applicative, ..., Data.Word, Foreign, ...)" \
    -package="no-trace (NoTrace as Debug.Trace)" \
    ...

This came from the crazy idea of using the compiler flag that changes the prelude to replace the prelude with one that had rewrite rules to remove traces, but those rewrite rules would taint anything that imported a module compiled with them, even if a downstream importer still wanted to use traces. When looking up how to replace the prelude I found that ghc can replace any module instead.

Upvotes: 9

Cirdec
Cirdec

Reputation: 24156

No, at least not based on assert. The magic for assert works the other direction and replaces the identity function with an assertion.

Here's assert from base 4.9:

-- Assertion function.  This simply ignores its boolean argument.
-- The compiler may rewrite it to @('assertError' line)@.

-- | If the first argument evaluates to 'True', then the result is the
-- second argument.  Otherwise an 'AssertionFailed' exception is raised,
-- containing a 'String' with the source file and line number of the
-- call to 'assert'.
--
-- Assertions can normally be turned on or off with a compiler flag
-- (for GHC, assertions are normally on unless optimisation is turned on
-- with @-O@ or the @-fignore-asserts@
-- option is given).  When assertions are turned off, the first
-- argument to 'assert' is ignored, and the second argument is
-- returned as the result.

--      SLPJ: in 5.04 etc 'assert' is in GHC.Prim,
--      but from Template Haskell onwards it's simply
--      defined here in Base.lhs
assert :: Bool -> a -> a
assert _pred r = r

Upvotes: 6

Related Questions