summaryrefslogtreecommitdiff
path: root/tests/Hakyll/Web/Template/Tests.hs
blob: a7b31a731b34f59d1c897c89c2f79d9ca6686293 (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
124
125
126
127
128
129
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Web.Template.Tests
    ( tests
    ) where


--------------------------------------------------------------------------------
import           Test.Framework                 (Test, testGroup)
import           Test.Framework.Providers.HUnit (testCase)
import           Test.HUnit                     (Assertion, (@=?), (@?=))


--------------------------------------------------------------------------------
import           Hakyll.Core.Compiler
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 :: Test
tests = testGroup "Hakyll.Core.Template.Tests" $ concat
    [ [ testCase "case01"                case01
      , testCase "applyJoinTemplateList" testApplyJoinTemplateList
      ]

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


--------------------------------------------------------------------------------
case01 :: Assertion
case01 = do
    store    <- newTestStore
    provider <- newTestProvider store

    out  <- resourceString provider "template.html.out"
    tpl  <- testCompilerDone store provider "template.html" templateBodyCompiler
    item <- testCompilerDone store provider "example.md" $
        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 = Template [Chunk "<b>", Expr (Ident "body"), Chunk "</b>"]