Skip to content

Commit

Permalink
test: add property tests for core module
Browse files Browse the repository at this point in the history
Add property tests for NMonad.Core.
  • Loading branch information
d3adb5 committed Sep 18, 2023
1 parent 43455fe commit a795e14
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 2 deletions.
1 change: 1 addition & 0 deletions nmonad.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,7 @@ test-suite nmonad-test
type: exitcode-stdio-1.0
main-is: Spec.hs
other-modules:
NMonad.CoreSpec
Test.NMonad
Paths_nmonad
hs-source-dirs:
Expand Down
38 changes: 38 additions & 0 deletions test/NMonad/CoreSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
{-# LANGUAGE StandaloneDeriving #-}

module NMonad.CoreSpec (spec) where

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

import NMonad.Core

deriving instance Show DBusNotification
deriving instance Eq Expiration
deriving instance Eq Notification

spec :: Spec
spec = do
describe "notificationFromDBus :: DBusNotification -> N Notification" $ do
prop "respects replacesId if set to something other than 0" $ \dbusnotif -> do
replacesId <- generate $ arbitrary `suchThat` (/= 0)
let (DBusNotification an _ ai s b a h t) = dbusnotif
dbusnotif' = DBusNotification an replacesId ai s b a h t
(notification, _, _) <- runGenN $ notificationFromDBus dbusnotif'
identifier notification `shouldBe` replacesId

prop "generates some notification id when replacesId is 0" $ \dbusnotif -> do
let (DBusNotification an _ ai s b a h t) = dbusnotif
dbusnotif' = DBusNotification an 0 ai s b a h t
(notification, finalState, (_, initialState)) <- runGenN $ notificationFromDBus dbusnotif'
identifier notification `shouldNotBe` 0
notificationCount finalState `shouldBe` 1 + notificationCount initialState

describe "addToNotificationsAndReturnId :: Notification -> N Word32" $ do
prop "adds the notification to the state and returns its identifier" $ \notif -> do
(returnedId, finalState, (_, initialState)) <- runGenN $ addToNotificationsAndReturnId notif
notif `shouldNotSatisfy` (`elem` notifications initialState)
notif `shouldSatisfy` (`elem` notifications finalState)
identifier notif `shouldBe` returnedId
3 changes: 1 addition & 2 deletions test/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,2 +1 @@
main :: IO ()
main = putStrLn "Test suite not yet implemented"
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}

0 comments on commit a795e14

Please sign in to comment.