{-# LANGUAGE CPP #-}

{-|
Module      : Debug.Pretty.Simple
Copyright   : (c) Dennis Gosnell, 2017
License     : BSD-style (see LICENSE file)
Maintainer  : cdep.illabout@gmail.com
Stability   : experimental
Portability : POSIX

This module contains the same functionality with Prelude's "Debug.Trace" module,
with pretty printing the debug strings.

Warning: This module also shares the same unsafety of "Debug.Trace" module.
-}

module Debug.Pretty.Simple
  ( -- * Trace with color on dark background
    -- This determines whether to print in color by looking at whether 'stderr'
    -- is a TTY device.
    pTrace
  , pTraceId
  , pTraceShow
  , pTraceShowId
  , pTraceIO
  , pTraceM
  , pTraceShowM
  , pTraceStack
  , pTraceEvent
  , pTraceEventIO
  , pTraceMarker
  , pTraceMarkerIO
  , pTraceWith
  , pTraceShowWith
    -- * Trace forcing color
  , pTraceForceColor
  , pTraceIdForceColor
  , pTraceShowForceColor
  , pTraceShowIdForceColor
  , pTraceMForceColor
  , pTraceShowMForceColor
  , pTraceStackForceColor
  , pTraceEventForceColor
  , pTraceEventIOForceColor
  , pTraceMarkerForceColor
  , pTraceMarkerIOForceColor
  , pTraceIOForceColor
    -- * Trace without color
  , pTraceNoColor
  , pTraceIdNoColor
  , pTraceShowNoColor
  , pTraceShowIdNoColor
  , pTraceMNoColor
  , pTraceShowMNoColor
  , pTraceStackNoColor
  , pTraceEventNoColor
  , pTraceEventIONoColor
  , pTraceMarkerNoColor
  , pTraceMarkerIONoColor
  , pTraceIONoColor
    -- * Trace With 'OutputOptions'
  , pTraceOpt
  , pTraceIdOpt
  , pTraceShowOpt
  , pTraceShowIdOpt
  , pTraceOptIO
  , pTraceOptM
  , pTraceShowOptM
  , pTraceStackOpt
  , pTraceEventOpt
  , pTraceEventOptIO
  , pTraceMarkerOpt
  , pTraceMarkerOptIO
  ) where

import Control.Monad ((<=<))
import Data.Text.Lazy (Text, unpack)
import Debug.Trace
       (trace, traceEvent, traceEventIO, traceIO, traceM, traceMarker,
        traceMarkerIO, traceStack)
import System.IO (stderr)
import System.IO.Unsafe (unsafePerformIO)
import Text.Pretty.Simple
       (CheckColorTty(..), OutputOptions, pStringOpt,
        defaultOutputOptionsNoColor, defaultOutputOptionsDarkBg)
import Text.Pretty.Simple.Internal (hCheckTTY)

#if __GLASGOW_HASKELL__ < 710
-- We don't need this import for GHC 7.10 as it exports all required functions
-- from Prelude
import Control.Applicative
#endif

{-|
The 'pTraceIO' function outputs the trace message from the IO monad.
This sequences the output with respect to other IO actions.

@since 2.0.1.0
-}
{-# WARNING pTraceIO "'pTraceIO' remains in code" #-}
pTraceIO :: String -> IO ()
pTraceIO :: String -> IO ()
pTraceIO = CheckColorTty -> OutputOptions -> String -> IO ()
pTraceOptIO CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
The 'pTrace' function pretty prints the trace message given as its first
argument, before returning the second argument as its result.

For example, this returns the value of @f x@ but first outputs the message.

> pTrace ("calling f with x = " ++ show x) (f x)

The 'pTrace' function should /only/ be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.

@since 2.0.1.0
-}
{-# WARNING pTrace "'pTrace' remains in code" #-}
pTrace :: String -> a -> a
pTrace :: String -> a -> a
pTrace = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
Like 'pTrace' but returns the message instead of a third value.

@since 2.0.1.0
-}
{-# WARNING pTraceId "'pTraceId' remains in code" #-}
pTraceId :: String -> String
pTraceId :: String -> String
pTraceId = CheckColorTty -> OutputOptions -> String -> String
pTraceIdOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
Like 'pTrace', but uses 'show' on the argument to convert it to a 'String'.

This makes it convenient for printing the values of interesting variables or
expressions inside a function. For example here we print the value of the
variables @x@ and @z@:

> f x y =
>     pTraceShow (x, z) $ result
>   where
>     z = ...
>     ...

@since 2.0.1.0
-}
{-# WARNING pTraceShow "'pTraceShow' remains in code" #-}
pTraceShow :: (Show a) => a -> b -> b
pTraceShow :: a -> b -> b
pTraceShow = CheckColorTty -> OutputOptions -> a -> b -> b
forall a b. Show a => CheckColorTty -> OutputOptions -> a -> b -> b
pTraceShowOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
Like 'pTraceShow' but returns the shown value instead of a third value.

@since 2.0.1.0
-}
{-# WARNING pTraceShowId "'pTraceShowId' remains in code" #-}
pTraceShowId :: (Show a) => a -> a
pTraceShowId :: a -> a
pTraceShowId = CheckColorTty -> OutputOptions -> a -> a
forall a. Show a => CheckColorTty -> OutputOptions -> a -> a
pTraceShowIdOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg
{-|
Like 'pTrace' but returning unit in an arbitrary 'Applicative' context. Allows
for convenient use in do-notation.

Note that the application of 'pTraceM' is not an action in the 'Applicative'
context, as 'pTraceIO' is in the 'IO' type. While the fresh bindings in the
following example will force the 'traceM' expressions to be reduced every time
the @do@-block is executed, @traceM "not crashed"@ would only be reduced once,
and the message would only be printed once.  If your monad is in 'MonadIO',
@liftIO . pTraceIO@ may be a better option.

> ... = do
>   x <- ...
>   pTraceM $ "x: " ++ show x
>   y <- ...
>   pTraceM $ "y: " ++ show y

@since 2.0.1.0
-}
{-# WARNING pTraceM "'pTraceM' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceM :: (Monad f) => String -> f ()
#else
pTraceM :: (Applicative f) => String -> f ()
#endif
pTraceM :: String -> f ()
pTraceM = CheckColorTty -> OutputOptions -> String -> f ()
forall (f :: * -> *).
Applicative f =>
CheckColorTty -> OutputOptions -> String -> f ()
pTraceOptM CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg
{-|
Like 'pTraceM', but uses 'show' on the argument to convert it to a 'String'.

> ... = do
>   x <- ...
>   pTraceShowM $ x
>   y <- ...
>   pTraceShowM $ x + y

@since 2.0.1.0
-}
{-# WARNING pTraceShowM "'pTraceShowM' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceShowM :: (Show a, Monad f) => a -> f ()
#else
pTraceShowM :: (Show a, Applicative f) => a -> f ()
#endif
pTraceShowM :: a -> f ()
pTraceShowM = CheckColorTty -> OutputOptions -> a -> f ()
forall a (f :: * -> *).
(Show a, Applicative f) =>
CheckColorTty -> OutputOptions -> a -> f ()
pTraceShowOptM CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
like 'pTrace', but additionally prints a call stack if one is
available.

In the current GHC implementation, the call stack is only
available if the program was compiled with @-prof@; otherwise
'pTraceStack' behaves exactly like 'pTrace'.  Entries in the call
stack correspond to @SCC@ annotations, so it is a good idea to use
@-fprof-auto@ or @-fprof-auto-calls@ to add SCC annotations automatically.

@since 2.0.1.0
-}
{-# WARNING pTraceStack "'pTraceStack' remains in code" #-}
pTraceStack :: String -> a -> a
pTraceStack :: String -> a -> a
pTraceStack = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceStackOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
The 'pTraceEvent' function behaves like 'trace' with the difference that
the message is emitted to the eventlog, if eventlog profiling is available
and enabled at runtime.

It is suitable for use in pure code. In an IO context use 'pTraceEventIO'
instead.

Note that when using GHC's SMP runtime, it is possible (but rare) to get
duplicate events emitted if two CPUs simultaneously evaluate the same thunk
that uses 'pTraceEvent'.

@since 2.0.1.0
-}
{-# WARNING pTraceEvent "'pTraceEvent' remains in code" #-}
pTraceEvent :: String -> a -> a
pTraceEvent :: String -> a -> a
pTraceEvent = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceEventOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

{-|
The 'pTraceEventIO' function emits a message to the eventlog, if eventlog
profiling is available and enabled at runtime.

Compared to 'pTraceEvent', 'pTraceEventIO' sequences the event with respect to
other IO actions.

@since 2.0.1.0
-}
{-# WARNING pTraceEventIO "'pTraceEventIO' remains in code" #-}
pTraceEventIO :: String -> IO ()
pTraceEventIO :: String -> IO ()
pTraceEventIO = CheckColorTty -> OutputOptions -> String -> IO ()
pTraceEventOptIO CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | The 'pTraceMarker' function emits a marker to the eventlog, if eventlog
-- profiling is available and enabled at runtime. The @String@ is the name of
-- the marker. The name is just used in the profiling tools to help you keep
-- clear which marker is which.
--
-- This function is suitable for use in pure code. In an IO context use
-- 'pTraceMarkerIO' instead.
--
-- Note that when using GHC's SMP runtime, it is possible (but rare) to get
-- duplicate events emitted if two CPUs simultaneously evaluate the same thunk
-- that uses 'pTraceMarker'.
--
-- @since 2.0.1.0
{-# WARNING pTraceMarker "'pTraceMarker' remains in code" #-}
pTraceMarker :: String -> a -> a
pTraceMarker :: String -> a -> a
pTraceMarker = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceMarkerOpt CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | The 'pTraceMarkerIO' function emits a marker to the eventlog, if eventlog
-- profiling is available and enabled at runtime.
--
-- Compared to 'pTraceMarker', 'pTraceMarkerIO' sequences the event with respect
-- to other IO actions.
--
-- @since 2.0.1.0
{-# WARNING pTraceMarkerIO "'pTraceMarkerIO' remains in code" #-}
pTraceMarkerIO :: String -> IO ()
pTraceMarkerIO :: String -> IO ()
pTraceMarkerIO = CheckColorTty -> OutputOptions -> String -> IO ()
pTraceMarkerOptIO CheckColorTty
CheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | The 'pTraceWith' function pretty prints the result of
-- applying @f to @a and returns back @a
--
-- @since ?
{-# WARNING pTraceWith "'pTraceWith' remains in code" #-}
pTraceWith :: (a -> String) -> a -> a
pTraceWith :: (a -> String) -> a -> a
pTraceWith a -> String
f a
a = String -> a -> a
forall a. String -> a -> a
pTrace (a -> String
f a
a) a
a

-- | The 'pTraceShowWith' function similar to 'pTraceWith' except that
-- @f can return any type that implements Show
--
-- @since ?
{-# WARNING pTraceShowWith "'pTraceShowWith' remains in code" #-}
pTraceShowWith :: Show b => (a -> b) -> a -> a
pTraceShowWith :: (a -> b) -> a -> a
pTraceShowWith a -> b
f = (b -> String
forall a. Show a => a -> String
show (b -> String) -> (a -> b) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) (a -> String) -> (String -> a -> a) -> a -> a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> a -> a
forall a b. Show a => a -> b -> b
pTraceShow

------------------------------------------
-- Helpers
------------------------------------------
{-# WARNING pStringTTYOptIO "'pStringTTYOptIO' remains in code" #-}
pStringTTYOptIO :: CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO :: CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions String
v = do
  OutputOptions
realOutputOpts <-
    case CheckColorTty
checkColorTty of
      CheckColorTty
CheckColorTty -> Handle -> OutputOptions -> IO OutputOptions
forall (m :: * -> *).
MonadIO m =>
Handle -> OutputOptions -> m OutputOptions
hCheckTTY Handle
stderr OutputOptions
outputOptions
      CheckColorTty
NoCheckColorTty -> OutputOptions -> IO OutputOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure OutputOptions
outputOptions
  Text -> IO Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ OutputOptions -> String -> Text
pStringOpt OutputOptions
realOutputOpts String
v

{-# WARNING pStringTTYOpt "'pStringTTYOpt' remains in code" #-}
pStringTTYOpt :: CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt :: CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  IO Text -> Text
forall a. IO a -> a
unsafePerformIO (IO Text -> Text) -> (String -> IO Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions

{-# WARNING pShowTTYOptIO "'pShowTTYOptIO' remains in code" #-}
pShowTTYOptIO :: Show a => CheckColorTty -> OutputOptions -> a -> IO Text
pShowTTYOptIO :: CheckColorTty -> OutputOptions -> a -> IO Text
pShowTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions =
  CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions (String -> IO Text) -> (a -> String) -> a -> IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show

{-# WARNING pShowTTYOpt "'pShowTTYOpt' remains in code" #-}
pShowTTYOpt :: Show a => CheckColorTty -> OutputOptions -> a -> Text
pShowTTYOpt :: CheckColorTty -> OutputOptions -> a -> Text
pShowTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  IO Text -> Text
forall a. IO a -> a
unsafePerformIO (IO Text -> Text) -> (a -> IO Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> a -> IO Text
forall a. Show a => CheckColorTty -> OutputOptions -> a -> IO Text
pShowTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions

------------------------------------------
-- Traces forcing color
------------------------------------------
-- | Similar to 'pTrace', but forcing color.
{-# WARNING pTraceForceColor "'pTraceForceColor' remains in code" #-}
pTraceForceColor :: String -> a -> a
pTraceForceColor :: String -> a -> a
pTraceForceColor = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceId', but forcing color.
{-# WARNING pTraceIdForceColor "'pTraceIdForceColor' remains in code" #-}
pTraceIdForceColor :: String -> String
pTraceIdForceColor :: String -> String
pTraceIdForceColor = CheckColorTty -> OutputOptions -> String -> String
pTraceIdOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceShow', but forcing color.
{-# WARNING pTraceShowForceColor "'pTraceShowForceColor' remains in code" #-}
pTraceShowForceColor :: (Show a) => a -> b -> b
pTraceShowForceColor :: a -> b -> b
pTraceShowForceColor = CheckColorTty -> OutputOptions -> a -> b -> b
forall a b. Show a => CheckColorTty -> OutputOptions -> a -> b -> b
pTraceShowOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceShowId', but forcing color.
{-# WARNING pTraceShowIdForceColor "'pTraceShowIdForceColor' remains in code" #-}
pTraceShowIdForceColor :: (Show a) => a -> a
pTraceShowIdForceColor :: a -> a
pTraceShowIdForceColor =
  CheckColorTty -> OutputOptions -> a -> a
forall a. Show a => CheckColorTty -> OutputOptions -> a -> a
pTraceShowIdOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg
-- | Similar to 'pTraceM', but forcing color.
{-# WARNING pTraceMForceColor "'pTraceMForceColor' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceMForceColor :: (Monad f) => String -> f ()
#else
pTraceMForceColor :: (Applicative f) => String -> f ()
#endif
pTraceMForceColor :: String -> f ()
pTraceMForceColor = CheckColorTty -> OutputOptions -> String -> f ()
forall (f :: * -> *).
Applicative f =>
CheckColorTty -> OutputOptions -> String -> f ()
pTraceOptM CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg
-- | Similar to 'pTraceShowM', but forcing color.
{-# WARNING pTraceShowMForceColor "'pTraceShowMForceColor' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceShowMForceColor :: (Show a, Monad f) => a -> f ()
#else
pTraceShowMForceColor :: (Show a, Applicative f) => a -> f ()
#endif
pTraceShowMForceColor :: a -> f ()
pTraceShowMForceColor =
  CheckColorTty -> OutputOptions -> a -> f ()
forall a (f :: * -> *).
(Show a, Applicative f) =>
CheckColorTty -> OutputOptions -> a -> f ()
pTraceShowOptM CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceStack', but forcing color.
{-# WARNING pTraceStackForceColor "'pTraceStackForceColor' remains in code" #-}
pTraceStackForceColor :: String -> a -> a
pTraceStackForceColor :: String -> a -> a
pTraceStackForceColor =
  CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceStackOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceEvent', but forcing color.
{-# WARNING pTraceEventForceColor "'pTraceEventForceColor' remains in code" #-}
pTraceEventForceColor :: String -> a -> a
pTraceEventForceColor :: String -> a -> a
pTraceEventForceColor =
  CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceEventOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceEventIO', but forcing color.
{-# WARNING pTraceEventIOForceColor "'pTraceEventIOForceColor' remains in code" #-}
pTraceEventIOForceColor :: String -> IO ()
pTraceEventIOForceColor :: String -> IO ()
pTraceEventIOForceColor =
  CheckColorTty -> OutputOptions -> String -> IO ()
pTraceEventOptIO CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceMarker', but forcing color.
{-# WARNING pTraceMarkerForceColor "'pTraceMarkerForceColor' remains in code" #-}
pTraceMarkerForceColor :: String -> a -> a
pTraceMarkerForceColor :: String -> a -> a
pTraceMarkerForceColor =
  CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceMarkerOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceMarkerIO', but forcing color.
{-# WARNING pTraceMarkerIOForceColor "'pTraceMarkerIOForceColor' remains in code" #-}
pTraceMarkerIOForceColor :: String -> IO ()
pTraceMarkerIOForceColor :: String -> IO ()
pTraceMarkerIOForceColor =
  CheckColorTty -> OutputOptions -> String -> IO ()
pTraceMarkerOptIO CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

-- | Similar to 'pTraceIO', but forcing color.
{-# WARNING pTraceIOForceColor "'pTraceIOForceColor' remains in code" #-}
pTraceIOForceColor :: String -> IO ()
pTraceIOForceColor :: String -> IO ()
pTraceIOForceColor = CheckColorTty -> OutputOptions -> String -> IO ()
pTraceOptIO CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsDarkBg

------------------------------------------
-- Traces without color
------------------------------------------
-- | Similar to 'pTrace', but without color.
--
-- >>> pTraceNoColor "wow" ()
-- wow
-- ()
--
-- @since 2.0.2.0
{-# WARNING pTraceNoColor "'pTraceNoColor' remains in code" #-}
pTraceNoColor :: String -> a -> a
pTraceNoColor :: String -> a -> a
pTraceNoColor = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceId', but without color.
--
-- >>> pTraceIdNoColor "(1, 2, 3)" `seq` ()
-- ( 1
-- , 2
-- , 3
-- )
-- ()
--
-- @since 2.0.2.0
{-# WARNING pTraceIdNoColor "'pTraceIdNoColor' remains in code" #-}
pTraceIdNoColor :: String -> String
pTraceIdNoColor :: String -> String
pTraceIdNoColor = CheckColorTty -> OutputOptions -> String -> String
pTraceIdOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceShow', but without color.
--
-- >>> import qualified Data.Map as M
-- >>> pTraceShowNoColor (M.fromList [(1, True)]) ()
-- fromList
--     [
--         ( 1
--         , True
--         )
--     ]
-- ()
--
-- @since 2.0.2.0
{-# WARNING pTraceShowNoColor "'pTraceShowNoColor' remains in code" #-}
pTraceShowNoColor :: (Show a) => a -> b -> b
pTraceShowNoColor :: a -> b -> b
pTraceShowNoColor = CheckColorTty -> OutputOptions -> a -> b -> b
forall a b. Show a => CheckColorTty -> OutputOptions -> a -> b -> b
pTraceShowOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceShowId', but without color.
--
-- >>> import qualified Data.Map as M
-- >>> pTraceShowIdNoColor (M.fromList [(1, True)]) `seq` ()
-- fromList
--     [
--         ( 1
--         , True
--         )
--     ]
-- ()
--
-- @since 2.0.2.0
{-# WARNING pTraceShowIdNoColor "'pTraceShowIdNoColor' remains in code" #-}
pTraceShowIdNoColor :: (Show a) => a -> a
pTraceShowIdNoColor :: a -> a
pTraceShowIdNoColor =
  CheckColorTty -> OutputOptions -> a -> a
forall a. Show a => CheckColorTty -> OutputOptions -> a -> a
pTraceShowIdOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor
-- | Similar to 'pTraceM', but without color.
--
-- >>> pTraceMNoColor "wow"
-- wow
--
-- @since 2.0.2.0
{-# WARNING pTraceMNoColor "'pTraceMNoColor' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceMNoColor :: (Monad f) => String -> f ()
#else
pTraceMNoColor :: (Applicative f) => String -> f ()
#endif
pTraceMNoColor :: String -> f ()
pTraceMNoColor = CheckColorTty -> OutputOptions -> String -> f ()
forall (f :: * -> *).
Applicative f =>
CheckColorTty -> OutputOptions -> String -> f ()
pTraceOptM CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor
-- | Similar to 'pTraceShowM', but without color.
--
-- >>> pTraceShowMNoColor [1,2,3]
-- [ 1
-- , 2
-- , 3
-- ]
--
-- @since 2.0.2.0
{-# WARNING pTraceShowMNoColor "'pTraceShowMNoColor' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceShowMNoColor :: (Show a, Monad f) => a -> f ()
#else
pTraceShowMNoColor :: (Show a, Applicative f) => a -> f ()
#endif
pTraceShowMNoColor :: a -> f ()
pTraceShowMNoColor = CheckColorTty -> OutputOptions -> a -> f ()
forall a (f :: * -> *).
(Show a, Applicative f) =>
CheckColorTty -> OutputOptions -> a -> f ()
pTraceShowOptM CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceStack', but without color.
--
-- >>> pTraceStackNoColor "wow" () `seq` ()
-- wow
-- ()
--
-- @since 2.0.2.0
{-# WARNING pTraceStackNoColor "'pTraceStackNoColor' remains in code" #-}
pTraceStackNoColor :: String -> a -> a
pTraceStackNoColor :: String -> a -> a
pTraceStackNoColor = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceStackOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceEvent', but without color.
--
-- @since 2.0.2.0
{-# WARNING pTraceEventNoColor "'pTraceEventNoColor' remains in code" #-}
pTraceEventNoColor :: String -> a -> a
pTraceEventNoColor :: String -> a -> a
pTraceEventNoColor = CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceEventOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceEventIO', but without color.
--
-- @since 2.0.2.0
{-# WARNING pTraceEventIONoColor "'pTraceEventIONoColor' remains in code" #-}
pTraceEventIONoColor :: String -> IO ()
pTraceEventIONoColor :: String -> IO ()
pTraceEventIONoColor =
  CheckColorTty -> OutputOptions -> String -> IO ()
pTraceEventOptIO CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceMarker', but without color.
--
-- @since 2.0.2.0
{-# WARNING pTraceMarkerNoColor "'pTraceMarkerNoColor' remains in code" #-}
pTraceMarkerNoColor :: String -> a -> a
pTraceMarkerNoColor :: String -> a -> a
pTraceMarkerNoColor =
  CheckColorTty -> OutputOptions -> String -> a -> a
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceMarkerOpt CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceMarkerIO', but without color.
--
-- @since 2.0.2.0
{-# WARNING pTraceMarkerIONoColor "'pTraceMarkerIONoColor' remains in code" #-}
pTraceMarkerIONoColor :: String -> IO ()
pTraceMarkerIONoColor :: String -> IO ()
pTraceMarkerIONoColor =
  CheckColorTty -> OutputOptions -> String -> IO ()
pTraceMarkerOptIO CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

-- | Similar to 'pTraceIO', but without color.
--
-- >>> pTraceIONoColor "(1, 2, 3)"
-- ( 1
-- , 2
-- , 3
-- )
--
-- @since 2.0.2.0
{-# WARNING pTraceIONoColor "'pTraceIONoColor' remains in code" #-}
pTraceIONoColor :: String -> IO ()
pTraceIONoColor :: String -> IO ()
pTraceIONoColor = CheckColorTty -> OutputOptions -> String -> IO ()
pTraceOptIO CheckColorTty
NoCheckColorTty OutputOptions
defaultOutputOptionsNoColor

------------------------------------------
-- Traces that take options
------------------------------------------
{-|
Like 'pTrace' but takes OutputOptions.
-}
{-# WARNING pTraceOpt "'pTraceOpt' remains in code" #-}
pTraceOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> a -> a
forall a. String -> a -> a
trace (String -> a -> a) -> (String -> String) -> String -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> (String -> Text) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceId' but takes OutputOptions.
-}
{-# WARNING pTraceIdOpt "'pTraceIdOpt' remains in code" #-}
pTraceIdOpt :: CheckColorTty -> OutputOptions -> String -> String
pTraceIdOpt :: CheckColorTty -> OutputOptions -> String -> String
pTraceIdOpt CheckColorTty
checkColorTty OutputOptions
outputOptions String
a =
  CheckColorTty -> OutputOptions -> String -> String -> String
forall a. CheckColorTty -> OutputOptions -> String -> a -> a
pTraceOpt CheckColorTty
checkColorTty OutputOptions
outputOptions String
a String
a

{-|
Like 'pTraceShow' but takes OutputOptions.
-}
{-# WARNING pTraceShowOpt "'pTraceShowOpt' remains in code" #-}
pTraceShowOpt :: (Show a) => CheckColorTty -> OutputOptions -> a -> b -> b
pTraceShowOpt :: CheckColorTty -> OutputOptions -> a -> b -> b
pTraceShowOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> b -> b
forall a. String -> a -> a
trace (String -> b -> b) -> (a -> String) -> a -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> (a -> Text) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> a -> Text
forall a. Show a => CheckColorTty -> OutputOptions -> a -> Text
pShowTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceShowId' but takes OutputOptions.
-}
{-# WARNING pTraceShowIdOpt "'pTraceShowIdOpt' remains in code" #-}
pTraceShowIdOpt :: (Show a) => CheckColorTty -> OutputOptions -> a -> a
pTraceShowIdOpt :: CheckColorTty -> OutputOptions -> a -> a
pTraceShowIdOpt CheckColorTty
checkColorTty OutputOptions
outputOptions a
a =
  String -> a -> a
forall a. String -> a -> a
trace (Text -> String
unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ CheckColorTty -> OutputOptions -> a -> Text
forall a. Show a => CheckColorTty -> OutputOptions -> a -> Text
pShowTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions a
a) a
a

{-|
Like 'pTraceIO' but takes OutputOptions.
-}
{-# WARNING pTraceOptIO "'pTraceOptIO' remains in code" #-}
pTraceOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
pTraceOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
pTraceOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> IO ()
traceIO (String -> IO ()) -> (Text -> String) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> IO ()) -> (String -> IO Text) -> String -> IO ()
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions
{-|
Like 'pTraceM' but takes OutputOptions.
-}
{-# WARNING pTraceOptM "'pTraceOptM' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceOptM :: (Monad f) => CheckColorTty -> OutputOptions -> String -> f ()
#else
pTraceOptM ::
     (Applicative f) => CheckColorTty -> OutputOptions -> String -> f ()
#endif
pTraceOptM :: CheckColorTty -> OutputOptions -> String -> f ()
pTraceOptM CheckColorTty
checkColorTty OutputOptions
outputOptions String
string =
  String -> f () -> f ()
forall a. String -> a -> a
trace (Text -> String
unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions String
string) (f () -> f ()) -> f () -> f ()
forall a b. (a -> b) -> a -> b
$ () -> f ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-|
Like 'pTraceShowM' but takes OutputOptions.
-}
{-# WARNING pTraceShowOptM "'pTraceShowOptM' remains in code" #-}
#if __GLASGOW_HASKELL__ < 800
pTraceShowOptM ::
     (Show a, Monad f) => CheckColorTty -> OutputOptions -> a -> f ()
#else
pTraceShowOptM ::
     (Show a, Applicative f) => CheckColorTty -> OutputOptions -> a -> f ()
#endif
pTraceShowOptM :: CheckColorTty -> OutputOptions -> a -> f ()
pTraceShowOptM CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> f ()
forall (f :: * -> *). Applicative f => String -> f ()
traceM (String -> f ()) -> (a -> String) -> a -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> (a -> Text) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> a -> Text
forall a. Show a => CheckColorTty -> OutputOptions -> a -> Text
pShowTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceStack' but takes OutputOptions.
-}
{-# WARNING pTraceStackOpt "'pTraceStackOpt' remains in code" #-}
pTraceStackOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceStackOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceStackOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> a -> a
forall a. String -> a -> a
traceStack (String -> a -> a) -> (String -> String) -> String -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> (String -> Text) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceEvent' but takes OutputOptions.
-}
{-# WARNING pTraceEventOpt "'pTraceEventOpt' remains in code" #-}
pTraceEventOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceEventOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceEventOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> a -> a
forall a. String -> a -> a
traceEvent (String -> a -> a) -> (String -> String) -> String -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> (String -> Text) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceEventIO' but takes OutputOptions.
-}
{-# WARNING pTraceEventOptIO "'pTraceEventOptIO' remains in code" #-}
pTraceEventOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
pTraceEventOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
pTraceEventOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> IO ()
traceEventIO (String -> IO ()) -> (Text -> String) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> IO ()) -> (String -> IO Text) -> String -> IO ()
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceMarker' but takes OutputOptions.
-}
{-# WARNING pTraceMarkerOpt "'pTraceMarkerOpt' remains in code" #-}
pTraceMarkerOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceMarkerOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
pTraceMarkerOpt CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> a -> a
forall a. String -> a -> a
traceMarker (String -> a -> a) -> (String -> String) -> String -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> (String -> Text) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckColorTty -> OutputOptions -> String -> Text
pStringTTYOpt CheckColorTty
checkColorTty OutputOptions
outputOptions

{-|
Like 'pTraceMarkerIO' but takes OutputOptions.
-}
{-# WARNING pTraceMarkerOptIO "'pTraceMarkerOptIO' remains in code" #-}
pTraceMarkerOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
pTraceMarkerOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
pTraceMarkerOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions =
  String -> IO ()
traceMarkerIO (String -> IO ()) -> (Text -> String) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> IO ()) -> (String -> IO Text) -> String -> IO ()
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< CheckColorTty -> OutputOptions -> String -> IO Text
pStringTTYOptIO CheckColorTty
checkColorTty OutputOptions
outputOptions