hakyll/tests/Hakyll/Core/Dependencies/Tests.hs

71 lines
2.2 KiB
Haskell
Raw Normal View History

2012-11-12 13:31:33 +00:00
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Core.Dependencies.Tests
( tests
) where
--------------------------------------------------------------------------------
2012-11-20 10:50:22 +00:00
import Data.List (delete)
import qualified Data.Map as M
import qualified Data.Set as S
import Test.Framework (Test, testGroup)
import Test.HUnit (Assertion, (@=?))
2012-11-12 13:31:33 +00:00
--------------------------------------------------------------------------------
import Hakyll.Core.Dependencies
import Hakyll.Core.Identifier
2012-11-20 10:50:22 +00:00
import TestSuite.Util
2012-11-12 13:31:33 +00:00
--------------------------------------------------------------------------------
tests :: Test
2012-11-20 10:50:22 +00:00
tests = testGroup "Hakyll.Core.Dependencies.Tests" $
fromAssertions "analyze" [case01, case02, case03]
2012-11-12 13:31:33 +00:00
--------------------------------------------------------------------------------
2012-11-12 15:10:06 +00:00
oldUniverse :: [Identifier]
2012-11-12 13:31:33 +00:00
oldUniverse = M.keys oldFacts
--------------------------------------------------------------------------------
oldFacts :: DependencyFacts
oldFacts = M.fromList
[ ("posts/01.md",
[])
, ("posts/02.md",
[])
, ("index.md",
2012-11-19 13:59:55 +00:00
[ PatternDependency "posts/*" ["posts/01.md", "posts/02.md"]
, IdentifierDependency "posts/01.md"
, IdentifierDependency "posts/02.md"
2012-11-12 13:31:33 +00:00
])
]
--------------------------------------------------------------------------------
-- | posts/02.md has changed
case01 :: Assertion
case01 = S.fromList ["posts/02.md", "index.md"] @=? ood
where
(ood, _, _) = outOfDate oldUniverse (S.singleton "posts/02.md") oldFacts
--------------------------------------------------------------------------------
-- | about.md was added
case02 :: Assertion
case02 = S.singleton "about.md" @=? ood
where
(ood, _, _) = outOfDate ("about.md" : oldUniverse) S.empty oldFacts
--------------------------------------------------------------------------------
-- | posts/01.md was removed
case03 :: Assertion
case03 = S.singleton "index.md" @=? ood
where
(ood, _, _) =
outOfDate ("posts/01.md" `delete` oldUniverse) S.empty oldFacts