hakyll/tests/Hakyll/Web/Template/Tests.hs

56 lines
1.7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Web.Template.Tests
( tests
) where
import Test.Framework
import Test.HUnit hiding (Test)
import qualified Data.Map as M
import Hakyll.Web.Page
import Hakyll.Web.Template
2011-02-10 11:30:58 +00:00
import Hakyll.Web.Template.Read
import TestSuite.Util
tests :: [Test]
tests = fromAssertions "applyTemplate"
-- Hakyll templates
2011-11-23 14:24:20 +00:00
[ applyTemplateAssertion readTemplate applyTemplate
2012-08-10 00:38:31 +00:00
("bar" @=?) "$foo$" [("foo", "bar")]
2011-11-23 14:24:20 +00:00
, applyTemplateAssertion readTemplate applyTemplate
2012-08-10 00:38:31 +00:00
("$ barqux" @=?) "$$ $foo$$bar$" [("foo", "bar"), ("bar", "qux")]
2011-11-23 14:24:20 +00:00
, applyTemplateAssertion readTemplate applyTemplate
2012-08-10 00:38:31 +00:00
("$foo$" @=?) "$foo$" []
2011-11-23 14:24:20 +00:00
-- Hamlet templates
2011-11-23 14:24:20 +00:00
, applyTemplateAssertion readHamletTemplate applyTemplate
2012-08-10 00:38:31 +00:00
(("<head><title>notice</title></head><body>A paragraph</body>" @=?) .
filter (/= '\n'))
2012-04-15 20:05:15 +00:00
"<head>\n\
\ <title>#{title}\n\
2012-04-15 20:05:15 +00:00
\<body>\n\
\ A paragraph\n"
[("title", "notice")]
2011-11-23 14:24:20 +00:00
-- Missing keys
, let missing "foo" = "bar"
missing "bar" = "qux"
missing x = reverse x
in applyTemplateAssertion readTemplate (applyTemplateWith missing)
2012-08-10 00:38:31 +00:00
("bar foo ver" @=?) "$foo$ $bar$ $rev$" [("bar", "foo")]
]
-- | Utility function to create quick template tests
--
2011-11-23 14:24:20 +00:00
applyTemplateAssertion :: (String -> Template)
-> (Template -> Page String -> Page String)
2012-08-10 00:38:31 +00:00
-> (String -> Assertion)
2011-11-23 14:24:20 +00:00
-> String
-> [(String, String)]
-> Assertion
2012-08-10 00:38:31 +00:00
applyTemplateAssertion parser apply correct template page =
correct $ pageBody (apply (parser template) (fromMap $ M.fromList page))