{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Trustworthy #-}
#if ( __GLASGOW_HASKELL__ >= 804 )
{-# LANGUAGE TypeInType #-}
#endif
module Universum.Debug
( Undefined (..)
, error
, trace
, traceM
, traceId
, traceIdWith
, traceShow
, traceShowId
, traceShowIdWith
, traceShowM
, undefined
) where
import Control.Monad (Monad, return)
import Data.Data (Data)
import Data.Text (Text, pack, unpack)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import System.IO.Unsafe (unsafePerformIO)
#if ( __GLASGOW_HASKELL__ >= 800 )
import GHC.Exception (errorCallWithCallStackException)
import GHC.Exts (RuntimeRep, TYPE, raise#)
import Universum.Base (HasCallStack, callStack)
#endif
import Universum.Applicative (pass)
import Universum.Print (putStrLn)
import qualified Prelude as P
{-# WARNING trace "'trace' remains in code" #-}
trace :: Text -> a -> a
trace string expr = unsafePerformIO (do
putStrLn string
return expr)
#if ( __GLASGOW_HASKELL__ >= 800 )
error :: forall (r :: RuntimeRep) . forall (a :: TYPE r) . HasCallStack
=> Text -> a
error s = raise# (errorCallWithCallStackException (unpack s) callStack)
#else
error :: Text -> a
error s = P.error (unpack s)
#endif
{-# WARNING traceShow "'traceShow' remains in code" #-}
traceShow :: P.Show a => a -> b -> b
traceShow a b = trace (pack (P.show a)) b
{-# WARNING traceShowId "'traceShowId' remains in code" #-}
traceShowId :: P.Show a => a -> a
traceShowId a = trace (pack (P.show a)) a
{-# WARNING traceIdWith "'traceIdWith' remains in code" #-}
traceIdWith :: (a -> Text) -> a -> a
traceIdWith f a = trace (f a) a
{-# WARNING traceShowIdWith "'traceShowIdWith' remains in code" #-}
traceShowIdWith :: P.Show s => (a -> s) -> a -> a
traceShowIdWith f a = trace (pack (P.show (f a))) a
{-# WARNING traceShowM "'traceShowM' remains in code" #-}
traceShowM :: (P.Show a, Monad m) => a -> m ()
traceShowM a = trace (pack (P.show a)) pass
{-# WARNING traceM "'traceM' remains in code" #-}
traceM :: (Monad m) => Text -> m ()
traceM s = trace s pass
{-# WARNING traceId "'traceId' remains in code" #-}
traceId :: Text -> Text
traceId s = trace s s
{-# WARNING Undefined "'Undefined' type remains in code" #-}
data Undefined = Undefined
deriving (P.Eq, P.Ord, P.Show, P.Read, P.Enum, P.Bounded, Data, Typeable, Generic)
{-# WARNING undefined "'undefined' function remains in code (or use 'error')" #-}
#if ( __GLASGOW_HASKELL__ >= 800 )
undefined :: forall (r :: RuntimeRep) . forall (a :: TYPE r) . HasCallStack => a
#else
undefined :: a
#endif
undefined = P.undefined