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

95 lines
3.1 KiB
Haskell
Raw Normal View History

2012-11-26 15:11:37 +00:00
--------------------------------------------------------------------------------
2011-05-24 12:40:45 +00:00
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Core.Rules.Tests
2011-05-24 21:17:32 +00:00
( tests
) where
2011-05-24 12:40:45 +00:00
2012-11-26 15:11:37 +00:00
--------------------------------------------------------------------------------
2013-01-08 11:47:55 +00:00
import Data.IORef (IORef, newIORef, readIORef,
writeIORef)
2012-11-26 15:11:37 +00:00
import qualified Data.Set as S
import Test.Framework (Test, testGroup)
import Test.HUnit (Assertion, assert, (@=?))
2011-05-24 12:40:45 +00:00
2012-11-26 15:11:37 +00:00
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
2013-01-06 17:33:00 +00:00
import Hakyll.Core.File
2012-11-26 15:11:37 +00:00
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
2012-11-26 15:11:37 +00:00
import Hakyll.Core.Routes
import Hakyll.Core.Rules
import Hakyll.Core.Rules.Internal
2012-12-15 17:02:47 +00:00
import Hakyll.Web.Pandoc
2012-11-26 15:11:37 +00:00
import TestSuite.Util
--------------------------------------------------------------------------------
tests :: Test
2013-02-16 11:59:38 +00:00
tests = testGroup "Hakyll.Core.Rules.Tests" $ fromAssertions "runRules"
[case01]
2011-05-24 20:29:47 +00:00
2012-11-26 15:11:37 +00:00
--------------------------------------------------------------------------------
2013-02-16 11:59:38 +00:00
case01 :: Assertion
case01 = do
2013-01-08 11:47:55 +00:00
ioref <- newIORef False
2013-01-06 17:33:00 +00:00
store <- newTestStore
2012-11-26 15:11:37 +00:00
provider <- newTestProvider store
2013-02-16 11:59:38 +00:00
ruleSet <- runRules (rules01 ioref) provider
2013-01-21 21:45:50 +00:00
let identifiers = S.fromList $ map fst $ rulesCompilers ruleSet
routes = rulesRoutes ruleSet
checkRoute ex i =
2013-05-03 09:35:31 +00:00
runRoutes routes provider i >>= \(r, _) -> Just ex @=? r
2012-11-26 15:11:37 +00:00
-- Test that we have some identifiers and that the routes work out
assert $ all (`S.member` identifiers) expected
2013-01-21 21:45:50 +00:00
checkRoute "example.html" "example.md"
checkRoute "example.md" (sv "raw" "example.md")
checkRoute "example.md" (sv "nav" "example.md")
checkRoute "example.mv1" (sv "mv1" "example.md")
checkRoute "example.mv2" (sv "mv2" "example.md")
2013-01-08 11:47:55 +00:00
readIORef ioref >>= assert
2013-02-09 14:11:40 +00:00
cleanTestEnv
2011-05-24 20:29:47 +00:00
where
sv g = setVersion (Just g)
2012-11-26 15:11:37 +00:00
expected =
[ "example.md"
, "russian.md"
, sv "raw" "example.md"
, sv "raw" "russian.md"
, sv "nav" "example.md"
2011-05-24 20:29:47 +00:00
]
2011-05-24 12:40:45 +00:00
2012-11-26 15:11:37 +00:00
--------------------------------------------------------------------------------
2013-02-16 11:59:38 +00:00
rules01 :: IORef Bool -> Rules ()
rules01 ioref = do
2011-05-24 12:40:45 +00:00
-- Compile some posts
2012-11-26 15:11:37 +00:00
match "*.md" $ do
2011-05-24 12:40:45 +00:00
route $ setExtension "html"
2012-12-15 17:02:47 +00:00
compile pandocCompiler
2011-05-24 12:40:45 +00:00
2013-01-08 11:47:55 +00:00
-- Yeah. I don't know how else to test this stuff?
preprocess $ writeIORef ioref True
2011-05-24 12:40:45 +00:00
-- Compile them, raw
2012-11-26 15:11:37 +00:00
match "*.md" $ version "raw" $ do
2011-05-24 20:29:47 +00:00
route idRoute
2012-11-26 15:11:37 +00:00
compile getResourceString
-- Regression test
version "nav" $ match (fromList ["example.md"]) $ do
route idRoute
compile copyFileCompiler
-- Another edge case: different versions in one match
match "*.md" $ do
version "mv1" $ do
route $ setExtension "mv1"
compile getResourceString
version "mv2" $ do
route $ setExtension "mv2"
compile getResourceString