blob: 27440dc45dece40950f5e03e97b7f4f46f2f0587 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
|
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Core.Rules.Tests
( tests
) where
--------------------------------------------------------------------------------
import qualified Data.Set as S
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.HUnit (testCase)
import Test.HUnit (Assertion, assert, (@=?))
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
import Hakyll.Core.Routes
import Hakyll.Core.Rules
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Writable.CopyFile
import Hakyll.Web.Pandoc
import TestSuite.Util
--------------------------------------------------------------------------------
tests :: Test
tests = testGroup "Hakyll.Core.Rules.Tests"
[ testCase "runRules" rulesTest
]
--------------------------------------------------------------------------------
rulesTest :: Assertion
rulesTest = withTestStore $ \store -> do
provider <- newTestProvider store
ruleSet <- runRules rules provider
let identifiers = S.fromList $ map fst $ rulesCompilers ruleSet
routes = rulesRoutes ruleSet
-- Test that we have some identifiers and that the routes work out
assert $ all (`S.member` identifiers) expected
Just "example.html" @=? runRoutes routes "example.md"
Just "example.md" @=? runRoutes routes (sv "raw" "example.md")
Just "example.md" @=? runRoutes routes (sv "nav" "example.md")
where
sv g = setVersion (Just g)
expected =
[ "example.md"
, "russian.md"
, sv "raw" "example.md"
, sv "raw" "russian.md"
, sv "nav" "example.md"
]
--------------------------------------------------------------------------------
rules :: Rules ()
rules = do
-- Compile some posts
match "*.md" $ do
route $ setExtension "html"
compile pandocCompiler
-- Compile them, raw
match "*.md" $ version "raw" $ do
route idRoute
compile getResourceString
-- Regression test
version "nav" $ match (fromList ["example.md"]) $ do
route idRoute
compile copyFileCompiler
|