better test suite for StringUtils

This commit is contained in:
Yann Esposito (Yogsototh) 2013-12-03 23:32:15 +01:00
parent c6b3225e4a
commit d021b69ffc
2 changed files with 31 additions and 9 deletions

View file

@ -1,4 +1,8 @@
module HolyProject.StringUtils where
module HolyProject.StringUtils
( projectNameFromString
, capitalize
, checkProjectName
) where
-- Project name manipulation
import Data.Char (toUpper,toLower,isLetter,isNumber)

View file

@ -1,23 +1,41 @@
module HolyProject.StringUtils.Test
( stringUtilsSuite
) where
import Data.Char (isControl,isSymbol)
import Test.Tasty (testGroup, TestTree)
import Test.Tasty.HUnit
import Test.Tasty.SmallCheck (forAll)
import qualified Test.Tasty.SmallCheck as SC
import qualified Test.Tasty.QuickCheck as QC
import Test.SmallCheck.Series (Serial)
import HolyProject.StringUtils
stringUtilsSuite :: TestTree
stringUtilsSuite = testGroup "StringUtils"
[ SC.testProperty "SC projectNameFromString idempotent" $
idempotent projectNameFromString
, SC.testProperty "SC capitalize idempotent" $
deeperIdempotent capitalize
, QC.testProperty "QC projectNameFromString idempotent" $
idempotent capitalize
tp name prop = testGroup name
[ QC.testProperty "QC" prop
, SC.testProperty "SC" prop
]
stringUtilsSuite :: TestTree
stringUtilsSuite = testGroup "StringUtils"
[ tp "projectNameFromString idempotent" $
idempotent projectNameFromString
, SC.testProperty "capitalize idempotent" $
deeperIdempotent capitalize
, tp "no space in project name" $
\s -> dropWhile (/=' ') (projectNameFromString s) == []
, tp "no space in capitalized name" $
\s -> dropWhile (/=' ') (capitalize s) == []
, tp "no dash in capitalized name" $
\s -> dropWhile (/='-') (capitalize s) == []
, tp "no control char" $
\s -> if (s /= "") && (checkProjectName s == True) then (all (not . isControl) s) else True
, tp "no symbol char" $
\s -> if (s /= "") && (checkProjectName s == True) then (all (not . isSymbol) s) else True
, testCase "doesn't accept empty project name" $
checkProjectName "" @=? False
]
idempotent :: (Eq a) => (a -> a) -> a -> Bool
idempotent f = \s -> f s == f (f s)
deeperIdempotent :: (Eq a, Show a, Serial m a) => (a -> a) -> SC.Property m