Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.

Commit 77f2e11

Browse files
committed
[CBR-275] cleanup; revisit tests in 'util'
Signed-off-by: Alexander Diemand <[email protected]>
1 parent 49000f3 commit 77f2e11

File tree

11 files changed

+153
-82
lines changed

11 files changed

+153
-82
lines changed

infra/src/Pos/Infra/Reporting/Wlog.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import qualified Data.ByteString.Lazy as BSL
1818
import Data.Conduit (runConduitRes, yield, (.|))
1919
import Data.Conduit.List (consume)
2020
import qualified Data.Conduit.Lzma as Lzma
21-
import Data.List (isSuffixOf)
21+
import Data.List (isInfixOf)
2222
import qualified Data.Text.IO as TIO
2323
import Data.Time.Clock (getCurrentTime)
2424
import Data.Time.Format (defaultTimeLocale, formatTime)
@@ -66,7 +66,7 @@ readWlogFile logConfig = case mLogFile of
6666
-- first one.
6767
basepath = fromMaybe "./" $ logConfig ^. lcBasePath
6868
allFiles = map ((</> basepath) . snd) $ retrieveLogFiles logConfig
69-
mLogFile = case filter (".pub" `isSuffixOf`) allFiles of
69+
mLogFile = case filter (".json" `isInfixOf`) allFiles of
7070
[] -> Nothing
7171
(f:_) -> Just f
7272
-- 2 megabytes, assuming we use chars which are ASCII mostly

lib/src/Pos/Launcher/Resource.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ import Pos.Launcher.Param (BaseParams (..), LoggingParams (..),
6666
NodeParams (..))
6767
import Pos.Util (bracketWithLogging, newInitFuture)
6868
import Pos.Util.Log.LoggerConfig (defaultInteractiveConfiguration)
69-
import Pos.Util.Wlog (LoggerConfig (..), Severity (Debug), WithLogger,
69+
import Pos.Util.Wlog (LoggerConfig (..), Severity (..), WithLogger,
7070
logDebug, logInfo, parseLoggerConfig, removeAllHandlers,
7171
setupLogging)
7272

@@ -243,7 +243,7 @@ getRealLoggerConfig LoggingParams{..} = do
243243
overrideConsoleLog :: LoggerConfig -> LoggerConfig
244244
overrideConsoleLog = case lpConsoleLog of
245245
Nothing -> identity
246-
Just True -> (<>) (defaultInteractiveConfiguration Debug)
246+
Just True -> (<>) (defaultInteractiveConfiguration Info)
247247
-- add output to the console with severity filter >= Info
248248
Just False -> identity
249249

lib/src/Pos/Launcher/Scenario.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -36,8 +36,7 @@ import Pos.Infra.Util.LogSafe (logInfoS)
3636
import Pos.Launcher.Resource (NodeResources (..))
3737
import Pos.Util.AssertMode (inAssertMode)
3838
import Pos.Util.CompileInfo (HasCompileInfo, compileInfo)
39-
import Pos.Util.Wlog (LoggerName (..), WithLogger, askLoggerName,
40-
logInfo)
39+
import Pos.Util.Wlog (WithLogger, askLoggerName, logInfo)
4140
import Pos.Worker (allWorkers)
4241
import Pos.WorkMode.Class (WorkMode)
4342

@@ -98,7 +97,7 @@ runNode' genesisConfig NodeResources {..} workers' plugins' = \diffusion -> do
9897
reportHandler (SomeException e) = do
9998
loggerName <- askLoggerName
10099
let msg = "Worker/plugin with logger name "%shown%" failed with exception: "%shown
101-
reportError $ sformat msg (getLoggerName loggerName) e
100+
reportError $ sformat msg loggerName e
102101
exitFailure
103102

104103
-- | Entry point of full node.

networking/cardano-sl-networking.cabal

+7-6
Original file line numberDiff line numberDiff line change
@@ -45,32 +45,33 @@ Library
4545
, async
4646
, attoparsec
4747
, base
48+
, binary >= 0.8
49+
, bytestring
4850
, cardano-sl-chain
4951
, cardano-sl-core
5052
, cardano-sl-util
5153
, containers
52-
, binary >= 0.8
53-
, bytestring
54+
, ekg-core
55+
, formatting
5456
, formatting
5557
, hashable
5658
, kademlia
5759
, lens
5860
, mtl
61+
, mtl >= 2.2.1
5962
, network
6063
, network-transport
6164
, network-transport-tcp
62-
, mtl >= 2.2.1
6365
, random
64-
, universum
6566
, safe-exceptions
6667
, scientific
6768
, stm
6869
, text
6970
, these
70-
, formatting
7171
, time
7272
, time-units
73-
, ekg-core
73+
, universum
74+
, unordered-containers
7475

7576
hs-source-dirs: src
7677
default-language: Haskell2010

tools/src/launcher/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -323,7 +323,7 @@ main =
323323
, _lhSecurityLevel=Just PublicLogLevel}] ++ xs)) .
324324
set ltMinSeverity Info
325325
logException loggerName . usingLoggerName loggerName $
326-
withConfigurations Nothing Nothing False loConfiguration $ \coreConfig _ _ _ -> do
326+
withConfigurations Nothing Nothing False loConfiguration $ \genesisConfig _ _ _ -> do
327327

