Skip to content

Commit

Permalink
test-framework is fixed again, so we use it again.
Browse files Browse the repository at this point in the history
  • Loading branch information
jaspervdj committed Jan 24, 2010
1 parent 81e3df1 commit 7a75e1f
Show file tree
Hide file tree
Showing 4 changed files with 46 additions and 26 deletions.
2 changes: 1 addition & 1 deletion .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ dist
tags

# Ignore test builds.
tests/Tests
tests/Main

# Rest of the file: ignore examples
examples/*/_cache
Expand Down
23 changes: 6 additions & 17 deletions tests/Main.hs
Original file line number Diff line number Diff line change
@@ -1,23 +1,12 @@
module Main where

import Control.Monad (mapM_)
import Test.QuickCheck
import Test.Framework (defaultMain, testGroup)
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2

import Template
import Util

main = do
runTests "Template" $ do
quickCheck prop_template_encode_id
quickCheck prop_substitute_id
quickCheck prop_substitute_case1

runTests "Util" $ do
quickCheck prop_trim_length
quickCheck prop_trim_id
quickCheck prop_stripHTML_length
quickCheck prop_stripHTML_id

where
runTests name action = do putStrLn name
action
main = defaultMain [ templateGroup
, utilGroup
]
32 changes: 25 additions & 7 deletions tests/Template.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,25 @@
module Template where
module Template
( templateGroup
) where

import qualified Data.Map as M

import Test.QuickCheck
import Data.Binary
import Test.Framework (testGroup)
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.HUnit

import Text.Hakyll.Internal.Template

-- Template test group.
templateGroup = testGroup "Template"
[ testProperty "prop_template_encode_id" prop_template_encode_id
, testProperty "prop_substitute_id" prop_substitute_id
, testCase "test_substitute_1" test_substitute_1
, testCase "test_substitute_2" test_substitute_2
]

-- Test encoding/decoding of templates.
prop_template_encode_id :: Template -> Bool
prop_template_encode_id template = decode (encode template) == template
Expand All @@ -16,10 +29,15 @@ prop_substitute_id string =
regularSubstitute (fromString string) M.empty == string

-- substitute test case 1.
prop_substitute_case1 string1 string2 =
finalSubstitute template context == string1 ++ " costs $" ++ string2 ++ "."
test_substitute_1 =
finalSubstitute template context @?= "Banana costs $4."
where
template = fromString "$product costs $$$price."
context = M.fromList [ ("product", string1)
, ("price", string2)
]
context = M.fromList [("product", "Banana"), ("price", "4")]

-- substitute test case 2.
test_substitute_2 =
regularSubstitute template context @?= "$$root is a special key."
where
template = fromString "$$root is a special $thing."
context = M.fromList [("root", "foo"), ("thing", "key")]
15 changes: 14 additions & 1 deletion tests/Util.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,24 @@
module Util where
module Util
( utilGroup
) where

import Data.Char

import Test.QuickCheck
import Test.Framework (testGroup)
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2

import Text.Hakyll.Util

-- Util test group.
utilGroup = testGroup "Util"
[ testProperty "prop_trim_length" prop_trim_length
, testProperty "prop_trim_id" prop_trim_id
, testProperty "prop_stripHTML_length" prop_stripHTML_length
, testProperty "prop_stripHTML_id" prop_stripHTML_id
]

-- Test that a string always becomes shorter when trimmed.
prop_trim_length str = length str >= length (trim str)

Expand Down

0 comments on commit 7a75e1f

Please sign in to comment.