summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--hakyll.cabal23
-rw-r--r--src/Hakyll/Core/Compiler.hs4
-rw-r--r--src/Hakyll/Core/Provider/Internal.hs38
-rw-r--r--src/Hakyll/Core/Provider/Metadata.hs8
-rw-r--r--src/Hakyll/Core/Provider/MetadataCache.hs2
-rw-r--r--src/Hakyll/Core/Provider/Modified.hs21
-rw-r--r--src/Hakyll/Core/Util/File.hs64
-rw-r--r--src/Hakyll/Web/Template/Context.hs4
-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
17 files changed, 256 insertions, 201 deletions
diff --git a/hakyll.cabal b/hakyll.cabal
index c88c269..7ec9de4 100644
--- a/hakyll.cabal
+++ b/hakyll.cabal
@@ -40,12 +40,19 @@ Category: Web
Cabal-Version: >= 1.8
Build-Type: Simple
Data-Dir: data
+
Data-Files:
templates/atom.xml
templates/atom-item.xml
templates/rss.xml
templates/rss-item.xml
+Extra-source-files:
+ tests/data/example.md
+ tests/data/example.md.metadata
+ tests/data/example.md.out
+ tests/data/template.html
+
Source-Repository head
Type: git
Location: git://github.com/jaspervdj/hakyll.git
@@ -200,19 +207,7 @@ Test-suite hakyll-tests
unix >= 2.4 && < 2.7
Other-modules:
- Hakyll.Web.Util.Html.Tests
- Hakyll.Web.Urls.Relativize.Tests
- Hakyll.Web.Urls.Tests
+ Hakyll.Core.Dependencies.Tests
+ Hakyll.Core.Provider.Tests
Hakyll.Web.Template.Tests
- Hakyll.Web.Page.Metadata.Tests
- Hakyll.Web.Page.Tests
- Hakyll.Core.Compiler.Tests
- Hakyll.Core.Identifier.Tests
- Hakyll.Core.Util.Arrow.Tests
- Hakyll.Core.Util.String.Tests
- Hakyll.Core.UnixFilter.Tests
- Hakyll.Core.Routes.Tests
- Hakyll.Core.Store.Tests
- Hakyll.Core.Rules.Tests
- Hakyll.Core.DependencyAnalyzer.Tests
TestSuite.Util
diff --git a/src/Hakyll/Core/Compiler.hs b/src/Hakyll/Core/Compiler.hs
index ccd056f..7193e4f 100644
--- a/src/Hakyll/Core/Compiler.hs
+++ b/src/Hakyll/Core/Compiler.hs
@@ -81,13 +81,13 @@ getResourceBody = getResourceWith resourceBody
--------------------------------------------------------------------------------
-- | Get the resource we are compiling as a string
getResourceString :: Compiler (Item String)
-getResourceString = getResourceWith $ const resourceString
+getResourceString = getResourceWith resourceString
--------------------------------------------------------------------------------
-- | Get the resource we are compiling as a lazy bytestring
getResourceLBS :: Compiler (Item ByteString)
-getResourceLBS = getResourceWith $ const resourceLBS
+getResourceLBS = getResourceWith resourceLBS
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Core/Provider/Internal.hs b/src/Hakyll/Core/Provider/Internal.hs
index 54332a9..1360ef5 100644
--- a/src/Hakyll/Core/Provider/Internal.hs
+++ b/src/Hakyll/Core/Provider/Internal.hs
@@ -7,32 +7,35 @@ module Hakyll.Core.Provider.Internal
, resourceExists
, resourceMetadataResource
+ , resourceFilePath
, resourceString
, resourceLBS
) where
--------------------------------------------------------------------------------
-import Control.Applicative ((<$>))
-import qualified Data.ByteString.Lazy as BL
+import Control.Applicative ((<$>))
+import qualified Data.ByteString.Lazy as BL
import Data.IORef
-import Data.Map (Map)
-import qualified Data.Map as M
-import Data.Set (Set)
-import qualified Data.Set as S
-import System.FilePath (addExtension)
+import Data.Map (Map)
+import qualified Data.Map as M
+import Data.Set (Set)
+import qualified Data.Set as S
+import System.FilePath (addExtension, (</>))
--------------------------------------------------------------------------------
+import Hakyll.Core.Identifier
import Hakyll.Core.Store
import Hakyll.Core.Util.File
-import Hakyll.Core.Identifier
--------------------------------------------------------------------------------
-- | Responsible for retrieving and listing resources
data Provider = Provider
- { -- | A list of all files found
+ { -- Top of the provided directory
+ providerDirectory :: FilePath
+ , -- | A list of all files found
providerSet :: Set Identifier
, -- | Cache keeping track of modified files
providerModifiedCache :: IORef (Map Identifier Bool)
@@ -49,9 +52,9 @@ newProvider :: Store -- ^ Store to use
-> IO Provider -- ^ Resulting provider
newProvider store ignore directory = do
list <- map fromFilePath . filter (not . ignore) <$>
- getRecursiveContents False directory
+ getRecursiveContents directory
cache <- newIORef M.empty
- return $ Provider (S.fromList list) cache store
+ return $ Provider directory (S.fromList list) cache store
--------------------------------------------------------------------------------
@@ -75,12 +78,17 @@ resourceMetadataResource =
--------------------------------------------------------------------------------
+resourceFilePath :: Provider -> Identifier -> FilePath
+resourceFilePath p i = providerDirectory p </> toFilePath i
+
+
+--------------------------------------------------------------------------------
-- | Get the raw body of a resource as string
-resourceString :: Identifier -> IO String
-resourceString = readFile . toFilePath
+resourceString :: Provider -> Identifier -> IO String
+resourceString p i = readFile $ resourceFilePath p i
--------------------------------------------------------------------------------
-- | Get the raw body of a resource of a lazy bytestring
-resourceLBS :: Identifier -> IO BL.ByteString
-resourceLBS = BL.readFile . toFilePath
+resourceLBS :: Provider -> Identifier -> IO BL.ByteString
+resourceLBS p i = BL.readFile $ resourceFilePath p i
diff --git a/src/Hakyll/Core/Provider/Metadata.hs b/src/Hakyll/Core/Provider/Metadata.hs
index 18536f4..52c07cb 100644
--- a/src/Hakyll/Core/Provider/Metadata.hs
+++ b/src/Hakyll/Core/Provider/Metadata.hs
@@ -25,19 +25,19 @@ import Hakyll.Core.Util.String
--------------------------------------------------------------------------------
loadMetadata :: Provider -> Identifier -> IO (Metadata, Maybe String)
-loadMetadata rp identifier = do
+loadMetadata p identifier = do
hasHeader <- probablyHasMetadataHeader fp
(md, body) <- if hasHeader
then second Just <$> loadMetadataHeader fp
else return (M.empty, Nothing)
- emd <- if resourceExists rp mi then loadMetadataFile mfp else return M.empty
+ emd <- if resourceExists p mi then loadMetadataFile mfp else return M.empty
return (M.union md emd, body)
where
- fp = toFilePath identifier
+ fp = resourceFilePath p identifier
mi = resourceMetadataResource identifier
- mfp = toFilePath mi
+ mfp = resourceFilePath p mi
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Core/Provider/MetadataCache.hs b/src/Hakyll/Core/Provider/MetadataCache.hs
index cd67370..03652e7 100644
--- a/src/Hakyll/Core/Provider/MetadataCache.hs
+++ b/src/Hakyll/Core/Provider/MetadataCache.hs
@@ -29,7 +29,7 @@ resourceBody p r = do
load p r
Store.Found bd <- Store.get (providerStore p)
[name, toFilePath r, "body"]
- maybe (resourceString r) return bd
+ maybe (resourceString p r) return bd
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Core/Provider/Modified.hs b/src/Hakyll/Core/Provider/Modified.hs
index 166019d..08bb66a 100644
--- a/src/Hakyll/Core/Provider/Modified.hs
+++ b/src/Hakyll/Core/Provider/Modified.hs
@@ -15,6 +15,7 @@ import Data.IORef
import qualified Data.Map as M
import Data.Time (UTCTime)
import System.Directory (getModificationTime)
+import System.FilePath ((</>))
--------------------------------------------------------------------------------
@@ -28,7 +29,7 @@ import qualified Hakyll.Core.Store as Store
--------------------------------------------------------------------------------
-- | A resource is modified if it or its metadata has changed
resourceModified :: Provider -> Identifier -> IO Bool
-resourceModified rp r
+resourceModified p r
| not exists = return False
| otherwise = do
cache <- readIORef cacheRef
@@ -38,19 +39,20 @@ resourceModified rp r
-- Check if the actual file was modified, and do a recursive
-- call to check if the metadata file was modified
m <- (||)
- <$> fileDigestModified store (toFilePath r)
- <*> resourceModified rp (resourceMetadataResource r)
+ <$> fileDigestModified store filePath
+ <*> resourceModified p (resourceMetadataResource r)
modifyIORef cacheRef (M.insert normalized m)
-- Important! (But ugly)
- when m $ resourceInvalidateMetadataCache rp r
+ when m $ resourceInvalidateMetadataCache p r
return m
where
normalized = setVersion Nothing r
- exists = resourceExists rp r
- store = providerStore rp
- cacheRef = providerModifiedCache rp
+ exists = resourceExists p r
+ store = providerStore p
+ cacheRef = providerModifiedCache p
+ filePath = resourceFilePath p r
--------------------------------------------------------------------------------
@@ -79,5 +81,6 @@ fileDigest = fmap MD5.hashlazy . BL.readFile
--------------------------------------------------------------------------------
-resourceModificationTime :: Identifier -> IO UTCTime
-resourceModificationTime = getModificationTime . toFilePath
+resourceModificationTime :: Provider -> Identifier -> IO UTCTime
+resourceModificationTime p i =
+ getModificationTime $ providerDirectory p </> toFilePath i
diff --git a/src/Hakyll/Core/Util/File.hs b/src/Hakyll/Core/Util/File.hs
index 5889664..85fbd76 100644
--- a/src/Hakyll/Core/Util/File.hs
+++ b/src/Hakyll/Core/Util/File.hs
@@ -1,52 +1,60 @@
+--------------------------------------------------------------------------------
-- | A module containing various file utility functions
---
module Hakyll.Core.Util.File
( makeDirectories
, getRecursiveContents
, isFileInternal
) where
-import Control.Applicative ((<$>))
-import Control.Monad (forM)
-import Data.List (isPrefixOf)
-import System.Directory ( createDirectoryIfMissing, doesDirectoryExist
- , getDirectoryContents
- )
-import System.FilePath ( normalise, takeDirectory, splitPath
- , dropTrailingPathSeparator, (</>)
- )
-import Hakyll.Core.Configuration
+--------------------------------------------------------------------------------
+import Control.Applicative ((<$>))
+import Control.Monad (forM)
+import Data.List (isPrefixOf)
+import System.Directory (createDirectoryIfMissing,
+ doesDirectoryExist,
+ getDirectoryContents)
+import System.FilePath (dropTrailingPathSeparator,
+ splitPath, takeDirectory, (</>))
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Configuration
+
+
+--------------------------------------------------------------------------------
-- | Given a path to a file, try to make the path writable by making
-- all directories on the path.
---
makeDirectories :: FilePath -> IO ()
makeDirectories = createDirectoryIfMissing True . takeDirectory
+
+--------------------------------------------------------------------------------
-- | Get all contents of a directory.
-getRecursiveContents :: Bool -- ^ Include directories?
- -> FilePath -- ^ Directory to search
+getRecursiveContents :: FilePath -- ^ Directory to search
-> IO [FilePath] -- ^ List of files found
-getRecursiveContents includeDirs topdir = do
- topdirExists <- doesDirectoryExist topdir
- if not topdirExists
- then return []
- else do
- names <- filter isProper <$> getDirectoryContents topdir
- paths <- forM names $ \name -> do
- let path = normalise $ topdir </> name
- isDirectory <- doesDirectoryExist path
- if isDirectory then getRecursiveContents includeDirs path
- else return [path]
- return $ if includeDirs then topdir : concat paths
- else concat paths
+getRecursiveContents top = go ""
where
isProper = (`notElem` [".", ".."])
+ go dir = do
+ dirExists <- doesDirectoryExist (top </> dir)
+ if not dirExists
+ then return []
+ else do
+ names <- filter isProper <$> getDirectoryContents (top </> dir)
+ paths <- forM names $ \name -> do
+ let rel = dir </> name
+ isDirectory <- doesDirectoryExist (top </> rel)
+ if isDirectory
+ then go rel
+ else return [rel]
+
+ return $ concat paths
+
+--------------------------------------------------------------------------------
-- | Check if a file is meant for Hakyll internal use, i.e. if it is located in
-- the destination or store directory
---
isFileInternal :: Configuration -- ^ Configuration
-> FilePath -- ^ File to check
-> Bool -- ^ If the given file is internal
diff --git a/src/Hakyll/Web/Template/Context.hs b/src/Hakyll/Web/Template/Context.hs
index fd9add9..eeec728 100644
--- a/src/Hakyll/Web/Template/Context.hs
+++ b/src/Hakyll/Web/Template/Context.hs
@@ -195,7 +195,9 @@ modificationTimeFieldWith :: TimeLocale -- ^ Time output locale
-> String -- ^ Format
-> Context a -- ^ Resulting context
modificationTimeFieldWith locale key fmt = field key $ \i -> do
- mtime <- compilerUnsafeIO $ resourceModificationTime $ itemIdentifier i
+ provider <- compilerProvider <$> compilerAsk
+ mtime <- compilerUnsafeIO $
+ resourceModificationTime provider $ itemIdentifier i
return $ formatTime locale fmt mtime
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>