@@ -15,15 +15,15 @@ import Test.Hspec.QuickCheck (modifyMaxSize, modifyMaxSuccess)
1515import Test.QuickCheck (Property , property )
1616import Test.QuickCheck.Monadic (assert , monadicIO , run )
1717
18+ import Pos.Util.Log
19+ import Pos.Util.Log.Internal (getLinesLogged )
1820import Pos.Util.Log.LoggerConfig (BackendKind (.. ), LogHandler (.. ),
1921 LogSecurityLevel (.. ), LoggerConfig (.. ), LoggerTree (.. ),
2022 defaultInteractiveConfiguration , defaultTestConfiguration ,
2123 lcLoggerTree , ltMinSeverity , ltNamedSeverity )
22- import Pos.Util.Wlog (Severity (.. ), WithLogger , getLinesLogged ,
23- logDebug , logError , logInfo , logNotice , logWarning ,
24- setupLogging , usingLoggerName )
25- -- import Pos.Util.Log.LogSafe (logDebugS, logErrorS, logInfoS,
26- -- logNoticeS, logWarningS)
24+ import Pos.Util.Log.LogSafe (logDebugS , logErrorS , logInfoS ,
25+ logNoticeS , logWarningS )
26+ import Pos.Util.Log.Severity (Severity (.. ))
2727
2828{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-}
2929
@@ -48,30 +48,26 @@ prop_lines =
4848 monadicIO $ do
4949 let n0 = 20
5050 n1 = 1
51- (_, linesLogged ) <- run (run_logging Debug 10 n0 n1)
51+ (_, lineslogged ) <- run (run_logging Debug 10 n0 n1)
5252 -- multiply by 5 because we log 5 different messages (n0 * n1) times
53- assert (linesLogged == n0 * n1 * 5 )
54- -- assert (linesLogged >= n0 * n1 * 5 `div` 2) -- weaker
53+ assert (lineslogged == n0 * n1 * 5 )
5554
56- {-
5755-- | Count as many lines as you intended to log.
5856prop_sev :: Property
5957prop_sev =
6058 monadicIO $ do
6159 let n0 = 20
6260 n1 = 1
63- (_, linesLogged ) <- run (run_logging Warning 10 n0 n1)
61+ (_, lineslogged ) <- run (run_logging Warning 10 n0 n1)
6462 -- multiply by 2 because Debug, Info and Notice messages must not be logged
65- assert (linesLogged == n0 * n1 * 2)
66- -- assert (linesLogged >= n0 * n1 * 2 `div` 2) -- weaker
67- -}
63+ assert (lineslogged == n0 * n1 * 2 )
64+
6865run_logging :: Severity -> Int -> Integer -> Integer -> IO (Microsecond , Integer )
69- run_logging _ n n0 n1= do
66+ run_logging sev n n0 n1= do
7067 startTime <- getPOSIXTime
71- -- setupLogging $ defaultTestConfiguration sev
72- lineslogged0 <- getLinesLogged
68+ lh <- setupLogging $ defaultTestConfiguration sev
7369 forM_ [1 .. n0] $ \ _ ->
74- usingLoggerName " test_log" $
70+ usingLoggerName lh " test_log" $
7571 forM_ [1 .. n1] $ \ _ -> do
7672 logDebug msg
7773 logInfo msg
@@ -82,29 +78,27 @@ run_logging _ n n0 n1= do
8278 threadDelay $ fromIntegral (5000 * n0)
8379 let diffTime = nominalDiffTimeToMicroseconds (endTime - startTime)
8480 putStrLn $ " time for " ++ (show (n0* n1)) ++ " iterations: " ++ (show diffTime)
85- lineslogged1 <- getLinesLogged
86- let lineslogged = lineslogged1 - lineslogged0
81+ lineslogged <- getLinesLogged lh
8782 putStrLn $ " lines logged :" ++ (show lineslogged)
8883 return (diffTime, lineslogged)
8984 where msg :: Text
9085 msg = replicate n " abcdefghijklmnopqrstuvwxyz"
9186
92- {-
9387prop_sevS :: Property
9488prop_sevS =
9589 monadicIO $ do
9690 let n0 = 200
9791 n1 = 1
98- (_, linesLogged ) <- run (run_loggingS Warning 10 n0 n1)
92+ (_, lineslogged ) <- run (run_loggingS Warning 10 n0 n1)
9993 -- multiply by 2 because Debug, Info and Notice messages must not be logged
100- assert (linesLogged == 0)
94+ assert (lineslogged == 0 )
10195
10296run_loggingS :: Severity -> Int -> Integer -> Integer -> IO (Microsecond , Integer )
10397run_loggingS sev n n0 n1= do
10498 startTime <- getPOSIXTime
105- -- setupLogging $ defaultTestConfiguration sev
99+ lh <- setupLogging $ defaultTestConfiguration sev
106100 forM_ [1 .. n0] $ \ _ ->
107- usingLoggerName "test_log" $
101+ usingLoggerName lh " test_log" $
108102 forM_ [1 .. n1] $ \ _ -> do
109103 logDebugS lh msg
110104 logInfoS lh msg
@@ -115,17 +109,17 @@ run_loggingS sev n n0 n1= do
115109 threadDelay 0500000
116110 let diffTime = nominalDiffTimeToMicroseconds (endTime - startTime)
117111 putStrLn $ " time for " ++ (show (n0* n1)) ++ " iterations: " ++ (show diffTime)
118- linesLogged <- getLinesLogged
119- putStrLn $ " lines logged :" ++ (show linesLogged )
120- return (diffTime, linesLogged )
112+ lineslogged <- getLinesLogged lh
113+ putStrLn $ " lines logged :" ++ (show lineslogged )
114+ return (diffTime, lineslogged )
121115 where msg :: Text
122116 msg = replicate n " ABCDEFGHIJKLMNOPQRSTUVWXYZ"
123- -}
117+
124118-- | example: setup logging
125119example_setup :: IO ()
126120example_setup = do
127- -- setupLogging (defaultTestConfiguration Debug)
128- usingLoggerName " processXYZ" $ do
121+ lh <- setupLogging (defaultTestConfiguration Debug )
122+ usingLoggerName lh " processXYZ" $ do
129123 logInfo " entering"
130124 complexWork " 42"
131125 logInfo " done."
@@ -135,12 +129,11 @@ example_setup = do
135129 complexWork m = do
136130 logDebug $ " let's see: " `append` m
137131
138- {-
139132-- | example: bracket logging
140133example_bracket :: IO ()
141134example_bracket = do
142- setupLogging (defaultTestConfiguration Debug)
143- loggerBracket "processXYZ" $ do
135+ lh <- setupLogging (defaultTestConfiguration Debug )
136+ loggerBracket lh " processXYZ" $ do
144137 logInfo " entering"
145138 complexWork " 42"
146139 logInfo " done."
@@ -150,17 +143,9 @@ example_bracket = do
150143 complexWork m =
151144 addLoggerName " in_complex" $ do
152145 logDebug $ " let's see: " `append` m
153- -}
146+
154147spec :: Spec
155148spec = describe " Logging" $ do
156- modifyMaxSuccess (const 1 ) $ modifyMaxSize (const 1 ) $
157- it " setup logging" $
158- monadicIO $ do
159- let lc0 = defaultTestConfiguration Debug
160- newlt = lc0 ^. lcLoggerTree & ltNamedSeverity .~ HM. fromList [(" cardano-sl.silent" , Error )]
161- lc = lc0 & lcLoggerTree .~ newlt
162- setupLogging lc
163-
164149 modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
165150 it " measure time for logging small messages" $
166151 property prop_small
@@ -173,24 +158,20 @@ spec = describe "Logging" $ do
173158 it " lines counted as logged must be equal to how many was intended to be written" $
174159 property prop_lines
175160
176- {-
177161 modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
178162 it " Debug, Info and Notice messages must not be logged" $
179163 property prop_sev
180- -}
181164
182- {- disabled for now
183165 modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
184166 it " DebugS, InfoS, NoticeS, WarningS and ErrorS messages must not be logged in public logs" $
185167 property prop_sevS
186- -}
168+
187169 it " demonstrating setup and initialisation of logging" $
188170 example_setup
189171
190- {- disabled for now
191172 it " demonstrating bracket logging" $
192173 example_bracket
193- -}
174+
194175 it " compose default LoggerConfig" $
195176 ((mempty :: LoggerConfig ) <> (LoggerConfig { _lcBasePath = Nothing , _lcRotation = Nothing
196177 , _lcLoggerTree = mempty }))
@@ -239,13 +220,14 @@ spec = describe "Logging" $ do
239220 modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
240221 it " change minimum severity filter for a specific context" $
241222 monadicIO $ do
242- lineslogged0 <- lift $ getLinesLogged
243- lift $ usingLoggerName " silent" $ do { logWarning " you won't see this!" }
223+ let lc0 = defaultTestConfiguration Info
224+ newlt = lc0 ^. lcLoggerTree & ltNamedSeverity .~ HM. fromList [(" cardano-sl.silent" , Error )]
225+ lc = lc0 & lcLoggerTree .~ newlt
226+ lh <- setupLogging lc
227+ lift $ usingLoggerName lh " silent" $ do { logWarning " you won't see this!" }
244228 lift $ threadDelay 0300000
245- lift $ usingLoggerName " verbose" $ do { logWarning " now you read this!" }
229+ lift $ usingLoggerName lh " verbose" $ do { logWarning " now you read this!" }
246230 lift $ threadDelay 0300000
247- lineslogged1 <- lift $ getLinesLogged
248- let lineslogged = lineslogged1 - lineslogged0
249- putStrLn $ " lines logged: " ++ (show lineslogged)
231+ lineslogged <- lift $ getLinesLogged lh
250232 assert (lineslogged == 1 )
251233
0 commit comments