summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2012-11-26 16:11:37 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2012-11-26 16:11:37 +0100
commit1bcce776e786eb6688bace653ecafa1a5a4fb563 (patch)
treefc889c8e4af23c32dec6637d5c4e2de1fe383830
parent25b8c8b199082ebbc41d1af03fc19202b798f156 (diff)
downloadhakyll-1bcce776e786eb6688bace653ecafa1a5a4fb563.tar.gz
Re-add some tests, cleanup...
-rw-r--r--hakyll.cabal4
-rw-r--r--src/Hakyll/Web/Page/List.hs83
-rw-r--r--tests/Hakyll/Core/Routes/Tests.hs21
-rw-r--r--tests/Hakyll/Core/Rules/Tests.hs86
-rw-r--r--tests/Hakyll/Core/Util/String/Tests.hs19
-rw-r--r--tests/Hakyll/Web/Util/Html/Tests.hs19
-rw-r--r--tests/TestSuite.hs10
7 files changed, 95 insertions, 147 deletions
diff --git a/hakyll.cabal b/hakyll.cabal
index 152dc7e..c72b284 100644
--- a/hakyll.cabal
+++ b/hakyll.cabal
@@ -202,10 +202,14 @@ Test-suite hakyll-tests
Hakyll.Core.Dependencies.Tests
Hakyll.Core.Identifier.Tests
Hakyll.Core.Provider.Tests
+ Hakyll.Core.Routes.Tests
+ Hakyll.Core.Rules.Tests
Hakyll.Core.Runtime.Tests
Hakyll.Core.Store.Tests
Hakyll.Core.UnixFilter.Tests
+ Hakyll.Core.Util.String.Tests
Hakyll.Web.Template.Tests
Hakyll.Web.Urls.Tests
Hakyll.Web.Urls.Relativize.Tests
+ Hakyll.Web.Util.Html.Tests
TestSuite.Util
diff --git a/src/Hakyll/Web/Page/List.hs b/src/Hakyll/Web/Page/List.hs
deleted file mode 100644
index 20c178c..0000000
--- a/src/Hakyll/Web/Page/List.hs
+++ /dev/null
@@ -1,83 +0,0 @@
--- TODO: Port
--- | Provides an easy way to combine several pages in a list. The applications
--- are obvious:
---
--- * A post list on a blog
---
--- * An image list in a gallery
---
--- * A sitemap
---
-module Hakyll.Web.Page.List
- ( setFieldPageList
- , pageListCompiler
- , chronological
- , recentFirst
- , sortByBaseName
- ) where
-
-import Control.Arrow ((>>>), arr)
-import Data.List (sortBy)
-import Data.Monoid (Monoid, mconcat)
-import Data.Ord (comparing)
-import System.FilePath (takeBaseName)
-
-import Hakyll.Core.Compiler
-import Hakyll.Core.Identifier
-import Hakyll.Core.Identifier.Pattern
-import Hakyll.Web.Page
-import Hakyll.Web.Page.Metadata
-import Hakyll.Web.Template
-
--- | Set a field of a page to a listing of pages
---
-setFieldPageList :: ([Page String] -> [Page String])
- -- ^ Determines list order
- -> Identifier Template
- -- ^ Applied to every page
- -> String
- -- ^ Key indicating which field should be set
- -> Pattern (Page String)
- -- ^ Selects pages to include in the list
- -> Compiler (Page String) (Page String)
- -- ^ Compiler that sets the page list in a field
-setFieldPageList sort template key pattern =
- requireAllA pattern $ setFieldA key $ pageListCompiler sort template
-
--- | Create a list of pages
---
-pageListCompiler :: ([Page String] -> [Page String]) -- ^ Determine list order
- -> Identifier Template -- ^ Applied to pages
- -> Compiler [Page String] String -- ^ Compiles page list
-pageListCompiler sort template =
- arr sort >>> applyTemplateToList template >>> arr concatPages
-
--- | Apply a template to every page in a list
---
-applyTemplateToList :: Identifier Template
- -> Compiler [Page String] [Page String]
-applyTemplateToList identifier = require identifier $
- \posts template -> map (applyTemplateToPage template) posts
-
--- | Concatenate the bodies of a page list
---
-concatPages :: Monoid m => [Page m] -> m
-concatPages = mconcat . map pageBody
-
--- | Sort pages chronologically. This function assumes that the pages have a
--- @year-month-day-title.extension@ naming scheme -- as is the convention in
--- Hakyll.
---
-chronological :: [Page a] -> [Page a]
-chronological = sortBy $ comparing $ takeBaseName . getField "path"
-
--- | The reverse of 'chronological'
---
-recentFirst :: [Page a] -> [Page a]
-recentFirst = reverse . chronological
-
--- | Deprecated, see 'chronological'
---
-sortByBaseName :: [Page a] -> [Page a]
-sortByBaseName = chronological
-{-# DEPRECATED sortByBaseName "Use chronological" #-}
diff --git a/tests/Hakyll/Core/Routes/Tests.hs b/tests/Hakyll/Core/Routes/Tests.hs
index d204b16..8bdbe85 100644
--- a/tests/Hakyll/Core/Routes/Tests.hs
+++ b/tests/Hakyll/Core/Routes/Tests.hs
@@ -1,17 +1,24 @@
+--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Core.Routes.Tests
( tests
) where
-import Test.Framework
-import Test.HUnit hiding (Test)
-import Hakyll.Core.Identifier
-import Hakyll.Core.Routes
-import TestSuite.Util
+--------------------------------------------------------------------------------
+import Test.Framework (Test, testGroup)
+import Test.HUnit ((@=?))
-tests :: [Test]
-tests = fromAssertions "runRoutes"
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Identifier
+import Hakyll.Core.Routes
+import TestSuite.Util
+
+
+--------------------------------------------------------------------------------
+tests :: Test
+tests = testGroup "Hakyll.Core.Routes.Tests" $ fromAssertions "runRoutes"
[ Just "foo.html" @=? runRoutes (setExtension "html") "foo"
, Just "foo.html" @=? runRoutes (setExtension ".html") "foo"
, Just "foo.html" @=? runRoutes (setExtension "html") "foo.markdown"
diff --git a/tests/Hakyll/Core/Rules/Tests.hs b/tests/Hakyll/Core/Rules/Tests.hs
index ac2126c..4f0b40e 100644
--- a/tests/Hakyll/Core/Rules/Tests.hs
+++ b/tests/Hakyll/Core/Rules/Tests.hs
@@ -1,67 +1,65 @@
+--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
-{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
module Hakyll.Core.Rules.Tests
( tests
) where
-import qualified Data.Map as M
-import qualified Data.Set as S
-import Test.Framework
-import Test.Framework.Providers.HUnit
-import Test.HUnit hiding (Test)
+--------------------------------------------------------------------------------
+import qualified Data.Set as S
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
+import Test.HUnit (Assertion, assert, (@=?))
-import Hakyll.Core.Rules
-import Hakyll.Core.Rules.Internal
-import Hakyll.Core.Identifier
-import Hakyll.Core.Routes
-import Hakyll.Core.Compiler
-import Hakyll.Core.Resource.Provider
-import Hakyll.Core.Resource.Provider.Dummy
-import Hakyll.Web.Page
-tests :: [Test]
-tests =
+--------------------------------------------------------------------------------
+import Hakyll.Core.Compiler
+import Hakyll.Core.Identifier
+import Hakyll.Core.Routes
+import Hakyll.Core.Rules
+import Hakyll.Core.Rules.Internal
+import Hakyll.Web.Page
+import TestSuite.Util
+
+
+--------------------------------------------------------------------------------
+tests :: Test
+tests = testGroup "Hakyll.Core.Rules.Tests"
[ testCase "runRules" rulesTest
]
--- | Main test
---
+
+--------------------------------------------------------------------------------
rulesTest :: Assertion
-rulesTest = do
- p <- provider
- let ruleSet = runRules rules p
- assert $ expected == S.fromList (map fst (rulesCompilers ruleSet))
+rulesTest = withTestStore $ \store -> do
+ provider <- newTestProvider store
+ ruleSet <- runRules rules provider
+ let identifiers = S.fromList $ map fst $ rulesCompilers ruleSet
+ routes = rulesRoutes ruleSet
+
+ -- Test that we have some identifiers and that the routes work out
+ assert $ all (`S.member` identifiers) expected
+ Just "example.html" @=? runRoutes routes "example.md"
+ Just "example.md" @=? runRoutes routes (raw "example.md")
where
- expected = S.fromList
- [ Identifier Nothing "posts/a-post.markdown"
- , Identifier Nothing "posts/some-other-post.markdown"
- , Identifier (Just "raw") "posts/a-post.markdown"
- , Identifier (Just "raw") "posts/some-other-post.markdown"
+ raw = setVersion (Just "raw")
+ expected =
+ [ "example.md"
+ , "russian.md"
+ , raw "example.md"
+ , raw "russian.md"
]
--- | Dummy resource provider
---
-provider :: IO ResourceProvider
-provider = dummyResourceProvider $ M.fromList $ map (flip (,) "No content")
- [ "posts/a-post.markdown"
- , "posts/some-other-post.markdown"
- ]
--- | Example rules
---
-rules :: Rules
+--------------------------------------------------------------------------------
+rules :: Rules ()
rules = do
-- Compile some posts
- match "posts/*" $ do
+ match "*.md" $ do
route $ setExtension "html"
compile pageCompiler
-- Compile them, raw
- group "raw" $ do
+ match "*.md" $ version "raw" $ do
route idRoute
- match "posts/*" $ do
- route $ setExtension "html"
- compile getResourceString
-
- return ()
+ compile getResourceString
diff --git a/tests/Hakyll/Core/Util/String/Tests.hs b/tests/Hakyll/Core/Util/String/Tests.hs
index bbdfb96..d5dcdb7 100644
--- a/tests/Hakyll/Core/Util/String/Tests.hs
+++ b/tests/Hakyll/Core/Util/String/Tests.hs
@@ -1,15 +1,22 @@
+--------------------------------------------------------------------------------
module Hakyll.Core.Util.String.Tests
( tests
) where
-import Test.Framework (Test)
-import Test.HUnit ((@=?))
-import Hakyll.Core.Util.String
-import TestSuite.Util
+--------------------------------------------------------------------------------
+import Test.Framework (Test, testGroup)
+import Test.HUnit ((@=?))
-tests :: [Test]
-tests = concat
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Util.String
+import TestSuite.Util
+
+
+--------------------------------------------------------------------------------
+tests :: Test
+tests = testGroup "Hakyll.Core.Util.String.Tests" $ concat
[ fromAssertions "trim"
[ "foo" @=? trim " foo\n\t "
]
diff --git a/tests/Hakyll/Web/Util/Html/Tests.hs b/tests/Hakyll/Web/Util/Html/Tests.hs
index e73c88b..3a99ca7 100644
--- a/tests/Hakyll/Web/Util/Html/Tests.hs
+++ b/tests/Hakyll/Web/Util/Html/Tests.hs
@@ -1,15 +1,22 @@
+--------------------------------------------------------------------------------
module Hakyll.Web.Util.Html.Tests
( tests
) where
-import Test.Framework
-import Test.HUnit hiding (Test)
-import Hakyll.Web.Util.Html
-import TestSuite.Util
+--------------------------------------------------------------------------------
+import Test.Framework (Test, testGroup)
+import Test.HUnit ((@=?))
-tests :: [Test]
-tests = concat
+
+--------------------------------------------------------------------------------
+import Hakyll.Web.Util.Html
+import TestSuite.Util
+
+
+--------------------------------------------------------------------------------
+tests :: Test
+tests = testGroup "Hakyll.Web.Util.Html" $ concat
[ fromAssertions "stripTags"
[ "foo" @=? stripTags "<p>foo</p>"
, "foo bar" @=? stripTags "<p>foo</p> bar"
diff --git a/tests/TestSuite.hs b/tests/TestSuite.hs
index 0476869..ef9d6d1 100644
--- a/tests/TestSuite.hs
+++ b/tests/TestSuite.hs
@@ -12,12 +12,16 @@ import Test.Framework (defaultMain)
import qualified Hakyll.Core.Dependencies.Tests
import qualified Hakyll.Core.Identifier.Tests
import qualified Hakyll.Core.Provider.Tests
+import qualified Hakyll.Core.Routes.Tests
+import qualified Hakyll.Core.Rules.Tests
import qualified Hakyll.Core.Runtime.Tests
import qualified Hakyll.Core.Store.Tests
import qualified Hakyll.Core.UnixFilter.Tests
+import qualified Hakyll.Core.Util.String.Tests
import qualified Hakyll.Web.Template.Tests
import qualified Hakyll.Web.Urls.Relativize.Tests
import qualified Hakyll.Web.Urls.Tests
+import qualified Hakyll.Web.Util.Html.Tests
--------------------------------------------------------------------------------
@@ -26,10 +30,14 @@ main = defaultMain
[ Hakyll.Core.Dependencies.Tests.tests
, Hakyll.Core.Identifier.Tests.tests
, Hakyll.Core.Provider.Tests.tests
+ , Hakyll.Core.Routes.Tests.tests
+ , Hakyll.Core.Rules.Tests.tests
, Hakyll.Core.Runtime.Tests.tests
, Hakyll.Core.Store.Tests.tests
, Hakyll.Core.UnixFilter.Tests.tests
+ , Hakyll.Core.Util.String.Tests.tests
, Hakyll.Web.Template.Tests.tests
- , Hakyll.Web.Urls.Tests.tests
, Hakyll.Web.Urls.Relativize.Tests.tests
+ , Hakyll.Web.Urls.Tests.tests
+ , Hakyll.Web.Util.Html.Tests.tests
]