{-# LANGUAGE CPP #-}
-- | This module defines the logging capability of Affection, whis is derived
-- from "Debug.Trace".
module Affection.Logging where

import Debug.Trace

-- | The log level definition
data LogLevel
  = Verbose -- ^ Log everything
  | Debug   -- ^ Log Debug messages and above
  | Warn    -- ^ Log only Warnings and errors
  | Error   -- ^ Log only errors

-- | Pure logging function
log
  :: LogLevel -- ^ Log level to log to
  -> String   -- ^ The message string
  -> a        -- ^ Arbitrary datatype to return
  -> a        -- ^ Returned data
#if defined(VERBOSE)
log Verbose s = trace ("VERBOSE: " ++ s)
#endif
#if defined(DEBUG) || defined(VERBOSE)
log Debug s = trace ("DEBUG: " ++ s)
#endif
#if defined(WARN) || defined(DEBUG) || defined(VERBOSE)
log Warn s = trace ("WARN: " ++ s)
#endif
#if defined(ERROR) || defined(WARN) || defined(DEBUG) || defined(VERBOSE)
log Error s = trace ("ERROR: " ++ s)
#endif
log _ _ = id

-- | Manadic logging function residing in the 'IO' Monad
logIO
  :: LogLevel -- ^ Log level to log to
  -> String   -- ^ The message string
  -> IO ()
#if defined(VERBOSE)
logIO Verbose s = traceIO ("VERBOSE: " ++ s)
#endif
#if defined(DEBUG) || defined(VERBOSE)
logIO Debug s = traceIO ("DEBUG: " ++ s)
#endif
#if defined(WARN) || defined(DEBUG) || defined(VERBOSE)
logIO Warn s = traceIO ("WARN: " ++ s)
#endif
#if defined(ERROR) || defined(WARN) || defined(DEBUG) || defined(VERBOSE)
logIO Error s = traceIO ("ERROR: " ++ s)
#endif
logIO _ _ = return ()