Skip to content

Commit

Permalink
Add Log tests
Browse files Browse the repository at this point in the history
  • Loading branch information
memowe committed Aug 14, 2024
1 parent 2af3046 commit 3d2c645
Show file tree
Hide file tree
Showing 4 changed files with 63 additions and 1 deletion.
3 changes: 2 additions & 1 deletion lib/LiBro/Log.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@ module LiBro.Log where
import Text.Printf
import Data.Time.Clock

data LogLevel = INFO | WARNING | ERROR | FATAL deriving (Eq, Ord, Show)
data LogLevel = INFO | WARNING | ERROR | FATAL
deriving (Eq, Ord, Enum, Bounded, Show)
type LogSource = String
type LogMessage = String
data Log = Log
Expand Down
2 changes: 2 additions & 0 deletions libro-backend.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ test-suite libro-backend-test
other-modules: LiBro.TestUtil
, LiBro.TestUtilSpec
, LiBro.ConfigSpec
, LiBro.LogSpec
, LiBro.DataSpec
, LiBro.Data.StorageSpec
, LiBro.Data.SafeTextSpec
Expand All @@ -102,5 +103,6 @@ test-suite libro-backend-test
, silently
, temporary
, text
, time
, transformers
, vector
57 changes: 57 additions & 0 deletions test/LiBro/LogSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,57 @@
module LiBro.LogSpec where

import Test.Hspec
import Test.QuickCheck
import Test.Hspec.QuickCheck

import LiBro.Base
import LiBro.Log
import Data.Default
import Data.Time.Clock
import Data.Tuple.Extra

spec :: Spec
spec = describe "Logging" $ do
format
collection

format :: Spec
format = describe "Log format" $ do

describe "Show instance" $ do
now <- runIO getCurrentTime
it "Correct log stringification" $
show (Log now WARNING "foo" "bar")
`shouldBe` "WARNING [" ++ show now ++ "] (foo): bar"

describe "Within LiBroIO monad" $ do
now <- runIO getCurrentTime
(_, logs) <- runIO $ runLiBroIOLogs def $ addLog WARNING "foo" "bar"
it "Exactly one log" $ length logs == 1
let l = head logs
it "Correct log level" $ level l `shouldBe` WARNING
it "Correct log source" $ source l `shouldBe` "foo"
it "Correct log message" $ message l `shouldBe` "bar"
it "Logged time is close enough" $
(time l `diffUTCTime` now) `shouldSatisfy` (< 0.42)

genLogData :: Gen (LogLevel, LogSource, LogMessage)
genLogData = (,,) <$> chooseEnum (minBound, maxBound)
<*> arbitrary
<*> arbitrary

collection :: Spec
collection = describe "Collection of logs" $ do

prop "Correct list of logs" $
forAll (listOf genLogData) $ \lds -> ioProperty $ do
(_, logs) <- runLiBroIOLogs def $ uncurry3 addLog `mapM_` lds
let logTuples = map ((,,) <$> level <*> source <*> message) logs
logTuples `shouldBe` lds

prop "Ordered by time" $
forAll (listOf genLogData) $ \lds -> ioProperty $ do
(_, logs) <- runLiBroIOLogs def $ uncurry3 addLog `mapM_` lds
time <$> logs `shouldSatisfy` isSorted

where isSorted = and . (zipWith (<=) <*> tail)
2 changes: 2 additions & 0 deletions test/run-all-tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module Main where
import Test.Hspec
import LiBro.Util

import qualified LiBro.LogSpec as Log
import qualified LiBro.DataSpec as Data
import qualified LiBro.Data.SafeTextSpec as Data.SafeText
import qualified LiBro.Data.StorageSpec as Data.Storage
Expand All @@ -24,6 +25,7 @@ withLibreOffice runTests = do

main :: IO ()
main = hspec $ aroundAll_ withLibreOffice $ do
Log.spec
Data.spec
Data.SafeText.spec
Data.Storage.spec
Expand Down

0 comments on commit 3d2c645

Please sign in to comment.