{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} module LoggingTest.ConfigSpec ( spec ) where import Data.Aeson as Json #if MIN_VERSION_aeson(1, 4, 3) import Data.Aeson.QQ.Simple (aesonQQ) #else import Data.Aeson.QQ (aesonQQ) #endif import Data.ByteString (ByteString, pack, writeFile) import Data.ByteString.Lazy (unpack) import qualified Data.Map as M import Data.Yaml as Yaml import Data.Yaml.TH import Prelude hiding (writeFile) import System.Directory import Test.Hspec import Test.Hspec.QuickCheck import Logging.Config.Json as Json import Logging.Config.Yaml as Yaml import Logging.Manager import Logging.Sink spec :: Spec spec = beforeAll_ prepare $ describe "Config & Manager" $ modifyMaxSize (const 1000) $ do it "json" $ do Manager{..} <- Json.getManager jsonRaw length sinks `shouldBe` 1 M.member "MyLogger" sinks `shouldBe` True disabled `shouldBe` False it "yaml" $ do Manager{..} <- Yaml.getManager yamlRaw length sinks `shouldBe` 1 M.member "MyLogger" sinks `shouldBe` True disabled `shouldBe` False it "json file" $ do Manager{..} <- Json.getManagerFile "/tmp/log4hs/config.json" length sinks `shouldBe` 1 M.member "MyLogger" sinks `shouldBe` True disabled `shouldBe` False it "yaml file" $ do Manager{..} <- Yaml.getManagerFile "/tmp/log4hs/config.yaml" length sinks `shouldBe` 1 M.member "MyLogger" sinks `shouldBe` True disabled `shouldBe` False it "root sink" $ do Sink{..} <- root <$> (Json.getManager jsonRaw) logger `shouldBe` "" level `shouldBe` "DEBUG" disabled `shouldBe` False propagate `shouldBe` False length filterer `shouldBe` 0 length handlers `shouldBe` 1 it "sinks" $ do Sink{..} <- (flip (M.!) "MyLogger" . sinks) <$> (Json.getManager jsonRaw) logger `shouldBe` "MyLogger" level `shouldBe` "INFO" propagate `shouldBe` False disabled `shouldBe` False length filterer `shouldBe` 1 filterer == ["MyLogger.Main"] `shouldBe` True length handlers `shouldBe` 2 prepare :: IO () prepare = do createDirectoryIfMissing False "/tmp/log4hs" writeFile "/tmp/log4hs/config.json" jsonRaw writeFile "/tmp/log4hs/config.yaml" yamlRaw jsonRaw :: ByteString jsonRaw = pack $ unpack $ Json.encode [aesonQQ|{ "sinks": { "root": { "level": "DEBUG", "handlers": ["console"], "propagate": false }, "MyLogger": { "level": "INFO", "filterer": ["MyLogger.Main"], "handlers": ["console", "file"], "propagate": false } }, "handlers": { "console": { "type": "StreamHandler", "stream": "stderr", "level": "DEBUG", "formatter": "default" }, "file": { "type": "FileHandler", "level": "INFO", "formatter": "default", "file": "./default.log" } }, "formatters": { "default": "{asctime} - {level} - {logger}:{lineno}] {message}" }, "catchUncaughtException": true }|] yamlRaw :: ByteString yamlRaw = Yaml.encode [yamlQQ| sinks: root: level: DEBUG handlers: - console propagate: false MyLogger: level: INFO filterer: - MyLogger.Main handlers: - console - file propagate: false handlers: console: type: StreamHandler stream: stderr level: DEBUG formatter: default file: type: FileHandler level: INFO formatter: default file: "./default.log" formatters: default: "{asctime} - {level} - {logger}:{lineno}] {message}" catchUncaughtException: true |]