summaryrefslogtreecommitdiff
path: root/tests/Hakyll/Core/Rules/Tests.hs
blob: e3d9c208b63bb424af54c5283459bda6f56ec76d (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
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Core.Rules.Tests
    ( tests
    ) where


--------------------------------------------------------------------------------
import           Data.IORef                     (IORef, newIORef, readIORef,
                                                 writeIORef)
import qualified Data.Set                       as S
import           Hakyll.Core.Compiler
import           Hakyll.Core.File
import           Hakyll.Core.Identifier
import           Hakyll.Core.Identifier.Pattern
import           Hakyll.Core.Metadata
import           Hakyll.Core.Routes
import           Hakyll.Core.Rules
import           Hakyll.Core.Rules.Internal
import           Hakyll.Web.Pandoc
import           System.FilePath                ((</>))
import           Test.Tasty                     (TestTree, testGroup)
import           Test.Tasty.HUnit               (Assertion, assert, (@=?))
import           TestSuite.Util


--------------------------------------------------------------------------------
tests :: TestTree
tests = testGroup "Hakyll.Core.Rules.Tests" $ fromAssertions "runRules"
    [case01]


--------------------------------------------------------------------------------
case01 :: Assertion
case01 = do
    ioref    <- newIORef False
    store    <- newTestStore
    provider <- newTestProvider store
    ruleSet  <- runRules (rules01 ioref) provider
    let identifiers     = S.fromList $ map fst $ rulesCompilers ruleSet
        routes          = rulesRoutes ruleSet
        checkRoute ex i =
            runRoutes routes provider i >>= \(r, _) -> Just ex @=? r

    -- Test that we have some identifiers and that the routes work out
    S.fromList expected @=? identifiers
    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")
    checkRoute "food/example.md" (sv "metadataMatch" "example.md")
    readIORef ioref >>= assert
    cleanTestEnv
  where
    sv g     = setVersion (Just g)
    expected =
        [                    "example.md"
        , sv "raw"           "example.md"
        , sv "metadataMatch" "example.md"
        , sv "nav"           "example.md"
        , sv "mv1"           "example.md"
        , sv "mv2"           "example.md"

        ,          "russian.md"
        , sv "raw" "russian.md"
        , sv "mv1" "russian.md"
        , sv "mv2" "russian.md"
        ]


--------------------------------------------------------------------------------
rules01 :: IORef Bool -> Rules ()
rules01 ioref = do
    -- Compile some posts
    match "*.md" $ do
        route $ setExtension "html"
        compile pandocCompiler

    -- Yeah. I don't know how else to test this stuff?
    preprocess $ writeIORef ioref True

    -- Compile them, raw
    match "*.md" $ version "raw" $ do
        route idRoute
        compile getResourceString

    version "metadataMatch" $
        matchMetadata "*.md" (\md -> lookupString "subblog" md == Just "food") $ do
            route $ customRoute $ \id' -> "food" </> toFilePath id'
            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