{-# LANGUAGE RecordWildCards #-}

module Logging.Manager
  ( Manager(..)
  , initialize
  , terminate
  ) where

import           Data.List             (nub)
import           Data.Map.Lazy         (Map, elems)
import           Data.Time.LocalTime

import           Logging.Class.Handler
import           Logging.Sink


-- |Logging 'Manager' which holds the hierarchy of sinks and other settings.
--
-- Since v0.7.0, the 'TimeZone' of the logging environment can be configurable.
data Manager = Manager { root                   :: Sink
                       , sinks                  :: Map String Sink
                       , timezone               :: TimeZone -- ^ @since 0.7.0
                       , disabled               :: Bool
                       , catchUncaughtException :: Bool
                         -- ^ Since 0.8.0, unhandled
                         -- 'Exception's are logged only in the global
                         -- logging environment.
                       }

{-# DEPRECATED catchUncaughtException "Will be removed" #-}


-- | Initialize a 'Manager', open all its handlers.
initialize :: Manager -> IO ()
initialize Manager{..} = mapM_ open $
  nub $ concat [ handlers | Sink{..} <- (root : (elems sinks)) ]


-- | Terminate a 'Manager', close all its handlers.
terminate :: Manager -> IO ()
terminate Manager{..} = mapM_ close $
  nub $ concat [ handlers | Sink{..} <- (root : (elems sinks)) ]