328328
-- Generate TLS certificates as needed
329329
generateTlsCertificates loConfiguration loX509ToolPath loTlsPath

util/src/Pos/Util/Log.hs

-1
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@ module Pos.Util.Log
55
-- * Logging
66
Severity (..)
77
, LogContext
8-
, LogContextT
98
, LoggingHandler
109
-- * Compatibility
1110
, CanLog (..)

util/src/Pos/Util/Log/Rotator.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,7 @@ initializeRotator rotation fdesc = do
109109
return stdout -- fallback to standard output in case of exception
110110
hSetBuffering hdl LineBuffering
111111
cursize <- hFileSize hdl
112-
let rottime = addUTCTime (fromInteger $ maxAge * 3600) now
112+
let rottime = addUTCTime (fromInteger $ maxAge * 3600) tsfp
113113
return (hdl, (maxSize - cursize), rottime)
114114
where
115115
fplen = length $ filename fdesc

util/src/Pos/Util/Wlog.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-# LANGUAGE Rank2Types #-}
22

3-
-- | an interface to 'log-warper'
4-
-- functions and types gradually migrate towards 'katip'
3+
-- | a compatible interface to 'log-warper'
4+
-- logging output is directed to 'katip'
55

66
module Pos.Util.Wlog
77
( -- * CanLog

util/src/Pos/Util/Wlog/Compatibility.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ instance CanLog IO where
9090
case mayEnv of
9191
Nothing -> error "logging not yet initialized. Abort."
9292
Just env -> Log.logItem' ()
93-
(K.Namespace [name])
93+
(K.Namespace (T.split (=='.') name))
9494
env
9595
Nothing
9696
(Internal.sev2klog severity)
@@ -284,7 +284,7 @@ logItemS lhandler a ns loc sev cond msg = do
284284

285285
logMCond :: MonadIO m => LoggerName -> Severity -> Text -> SelectionMode -> m ()
286286
logMCond name severity msg cond = do
287-
let ns = K.Namespace [name]
287+
let ns = K.Namespace (T.split (=='.') name)
288288
lh <- liftIO $ readMVar loggingHandler
289289
logItemS lh () ns Nothing (Internal.sev2klog severity) cond $ K.logStr msg
290290

util/test/Test/Pos/Util/LogSpec.hs

+36-54
Original file line numberDiff line numberDiff line change
@@ -15,15 +15,15 @@ import Test.Hspec.QuickCheck (modifyMaxSize, modifyMaxSuccess)
1515
import Test.QuickCheck (Property, property)
1616
import Test.QuickCheck.Monadic (assert, monadicIO, run)
1717

18+
import Pos.Util.Log
19+
import Pos.Util.Log.Internal (getLinesLogged)
1820
import 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.
5856
prop_sev :: Property
5957
prop_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+
6865
run_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-
{-
9387
prop_sevS :: Property
9488
prop_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

10296
run_loggingS :: Severity -> Int -> Integer -> Integer-> IO (Microsecond, Integer)
10397
run_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
125119
example_setup :: IO ()
126120
example_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
140133
example_bracket :: IO ()
141134
example_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+
154147
spec :: Spec
155148
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-
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

Comments
 (0)