summaryrefslogtreecommitdiff
path: root/tests
diff options
context:
space:
mode:
Diffstat (limited to 'tests')
-rw-r--r--tests/Hakyll/Core/Dependencies/Tests.hs6
-rw-r--r--tests/Hakyll/Core/Provider/Tests.hs35
-rw-r--r--tests/Hakyll/Web/Template/Tests.hs81
-rw-r--r--tests/TestSuite.hs62
-rw-r--r--tests/TestSuite/Util.hs97
-rw-r--r--tests/data/example.md5
-rw-r--r--tests/data/example.md.metadata1
-rw-r--r--tests/data/example.md.out3
-rw-r--r--tests/data/template.html3
9 files changed, 166 insertions, 127 deletions
diff --git a/tests/Hakyll/Core/Dependencies/Tests.hs b/tests/Hakyll/Core/Dependencies/Tests.hs
index cf1d682..22d606f 100644
--- a/tests/Hakyll/Core/Dependencies/Tests.hs
+++ b/tests/Hakyll/Core/Dependencies/Tests.hs
@@ -41,9 +41,9 @@ oldFacts = M.fromList
, ("posts/02.md",
[])
, ("index.md",
- [ Pattern "posts/*" ["posts/01.md", "posts/02.md"]
- , Identifier "posts/01.md"
- , Identifier "posts/02.md"
+ [ PatternDependency "posts/*" ["posts/01.md", "posts/02.md"]
+ , IdentifierDependency "posts/01.md"
+ , IdentifierDependency "posts/02.md"
])
]
diff --git a/tests/Hakyll/Core/Provider/Tests.hs b/tests/Hakyll/Core/Provider/Tests.hs
new file mode 100644
index 0000000..9e46893
--- /dev/null
+++ b/tests/Hakyll/Core/Provider/Tests.hs
@@ -0,0 +1,35 @@
+--------------------------------------------------------------------------------
+{-# LANGUAGE OverloadedStrings #-}
+module Hakyll.Core.Provider.Tests
+ ( tests
+ ) where
+
+
+--------------------------------------------------------------------------------
+import qualified Data.Map as M
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
+import Test.HUnit (Assertion, assert, (@=?))
+
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Provider
+import TestSuite.Util
+
+
+--------------------------------------------------------------------------------
+tests :: Test
+tests = testGroup "Hakyll.Core.Provider.Tests"
+ [ testCase "case01" case01
+ ]
+
+
+--------------------------------------------------------------------------------
+case01 :: Assertion
+case01 = withTestStore $ \store -> do
+ provider <- newTestProvider store
+ assert $ resourceExists provider "example.md"
+
+ metadata <- resourceMetadata provider "example.md"
+ Just "An example" @=? M.lookup "title" metadata
+ Just "External data" @=? M.lookup "external" metadata
diff --git a/tests/Hakyll/Web/Template/Tests.hs b/tests/Hakyll/Web/Template/Tests.hs
index 991a76f..42be506 100644
--- a/tests/Hakyll/Web/Template/Tests.hs
+++ b/tests/Hakyll/Web/Template/Tests.hs
@@ -1,55 +1,40 @@
+--------------------------------------------------------------------------------
{-# 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
-import Hakyll.Web.Template.Read
-import TestSuite.Util
-
-tests :: [Test]
-tests = fromAssertions "applyTemplate"
- -- Hakyll templates
- [ applyTemplateAssertion readTemplate applyTemplate
- ("bar" @=?) "$foo$" [("foo", "bar")]
-
- , applyTemplateAssertion readTemplate applyTemplate
- ("$ barqux" @=?) "$$ $foo$$bar$" [("foo", "bar"), ("bar", "qux")]
-
- , applyTemplateAssertion readTemplate applyTemplate
- ("$foo$" @=?) "$foo$" []
-
- -- Hamlet templates
- , applyTemplateAssertion readHamletTemplate applyTemplate
- (("<head><title>notice</title></head><body>A paragraph</body>" @=?) .
- filter (/= '\n'))
- "<head>\n\
- \ <title>#{title}\n\
- \<body>\n\
- \ A paragraph\n"
- [("title", "notice")]
-
- -- Missing keys
- , let missing "foo" = "bar"
- missing "bar" = "qux"
- missing x = reverse x
- in applyTemplateAssertion readTemplate (applyTemplateWith missing)
- ("bar foo ver" @=?) "$foo$ $bar$ $rev$" [("bar", "foo")]
+
+--------------------------------------------------------------------------------
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
+import Test.HUnit (Assertion, (@=?))
+
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Item
+import Hakyll.Core.Provider
+import Hakyll.Web.Page
+import Hakyll.Web.Template
+import Hakyll.Web.Template.Context
+import TestSuite.Util
+
+
+--------------------------------------------------------------------------------
+tests :: Test
+tests = testGroup "Hakyll.Core.Template.Tests"
+ [ testCase "case01" case01
]
--- | Utility function to create quick template tests
---
-applyTemplateAssertion :: (String -> Template)
- -> (Template -> Page String -> Page String)
- -> (String -> Assertion)
- -> String
- -> [(String, String)]
- -> Assertion
-applyTemplateAssertion parser apply correct template page =
- correct $ pageBody (apply (parser template) (fromMap $ M.fromList page))
+
+--------------------------------------------------------------------------------
+case01 :: Assertion
+case01 = withTestStore $ \store -> do
+ provider <- newTestProvider store
+
+ out <- resourceString provider "example.md.out"
+ tpl <- testCompilerDone store provider "template.html" $ templateCompiler
+ item <- testCompilerDone store provider "example.md" $
+ pageCompiler >>= applyTemplate (itemBody tpl) defaultContext
+
+ out @=? itemBody item
diff --git a/tests/TestSuite.hs b/tests/TestSuite.hs
index 4eb657b..4244bc9 100644
--- a/tests/TestSuite.hs
+++ b/tests/TestSuite.hs
@@ -1,53 +1,23 @@
-module Main where
+--------------------------------------------------------------------------------
+module Main
+ ( main
+ ) where
-import Test.Framework (defaultMain, testGroup)
-import qualified Hakyll.Core.Compiler.Tests
-import qualified Hakyll.Core.DependencyAnalyzer.Tests
-import qualified Hakyll.Core.Identifier.Tests
-import qualified Hakyll.Core.Routes.Tests
-import qualified Hakyll.Core.Rules.Tests
-import qualified Hakyll.Core.Store.Tests
-import qualified Hakyll.Core.UnixFilter.Tests
-import qualified Hakyll.Core.Util.Arrow.Tests
-import qualified Hakyll.Core.Util.String.Tests
-import qualified Hakyll.Web.Page.Tests
-import qualified Hakyll.Web.Page.Metadata.Tests
+--------------------------------------------------------------------------------
+import Test.Framework (defaultMain)
+
+
+--------------------------------------------------------------------------------
+import qualified Hakyll.Core.Dependencies.Tests
+import qualified Hakyll.Core.Provider.Tests
import qualified Hakyll.Web.Template.Tests
-import qualified Hakyll.Web.Urls.Tests
-import qualified Hakyll.Web.Urls.Relativize.Tests
-import qualified Hakyll.Web.Util.Html.Tests
+
+--------------------------------------------------------------------------------
main :: IO ()
main = defaultMain
- [ testGroup "Hakyll.Core.Compiler.Tests"
- Hakyll.Core.Compiler.Tests.tests
- , testGroup "Hakyll.Core.DependencyAnalyzer.Tests"
- Hakyll.Core.DependencyAnalyzer.Tests.tests
- , testGroup "Hakyll.Core.Identifier.Tests"
- Hakyll.Core.Identifier.Tests.tests
- , testGroup "Hakyll.Core.Routes.Tests"
- Hakyll.Core.Routes.Tests.tests
- , testGroup "Hakyll.Core.Rules.Tests"
- Hakyll.Core.Rules.Tests.tests
- , testGroup "Hakyll.Core.Store.Tests"
- Hakyll.Core.Store.Tests.tests
- , testGroup "Hakyll.Core.UnixFilter.Tests"
- Hakyll.Core.UnixFilter.Tests.tests
- , testGroup "Hakyll.Core.Util.Arrow.Tests"
- Hakyll.Core.Util.Arrow.Tests.tests
- , testGroup "Hakyll.Core.Util.String.Tests"
- Hakyll.Core.Util.String.Tests.tests
- , testGroup "Hakyll.Web.Page.Tests"
- Hakyll.Web.Page.Tests.tests
- , testGroup "Hakyll.Web.Page.Metadata.Tests"
- Hakyll.Web.Page.Metadata.Tests.tests
- , testGroup "Hakyll.Web.Template.Tests"
- Hakyll.Web.Template.Tests.tests
- , testGroup "Hakyll.Web.Urls.Tests"
- Hakyll.Web.Urls.Tests.tests
- , testGroup "Hakyll.Web.Urls.Relativize.Tests"
- Hakyll.Web.Urls.Relativize.Tests.tests
- , testGroup "Hakyll.Web.Util.Html.Tests"
- Hakyll.Web.Util.Html.Tests.tests
+ [ Hakyll.Core.Dependencies.Tests.tests
+ , Hakyll.Core.Provider.Tests.tests
+ , Hakyll.Web.Template.Tests.tests
]
diff --git a/tests/TestSuite/Util.hs b/tests/TestSuite/Util.hs
index 4fd87bf..6b19333 100644
--- a/tests/TestSuite/Util.hs
+++ b/tests/TestSuite/Util.hs
@@ -1,24 +1,32 @@
+--------------------------------------------------------------------------------
-- | Test utilities
---
module TestSuite.Util
( fromAssertions
- , makeStoreTest
- , runCompilerJobTest
+ , withTestStore
+ , newTestProvider
+ , testCompiler
+ , testCompilerDone
) where
-import Data.Monoid (mempty)
-import Test.Framework
-import Test.Framework.Providers.HUnit
-import Test.HUnit hiding (Test)
+--------------------------------------------------------------------------------
+import Data.Monoid (mempty)
+import System.Directory (removeDirectoryRecursive)
+import Test.Framework
+import Test.Framework.Providers.HUnit
+import Test.HUnit hiding (Test)
-import Hakyll.Core.Compiler.Internal
-import Hakyll.Core.Identifier
-import Hakyll.Core.Logger
-import Hakyll.Core.Resource.Provider
-import Hakyll.Core.Store (Store)
-import qualified Hakyll.Core.Store as Store
+--------------------------------------------------------------------------------
+import Hakyll.Core.Compiler.Internal
+import Hakyll.Core.Identifier
+import qualified Hakyll.Core.Logger as Logger
+import Hakyll.Core.Provider
+import Hakyll.Core.Store (Store)
+import qualified Hakyll.Core.Store as Store
+
+
+--------------------------------------------------------------------------------
fromAssertions :: String -- ^ Name
-> [Assertion] -- ^ Cases
-> [Test] -- ^ Result tests
@@ -26,20 +34,49 @@ fromAssertions name = zipWith testCase names
where
names = map (\n -> name ++ " [" ++ show n ++ "]") [1 :: Int ..]
--- | Create a store for testing
---
-makeStoreTest :: IO Store
-makeStoreTest = Store.new True "_store"
-
--- | Testing for 'runCompilerJob'
---
-runCompilerJobTest :: Compiler () a
- -> Identifier ()
- -> ResourceProvider
- -> [Identifier ()]
- -> IO a
-runCompilerJobTest compiler id' provider uni = do
- store <- makeStoreTest
- logger <- makeLogger $ const $ return ()
- Right x <- runCompilerJob compiler id' provider uni mempty store True logger
- return x
+
+--------------------------------------------------------------------------------
+withTestStore :: (Store -> IO a) -> IO a
+withTestStore f = do
+ store <- Store.new True "_teststore"
+ result <- f store
+ removeDirectoryRecursive "_teststore"
+ return result
+
+
+--------------------------------------------------------------------------------
+newTestProvider :: Store -> IO Provider
+newTestProvider store = newProvider store (const False) "tests/data"
+
+
+--------------------------------------------------------------------------------
+testCompiler :: Store -> Provider -> Identifier -> Compiler a
+ -> IO (CompilerResult a)
+testCompiler store provider underlying compiler = do
+ logger <- Logger.new Logger.Debug (\_ -> return ())
+ let read' = CompilerRead
+ { compilerUnderlying = underlying
+ , compilerProvider = provider
+ , compilerUniverse = []
+ , compilerRoutes = mempty
+ , compilerStore = store
+ , compilerLogger = logger
+ }
+
+ result <- runCompiler compiler read'
+ Logger.flush logger
+ return result
+
+
+--------------------------------------------------------------------------------
+testCompilerDone :: Store -> Provider -> Identifier -> Compiler a -> IO a
+testCompilerDone store provider underlying compiler = do
+ result <- testCompiler store provider underlying compiler
+ case result of
+ CompilerDone x _ -> return x
+ CompilerError e -> error $
+ "TestSuite.Util.testCompilerDone: compiler " ++ show underlying ++
+ " threw: " ++ e
+ CompilerRequire i _ -> error $
+ "TestSuite.Util.testCompilerDone: compiler " ++ show underlying ++
+ " requires: " ++ show i
diff --git a/tests/data/example.md b/tests/data/example.md
new file mode 100644
index 0000000..6c51faa
--- /dev/null
+++ b/tests/data/example.md
@@ -0,0 +1,5 @@
+---
+title: An example
+---
+
+This is an example.
diff --git a/tests/data/example.md.metadata b/tests/data/example.md.metadata
new file mode 100644
index 0000000..b757d9b
--- /dev/null
+++ b/tests/data/example.md.metadata
@@ -0,0 +1 @@
+external: External data
diff --git a/tests/data/example.md.out b/tests/data/example.md.out
new file mode 100644
index 0000000..f2c4c28
--- /dev/null
+++ b/tests/data/example.md.out
@@ -0,0 +1,3 @@
+<div>
+ <p>This is an example.</p>
+</div>
diff --git a/tests/data/template.html b/tests/data/template.html
new file mode 100644
index 0000000..8fa47e4
--- /dev/null
+++ b/tests/data/template.html
@@ -0,0 +1,3 @@
+<div>
+ $body$
+</div>