@@ -15,15 +15,15 @@ import Test.Hspec.QuickCheck (modifyMaxSize, modifyMaxSuccess)
15
15
import Test.QuickCheck (Property , property )
16
16
import Test.QuickCheck.Monadic (assert , monadicIO , run )
17
17
18
+ import Pos.Util.Log
19
+ import Pos.Util.Log.Internal (getLinesLogged )
18
20
import Pos.Util.Log.LoggerConfig (BackendKind (.. ), LogHandler (.. ),
19
21
LogSecurityLevel (.. ), LoggerConfig (.. ), LoggerTree (.. ),
20
22
defaultInteractiveConfiguration , defaultTestConfiguration ,
21
23
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 (.. ))
27
27
28
28
{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-}
29
29
@@ -48,30 +48,26 @@ prop_lines =
48
48
monadicIO $ do
49
49
let n0 = 20
50
50
n1 = 1
51
- (_, linesLogged ) <- run (run_logging Debug 10 n0 n1)
51
+ (_, lineslogged ) <- run (run_logging Debug 10 n0 n1)
52
52
-- 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 )
55
54
56
- {-
57
55
-- | Count as many lines as you intended to log.
58
56
prop_sev :: Property
59
57
prop_sev =
60
58
monadicIO $ do
61
59
let n0 = 20
62
60
n1 = 1
63
- (_, linesLogged ) <- run (run_logging Warning 10 n0 n1)
61
+ (_, lineslogged ) <- run (run_logging Warning 10 n0 n1)
64
62
-- 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
+
68
65
run_logging :: Severity -> Int -> Integer -> Integer -> IO (Microsecond , Integer )
69
- run_logging _ n n0 n1= do
66
+ run_logging sev n n0 n1= do
70
67
startTime <- getPOSIXTime
71
- -- setupLogging $ defaultTestConfiguration sev
72
- lineslogged0 <- getLinesLogged
68
+ lh <- setupLogging $ defaultTestConfiguration sev
73
69
forM_ [1 .. n0] $ \ _ ->
74
- usingLoggerName " test_log" $
70
+ usingLoggerName lh " test_log" $
75
71
forM_ [1 .. n1] $ \ _ -> do
76
72
logDebug msg
77
73
logInfo msg
@@ -82,29 +78,27 @@ run_logging _ n n0 n1= do
82
78
threadDelay $ fromIntegral (5000 * n0)
83
79
let diffTime = nominalDiffTimeToMicroseconds (endTime - startTime)
84
80
putStrLn $ " time for " ++ (show (n0* n1)) ++ " iterations: " ++ (show diffTime)
85
- lineslogged1 <- getLinesLogged
86
- let lineslogged = lineslogged1 - lineslogged0
81
+ lineslogged <- getLinesLogged lh
87
82
putStrLn $ " lines logged :" ++ (show lineslogged)
88
83
return (diffTime, lineslogged)
89
84
where msg :: Text
90
85
msg = replicate n " abcdefghijklmnopqrstuvwxyz"
91
86
92
- {-
93
87
prop_sevS :: Property
94
88
prop_sevS =
95
89
monadicIO $ do
96
90
let n0 = 200
97
91
n1 = 1
98
- (_, linesLogged ) <- run (run_loggingS Warning 10 n0 n1)
92
+ (_, lineslogged ) <- run (run_loggingS Warning 10 n0 n1)
99
93
-- multiply by 2 because Debug, Info and Notice messages must not be logged
100
- assert (linesLogged == 0)
94
+ assert (lineslogged == 0 )
101
95
102
96
run_loggingS :: Severity -> Int -> Integer -> Integer -> IO (Microsecond , Integer )
103
97
run_loggingS sev n n0 n1= do
104
98
startTime <- getPOSIXTime
105
- -- setupLogging $ defaultTestConfiguration sev
99
+ lh <- setupLogging $ defaultTestConfiguration sev
106
100
forM_ [1 .. n0] $ \ _ ->
107
- usingLoggerName "test_log" $
101
+ usingLoggerName lh " test_log" $
108
102
forM_ [1 .. n1] $ \ _ -> do
109
103
logDebugS lh msg
110
104
logInfoS lh msg
@@ -115,17 +109,17 @@ run_loggingS sev n n0 n1= do
115
109
threadDelay 0500000
116
110
let diffTime = nominalDiffTimeToMicroseconds (endTime - startTime)
117
111
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 )
121
115
where msg :: Text
122
116
msg = replicate n " ABCDEFGHIJKLMNOPQRSTUVWXYZ"
123
- -}
117
+
124
118
-- | example: setup logging
125
119
example_setup :: IO ()
126
120
example_setup = do
127
- -- setupLogging (defaultTestConfiguration Debug)
128
- usingLoggerName " processXYZ" $ do
121
+ lh <- setupLogging (defaultTestConfiguration Debug )
122
+ usingLoggerName lh " processXYZ" $ do
129
123
logInfo " entering"
130
124
complexWork " 42"
131
125
logInfo " done."
@@ -135,12 +129,11 @@ example_setup = do
135
129
complexWork m = do
136
130
logDebug $ " let's see: " `append` m
137
131
138
- {-
139
132
-- | example: bracket logging
140
133
example_bracket :: IO ()
141
134
example_bracket = do
142
- setupLogging (defaultTestConfiguration Debug)
143
- loggerBracket "processXYZ" $ do
135
+ lh <- setupLogging (defaultTestConfiguration Debug )
136
+ loggerBracket lh " processXYZ" $ do
144
137
logInfo " entering"
145
138
complexWork " 42"
146
139
logInfo " done."
@@ -150,17 +143,9 @@ example_bracket = do
150
143
complexWork m =
151
144
addLoggerName " in_complex" $ do
152
145
logDebug $ " let's see: " `append` m
153
- -}
146
+
154
147
spec :: Spec
155
148
spec = 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
-
164
149
modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
165
150
it " measure time for logging small messages" $
166
151
property prop_small
@@ -173,24 +158,20 @@ spec = describe "Logging" $ do
173
158
it " lines counted as logged must be equal to how many was intended to be written" $
174
159
property prop_lines
175
160
176
- {-
177
161
modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
178
162
it " Debug, Info and Notice messages must not be logged" $
179
163
property prop_sev
180
- -}
181
164
182
- {- disabled for now
183
165
modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
184
166
it " DebugS, InfoS, NoticeS, WarningS and ErrorS messages must not be logged in public logs" $
185
167
property prop_sevS
186
- -}
168
+
187
169
it " demonstrating setup and initialisation of logging" $
188
170
example_setup
189
171
190
- {- disabled for now
191
172
it " demonstrating bracket logging" $
192
173
example_bracket
193
- -}
174
+
194
175
it " compose default LoggerConfig" $
195
176
((mempty :: LoggerConfig ) <> (LoggerConfig { _lcBasePath = Nothing , _lcRotation = Nothing
196
177
, _lcLoggerTree = mempty }))
@@ -239,13 +220,14 @@ spec = describe "Logging" $ do
239
220
modifyMaxSuccess (const 2 ) $ modifyMaxSize (const 2 ) $
240
221
it " change minimum severity filter for a specific context" $
241
222
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!" }
244
228
lift $ threadDelay 0300000
245
- lift $ usingLoggerName " verbose" $ do { logWarning " now you read this!" }
229
+ lift $ usingLoggerName lh " verbose" $ do { logWarning " now you read this!" }
246
230
lift $ threadDelay 0300000
247
- lineslogged1 <- lift $ getLinesLogged
248
- let lineslogged = lineslogged1 - lineslogged0
249
- putStrLn $ " lines logged: " ++ (show lineslogged)
231
+ lineslogged <- lift $ getLinesLogged lh
250
232
assert (lineslogged == 1 )
251
233
0 commit comments