Skip to content
Snippets Groups Projects
Commit d34bd2d7 authored by Jens Nolte's avatar Jens Nolte
Browse files

Add test for ObservablePriority

parent 7bcfa0ee
No related branches found
No related tags found
No related merge requests found
module Qd.Observable.ObservablePrioritySpec where
import Qd.Observable
import Qd.Observable.ObservablePriority (ObservablePriority)
import qualified Qd.Observable.ObservablePriority as OP
import Control.Monad (void)
import Data.IORef
import Test.Hspec
spec :: Spec
spec = do
describe "ObservablePriority" $ parallel $ do
it "can be created" $ do
void $ OP.create
specify "getValue returns the value with the highest priority" $ do
(op :: ObservablePriority Int String) <- OP.create
p2 <- OP.insertValue op 2 "p2"
getValue op `shouldReturn` (Just "p2")
p1 <- OP.insertValue op 1 "p1"
getValue op `shouldReturn` (Just "p2")
deregister p2
getValue op `shouldReturn` (Just "p1")
deregister p1
getValue op `shouldReturn` (Nothing)
it "sends updates when its value changes" $ do
result <- newIORef []
let mostRecentShouldBe = (head <$> readIORef result `shouldReturn`)
(op :: ObservablePriority Int String) <- OP.create
_s <- subscribe op (modifyIORef result . (:))
readIORef result `shouldReturn` ([(Current, Nothing)])
p2 <- OP.insertValue op 2 "p2"
mostRecentShouldBe (Update, Just "p2")
p1 <- OP.insertValue op 1 "p1"
mostRecentShouldBe (Update, Just "p2")
deregister p2
mostRecentShouldBe (Update, Just "p1")
deregister p1
mostRecentShouldBe (Update, Nothing)
length <$> readIORef result `shouldReturn` 4
main :: IO ()
main = putStrLn "Test suite not yet implemented"
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment