summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--tests/Hakyll/Core/Rules/Tests.hs67
-rw-r--r--tests/Hakyll/Core/Store/Tests.hs66
-rw-r--r--tests/TestSuite.hs6
3 files changed, 139 insertions, 0 deletions
diff --git a/tests/Hakyll/Core/Rules/Tests.hs b/tests/Hakyll/Core/Rules/Tests.hs
new file mode 100644
index 0000000..ac2126c
--- /dev/null
+++ b/tests/Hakyll/Core/Rules/Tests.hs
@@ -0,0 +1,67 @@
+{-# 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 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 =
+ [ testCase "runRules" rulesTest
+ ]
+
+-- | Main test
+--
+rulesTest :: Assertion
+rulesTest = do
+ p <- provider
+ let ruleSet = runRules rules p
+ assert $ expected == S.fromList (map fst (rulesCompilers ruleSet))
+ 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"
+ ]
+
+-- | 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 = do
+ -- Compile some posts
+ match "posts/*" $ do
+ route $ setExtension "html"
+ compile pageCompiler
+
+ -- Compile them, raw
+ group "raw" $ do
+ route idRoute
+ match "posts/*" $ do
+ route $ setExtension "html"
+ compile getResourceString
+
+ return ()
diff --git a/tests/Hakyll/Core/Store/Tests.hs b/tests/Hakyll/Core/Store/Tests.hs
new file mode 100644
index 0000000..4f35abd
--- /dev/null
+++ b/tests/Hakyll/Core/Store/Tests.hs
@@ -0,0 +1,66 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Hakyll.Core.Store.Tests
+ ( tests
+ ) where
+
+import Control.Applicative ((<$>))
+import Control.Monad (replicateM)
+
+import Test.Framework
+import Test.Framework.Providers.QuickCheck2
+import Test.Framework.Providers.HUnit
+import Test.QuickCheck
+import Test.QuickCheck.Monadic
+import qualified Test.HUnit as H
+
+import Hakyll.Core.Identifier
+import Hakyll.Core.Store
+
+tests :: [Test]
+tests =
+ [ testProperty "simple storeGet . storeSet" simpleSetGet
+ , testProperty "persistent storeGet . storeSet" persistentSetGet
+ , testCase "WrongType storeGet . storeSet" wrongType
+ ]
+
+simpleSetGet :: Property
+simpleSetGet = monadicIO $ do
+ identifier <- parseIdentifier . unFileName <$> pick arbitrary
+ FileName name <- pick arbitrary
+ value <- pick arbitrary
+ store <- run $ makeStore "_store"
+ run $ storeSet store name identifier (value :: String)
+ value' <- run $ storeGet store name identifier
+ assert $ Found value == value'
+
+persistentSetGet :: Property
+persistentSetGet = monadicIO $ do
+ identifier <- parseIdentifier . unFileName <$> pick arbitrary
+ FileName name <- pick arbitrary
+ value <- pick arbitrary
+ store1 <- run $ makeStore "_store"
+ run $ storeSet store1 name identifier (value :: String)
+ -- Now Create another store from the same dir to test persistence
+ store2 <- run $ makeStore "_store"
+ value' <- run $ storeGet store2 name identifier
+ assert $ Found value == value'
+
+wrongType :: H.Assertion
+wrongType = do
+ store <- makeStore "_store"
+ -- Store a string and try to fetch an int
+ storeSet store "foo" "bar" ("qux" :: String)
+ value <- storeGet store "foo" "bar" :: IO (StoreGet Int)
+ H.assert $ case value of WrongType _ _ -> True
+ _ -> False
+
+newtype FileName = FileName {unFileName :: String}
+ deriving (Show)
+
+instance Arbitrary FileName where
+ arbitrary = do
+ length' <- choose (5, 100)
+ str <- replicateM length' $ elements cs
+ return $ FileName str
+ where
+ cs = ['a' .. 'z'] ++ ['A' .. 'Z'] ++ ['0' .. '9'] ++ ".- "
diff --git a/tests/TestSuite.hs b/tests/TestSuite.hs
index 4d2c95d..e459529 100644
--- a/tests/TestSuite.hs
+++ b/tests/TestSuite.hs
@@ -5,6 +5,8 @@ import Test.Framework (defaultMain, testGroup)
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.Web.Page.Tests
import qualified Hakyll.Web.Page.Metadata.Tests
import qualified Hakyll.Web.RelativizeUrls.Tests
@@ -19,6 +21,10 @@ main = defaultMain
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.Web.Page.Tests"
Hakyll.Web.Page.Tests.tests
, testGroup "Hakyll.Web.Page.Metadata.Tests"