summaryrefslogtreecommitdiff
path: root/tests/Hakyll/Web/Template/Tests.hs
blob: 054a9bd63c3d512fed6d8b53b1e1512ddb3d77a6 (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
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Web.Template.Tests
    ( tests
    ) where


--------------------------------------------------------------------------------
import           Test.Tasty                   (TestTree, testGroup)
import           Test.Tasty.HUnit             (Assertion, testCase, (@=?),
                                               (@?=))


--------------------------------------------------------------------------------
import           Hakyll.Core.Compiler
import           Hakyll.Core.Identifier
import           Hakyll.Core.Item
import           Hakyll.Core.Provider
import           Hakyll.Web.Pandoc
import           Hakyll.Web.Template
import           Hakyll.Web.Template.Context
import           Hakyll.Web.Template.Internal
import           Hakyll.Web.Template.List
import           TestSuite.Util


--------------------------------------------------------------------------------
tests :: TestTree
tests = testGroup "Hakyll.Core.Template.Tests" $ concat
    [ [ testCase "case01" $ test ("template.html.out", "template.html", "example.md")
      , testCase "case02" $ test ("strip.html.out", "strip.html", "example.md")
      , testCase "case03" $ test ("just-meta.html.out", "just-meta.html", "example.md")
      , testCase "applyJoinTemplateList" testApplyJoinTemplateList
      ]

    , fromAssertions "readTemplate"
        [ [Chunk "Hello ", Expr (Call "guest" [])]
            @=? readTemplateElems "Hello $guest()$"
        , [If (Call "a" [StringLiteral "bar"]) [Chunk "foo"] Nothing]
            @=? readTemplateElems "$if(a(\"bar\"))$foo$endif$"
        -- 'If' trim check.
        , [ TrimL
          , If (Ident (TemplateKey "body"))
               [ TrimR
               , Chunk "\n"
               , Expr (Ident (TemplateKey "body"))
               , Chunk "\n"
               , TrimL
               ]
               (Just [ TrimR
                     , Chunk "\n"
                     , Expr (Ident (TemplateKey "body"))
                     , Chunk "\n"
                     , TrimL
                     ])
          , TrimR
          ]
          @=? readTemplateElems "$-if(body)-$\n$body$\n$-else-$\n$body$\n$-endif-$"
        -- 'For' trim check.
        , [ TrimL
          , For (Ident (TemplateKey "authors"))
                [TrimR, Chunk "\n   body   \n", TrimL]
                Nothing
          , TrimR
          ]
          @=? readTemplateElems "$-for(authors)-$\n   body   \n$-endfor-$"
        -- 'Partial' trim check.
        , [ TrimL
          , Partial (StringLiteral "path")
          , TrimR
          ]
          @=? readTemplateElems "$-partial(\"path\")-$"
        -- 'Expr' trim check.
        , [ TrimL
          , Expr (Ident (TemplateKey "foo"))
          , TrimR
          ]
          @=? readTemplateElems "$-foo-$"
        ]
    ]


--------------------------------------------------------------------------------
test :: (Identifier, Identifier, Identifier) -> Assertion
test (outf, tplf, itemf) = do
    store    <- newTestStore
    provider <- newTestProvider store

    out  <- resourceString provider outf
    tpl  <- testCompilerDone store provider tplf templateBodyCompiler
    item <- testCompilerDone store provider itemf $
        pandocCompiler >>= applyTemplate (itemBody tpl) testContext

    out @=? itemBody item
    cleanTestEnv


--------------------------------------------------------------------------------
testContext :: Context String
testContext = mconcat
    [ defaultContext
    , listField "authors" (bodyField "name") $ do
        n1 <- makeItem "Jan"
        n2 <- makeItem "Piet"
        return [n1, n2]
    , functionField "rev" $ \args _ -> return $ unwords $ map reverse args
    ]


--------------------------------------------------------------------------------
testApplyJoinTemplateList :: Assertion
testApplyJoinTemplateList = do
    store    <- newTestStore
    provider <- newTestProvider store
    str      <- testCompilerDone store provider "item3" $
        applyJoinTemplateList ", " tpl defaultContext [i1, i2]

    str @?= "<b>Hello</b>, <b>World</b>"
    cleanTestEnv
  where
    i1  = Item "item1" "Hello"
    i2  = Item "item2" "World"
    tpl = readTemplate "<b>$body$</b>"