{-# LANGUAGE CPP, ScopedTypeVariables #-}
module Network.Riak.Debug
(
level
, debug
, debugValues
, setHandle
, showM
) where
import Control.Concurrent.MVar (MVar, modifyMVar_, newMVar, withMVar)
import Control.Exception hiding (handle)
import Control.Monad (forM_, when)
import Network.Riak.Types.Internal
import System.Environment (getEnv)
import System.IO (Handle, hPutStrLn, stderr)
import System.IO.Unsafe (unsafePerformIO)
level :: Int
#ifdef DEBUG
level = unsafePerformIO $ do
es <- try $ getEnv "RIAK_DEBUG"
case es of
Left (_::SomeException) -> return 0
Right "on" -> return 1
Right s -> case reads s of
((n,_):_) -> return n
_ -> return 1
{-# NOINLINE level #-}
#else
level = 0
{-# INLINE level #-}
#endif
#ifdef DEBUG
handle :: MVar Handle
handle = unsafePerformIO $ newMVar stderr
{-# NOINLINE handle #-}
#endif
setHandle :: Handle -> IO ()
#ifdef DEBUG
setHandle = modifyMVar_ handle . const . return
#else
setHandle _ = return ()
{-# INLINE setHandle #-}
#endif
debug :: String
-> String
-> IO ()
#ifdef DEBUG
debug func str
| level == 0 = return ()
| otherwise =
withMVar handle $ \h -> hPutStrLn h $ str ++ " [" ++ func ++ "]"
#else
debug _ _ = return ()
{-# INLINE debug #-}
#endif
debugValues :: (Show a) =>
String
-> String
-> [a]
-> IO ()
debugValues func str values
#ifdef DEBUG
| level == 0 = return ()
| otherwise =
withMVar handle $ \h -> do
hPutStrLn h $ str ++ ": " ++ show (length values) ++
" values [" ++ func ++ "]"
when (level > 1) .
forM_ (zip [(0::Int)..] values) $ \(i,v) ->
hPutStrLn h $ " [" ++ show i ++ "] " ++ show v
#else
debugValues _ _ _ = return ()
{-# INLINE debugValues #-}
#endif
showM :: (Show a, Tagged a) => a -> String
showM m | level > 1 = show m
| otherwise = show (messageTag m)