Switch tests to hspec (#22)

This commit is contained in:
Juan Pablo Santos 2016-06-23 04:01:49 -05:00 committed by Mark Karpov
parent 456fd6c1f0
commit f69e7a4295
15 changed files with 239 additions and 307 deletions

View File

@ -23,7 +23,6 @@ library
exposed-modules: Text.Inflections
, Text.Inflections.Parse.Types
other-modules: Text.Inflections.Data
, Text.Inflections.Parameterize
, Text.Inflections.Humanize
@ -47,12 +46,14 @@ library
test-suite test
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Suite.hs
main-is: Spec.hs
build-depends:
inflections
, base >=4.2 && <4.10
, test-framework
, HUnit
, hspec
, hspec-discover
, QuickCheck
, test-framework-hunit
, test-framework-quickcheck2
@ -61,9 +62,9 @@ test-suite test
ghc-options: -Wall
default-language: Haskell2010
other-modules:
Text.InflectionsTest
Text.Inflections.HumanizeTest
Text.Inflections.OrdinalTest
Text.Inflections.Tests
Text.Inflections.TitleizeTest
Text.Inflections.UnderscoreTest
Text.Inflections.HumanizeSpec
, Text.Inflections.OrdinalSpec
, Text.Inflections.PropertiesSpec
, Text.Inflections.TitleizeSpec
, Text.Inflections.UnderscoreSpec
, Text.InflectionsSpec

1
test/Spec.hs Normal file
View File

@ -0,0 +1 @@
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}

View File

@ -1,18 +0,0 @@
module Main where
import Test.Framework (defaultMain)
import qualified Text.InflectionsTest
import qualified Text.Inflections.Tests
import qualified Text.Inflections.UnderscoreTest
import qualified Text.Inflections.OrdinalTest
import qualified Text.Inflections.HumanizeTest
import qualified Text.Inflections.TitleizeTest
main :: IO ()
main = defaultMain $ Text.InflectionsTest.tests ++
Text.Inflections.Tests.tests ++
Text.Inflections.UnderscoreTest.tests ++
Text.Inflections.OrdinalTest.tests ++
Text.Inflections.HumanizeTest.tests ++
Text.Inflections.TitleizeTest.tests

View File

@ -0,0 +1,21 @@
module Text.Inflections.HumanizeSpec (spec) where
import Test.Hspec
import Text.Inflections (humanize)
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec = do
snakeCaseHumanize
capitalizeFirstWord
snakeCaseHumanize :: Spec
snakeCaseHumanize =
it "converts snake case to a human-readable string" $
humanize [Word "employee", Word "salary"] `shouldBe` "Employee salary"
capitalizeFirstWord :: Spec
capitalizeFirstWord =
it "capitalizes the first word of a sentence" $
humanize [Word "underground"] `shouldBe` "Underground"

View File

@ -1,28 +0,0 @@
module Text.Inflections.HumanizeTest where
import Test.HUnit hiding (Test)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework (Test, testGroup)
import Text.Inflections (humanize)
import Text.Inflections.Parse.Types (Word(..))
{-# ANN module "HLint: ignore Use camelCase" #-}
tests :: [Test]
tests = [ testGroup "humanize"
[ testCase "employee_salary -> Employee salary" test_humanize1
, testCase "underground -> underground" test_humanize2
]
]
----------------------------------------------------
test_humanize1 :: Assertion
test_humanize1 = "Employee salary" @?=
humanize [Word "employee", Word "salary"]
test_humanize2 :: Assertion
test_humanize2 = "Underground" @?= humanize [Word "underground"]

View File

@ -0,0 +1,62 @@
module Text.Inflections.OrdinalSpec (spec) where
import Control.Applicative ((<$>))
import Test.Hspec
import Test.QuickCheck.Property
import Text.Inflections (ordinal, ordinalize)
spec :: Spec
spec = do
describe "ordinal" $ do
one
two
thousands
negatives
ordinalReturnsNotEmpty
describe "ordinalize" $ do
fullOrdinals
ordinalizeContainsTheSameNumber
one :: Spec
one =
it "returns the ordinal for 1" $
ordinal 1 `shouldBe` "st"
two :: Spec
two =
it "returns the ordinal for 2" $
ordinal 2 `shouldBe` "nd"
thousands :: Spec
thousands = do
it "returns the ordinal for 1002" $
ordinal 1002 `shouldBe` "nd"
it "returns the ordinal for 1003" $
ordinal 1003 `shouldBe` "rd"
negatives :: Spec
negatives = do
it "returns the ordinal for -11" $
ordinal (-11) `shouldBe` "th"
it "returns the ordinal for -1021" $
ordinal (-1021) `shouldBe` "st"
fullOrdinals :: Spec
fullOrdinals = do
it "returns the full ordinal for 1" $
ordinalize 1 `shouldBe` "1st"
it "returns the full ordinal for -1021" $
ordinalize (-1021) `shouldBe` "-1021st"
ordinalReturnsNotEmpty :: Spec
ordinalReturnsNotEmpty =
it "never returns empty" $ property $
property <$> not . null . ordinal
ordinalizeContainsTheSameNumber :: Spec
ordinalizeContainsTheSameNumber =
it "always returns the number as part of the result" $ property ordinalizeSamePrefix
ordinalizeSamePrefix :: Integer -> Bool
ordinalizeSamePrefix n = show n == take (length $ show n) (ordinalize n)

View File

@ -1,65 +0,0 @@
module Text.Inflections.OrdinalTest where
import Test.HUnit hiding (Test)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework (Test, testGroup)
import Text.Inflections (ordinal, ordinalize)
{-# ANN module "HLint: ignore Use camelCase" #-}
tests :: [Test]
tests = [ testGroup "ordinal"
[ testCase "1 -> st" test_ordinal1
, testCase "2 -> nd" test_ordinal2
, testCase "1002 -> nd" test_ordinal1002
, testCase "1003 -> rd" test_ordinal1003
, testCase "-11 -> th" test_ordinalNegative11
, testCase "-1021 -> st" test_ordinalNegative1021
, testProperty "notEmpty" prop_ordinalReturnsNotEmpty
]
, testGroup "ordinalize"
[ testCase "1 -> st" test_ordinalize1
, testCase "-1021 -> st" test_ordinalizeNegative1021
, testProperty "result contains number" prop_ordinalizeSamePrefix
]
]
----------------------------------------------------
test_ordinal1 :: Assertion
test_ordinal1 = "st" @?= ordinal 1
test_ordinal2 :: Assertion
test_ordinal2 = "nd" @?= ordinal 2
test_ordinal1002 :: Assertion
test_ordinal1002 = "nd" @?= ordinal 1002
test_ordinal1003 :: Assertion
test_ordinal1003 = "rd" @?= ordinal 1003
test_ordinalNegative11 :: Assertion
test_ordinalNegative11 = "th" @?= ordinal (-11)
test_ordinalNegative1021 :: Assertion
test_ordinalNegative1021 = "st" @?= ordinal (-1021)
----------------------------------------------------
test_ordinalize1 :: Assertion
test_ordinalize1 = "1st" @?= ordinalize 1
test_ordinalizeNegative1021 :: Assertion
test_ordinalizeNegative1021 = "-1021st" @?= ordinalize (-1021)
----------------------------------------------------
prop_ordinalReturnsNotEmpty :: Integer -> Bool
prop_ordinalReturnsNotEmpty = not . null . ordinal
prop_ordinalizeSamePrefix :: Integer -> Bool
prop_ordinalizeSamePrefix n = show n == take (length $ show n) (ordinalize n)

View File

@ -0,0 +1,90 @@
module Text.Inflections.PropertiesSpec (spec) where
import Data.Char (toLower)
import Data.List (group)
import Test.Hspec
import Test.QuickCheck
import Text.Inflections
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec = do
describe "dasherize"
dasherizeSpacedSentence
describe "transliterate" $ do
withSubstitutions
withoutSubstitutions
missingSubstitutions
describe "parameterize" $ do
onlyValidCharacters
notBeginWithSeparator
notEndWithSeparator
noMissingAlphanumerics
noMoreThanOneHyphen
withoutSubstitutions :: Spec
withoutSubstitutions =
it "transliterates without subsitutions" $
transliterate "this is a test" `shouldBe` "this is a test"
withSubstitutions :: Spec
withSubstitutions =
it "transliterates with substitution" $
transliterate "Feliz año nuevo" `shouldBe` "Feliz ano nuevo"
missingSubstitutions :: Spec
missingSubstitutions =
it "transliterates with missing substitutions" $
transliterate "Have a ❤ ñ!" `shouldBe` "Have a ? n!"
dasherizeSpacedSentence :: Spec
dasherizeSpacedSentence =
it "dasherizes a space separated sentence" $
dasherize [Word "foo", Word "bar"] `shouldBe` "foo-bar"
onlyValidCharacters :: Spec
onlyValidCharacters =
it "returns only valid characters" (property onlyValidCharactersPredicate)
where onlyValidCharactersPredicate sf = all (`elem` (alphaNumerics ++ "-_")) $ parameterize sf
notBeginWithSeparator :: Spec
notBeginWithSeparator =
it "never returns a string beginning ending with a separator" (property notBeginWithSeparatorPredicate)
where
notBeginWithSeparatorPredicate s =
let parameterized = parameterize s in
(not . null) parameterized ==> head parameterized /= '-'
notEndWithSeparator :: Spec
notEndWithSeparator =
it "never returns a string beginning with a separator" (property notBeginWithSeparatorPredicate)
where
notBeginWithSeparatorPredicate s =
let parameterized = parameterize s in
(not . null) parameterized ==> last parameterized /= '-'
noMissingAlphanumerics :: Spec
noMissingAlphanumerics =
it "returns every alphanumeric character from the input" (property noMissingAlphanumericsPredicate)
where noMissingAlphanumericsPredicate s =
let parameterized = parameterize s in
all (\c -> c `notElem` alphaNumerics ||
c `elem` (alphaNumerics ++ "-") &&
c `elem` parameterized) $ map toLower s
noMoreThanOneHyphen :: Spec
noMoreThanOneHyphen =
it "never returns a string with a sequence of dashes" (property noMoreThanOneHyphenPredicate)
where noMoreThanOneHyphenPredicate s =
let parameterized = parameterize s in longestSequenceOf '-' parameterized <= 1
longestSequenceOf :: Char -> String -> Int
longestSequenceOf _ [] = 0
longestSequenceOf c s =
if null subseqLengths then 0 else maximum subseqLengths
where subseqLengths = (map length . filter (\str -> head str == c) . group) s
alphaNumerics :: String
alphaNumerics = ['a'..'z'] ++ ['0'..'9']

View File

@ -1,107 +0,0 @@
module Text.Inflections.Tests where
import Test.HUnit hiding (Test)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.Framework.Providers.HUnit (testCase)
import Test.QuickCheck
import Test.Framework (Test, testGroup)
import Data.List (group)
import Data.Char (toLower)
import Text.Inflections
import Text.Inflections.Parse.Types (Word(..))
{-# ANN module "HLint: ignore Use camelCase" #-}
tests :: [Test]
tests = [testGroup "dasherize"
[ testCase "foo bar -> foo-bar" test_dasherize1
],
testGroup "transliterate"
[ testCase "Without substitutions" test_correctTransliterationWithoutSubs
, testCase "With substitutions" test_correctTransliterationWithSubs
, testCase "Missing subs" test_correctTransliterationMissingSubs
],
testGroup "parameterize"
[ testProperty "Contains only valid chars"
prop_parameterize1
, testProperty "Does not begin with a separator character"
prop_parameterize2
, testProperty "Does not end in a separator character"
prop_parameterize3
, testProperty "All alphanumerics in input exist in output"
prop_parameterize4
, testProperty "Doesn't have subsequences of more than one hyphen"
prop_parameterize5
]
]
test_correctTransliterationWithoutSubs :: Assertion
test_correctTransliterationWithoutSubs =
transliterate "this is a test" @?= "this is a test"
test_correctTransliterationWithSubs :: Assertion
test_correctTransliterationWithSubs =
transliterate "Feliz año nuevo" @?= "Feliz ano nuevo"
test_correctTransliterationMissingSubs :: Assertion
test_correctTransliterationMissingSubs =
transliterate "Have a ❤ ñ!" @?= "Have a ? n!"
fromRight :: Either a b -> b
fromRight (Left _) =
error "Either.Unwrap.fromRight: Argument takes form 'Left _'"
fromRight (Right x) = x
isRight :: Either a b -> Bool
isRight (Left _) = False
isRight (Right _) = True
test_dasherize1 :: Assertion
test_dasherize1 = "foo-bar" @?= dasherize [Word "foo", Word "bar"]
prop_parameterize1 :: String -> Bool
prop_parameterize1 sf = all (`elem` (alphaNumerics ++ "-_")) $
parameterize sf
prop_parameterize2 :: String -> Property
prop_parameterize2 s =
(not . null) parameterized ==> head parameterized /= '-'
where parameterized = parameterize s
prop_parameterize3 :: String -> Property
prop_parameterize3 s =
(not . null) parameterized ==> last parameterized /= '-'
where parameterized = parameterize s
prop_parameterize4 :: String -> Bool
prop_parameterize4 s = all (\c -> c `notElem` alphaNumerics ||
c `elem` (alphaNumerics ++ "-") &&
c `elem` parameterized) $ map toLower s
where parameterized = parameterize s
prop_parameterize5 :: String -> Bool
prop_parameterize5 s = longestSequenceOf '-' parameterized <= 1
where parameterized = parameterize s
-- Helper functions and shared tests
longestSequenceOf :: Char -> String -> Int
longestSequenceOf _ [] = 0
longestSequenceOf c s =
if null subseqLengths then 0 else maximum subseqLengths
where subseqLengths = (map length . filter (\str -> head str == c) . group) s
numMatching :: Eq a => a -> [a] -> Int
numMatching char str = length $ filter (== char) str
alphaNumerics :: String
alphaNumerics = ['a'..'z'] ++ ['0'..'9']

View File

@ -0,0 +1,21 @@
module Text.Inflections.TitleizeSpec (spec) where
import Test.Hspec
import Text.Inflections (titleize)
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec = do
twoWordsToTitleCase
oneWordToTitleCase
twoWordsToTitleCase :: Spec
twoWordsToTitleCase =
it "converts two words to title case" $
titleize [Word "Employee", Word "Salary"] `shouldBe` "Employee Salary"
oneWordToTitleCase :: Spec
oneWordToTitleCase =
it "converts one word to title case" $
titleize [Word "underground"] `shouldBe` "Underground"

View File

@ -1,28 +0,0 @@
module Text.Inflections.TitleizeTest where
import Test.HUnit hiding (Test)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework (Test, testGroup)
import Text.Inflections (titleize)
import Text.Inflections.Parse.Types (Word(..))
{-# ANN module "HLint: ignore Use camelCase" #-}
tests :: [Test]
tests = [ testGroup "titleize"
[ testCase "employee_salary -> Employee Salary" test_titleize1
, testCase "underground -> Underground" test_titleize2
]
]
----------------------------------------------------
test_titleize1 :: Assertion
test_titleize1 = "Employee Salary" @?=
titleize [Word "Employee", Word "Salary"]
test_titleize2 :: Assertion
test_titleize2 = "Underground" @?= titleize [Word "underground"]

View File

@ -0,0 +1,10 @@
module Text.Inflections.UnderscoreSpec (spec) where
import Test.Hspec
import Text.Inflections (underscore)
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec =
it "converts a word list to snake case" $
underscore [Word "test", Word "this"] `shouldBe` "test_this"

View File

@ -1,21 +0,0 @@
module Text.Inflections.UnderscoreTest where
import Test.HUnit hiding (Test)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework (Test, testGroup)
import Text.Inflections (underscore)
import Text.Inflections.Parse.Types (Word(..))
{-# ANN module "HLint: ignore Use camelCase" #-}
tests :: [Test]
tests = [testGroup "underscore"
[ testCase "testThis -> test_this" test_underscore
]
]
test_underscore :: Assertion
test_underscore = "test_this" @?= underscore [Word "test", Word "this"]

View File

@ -0,0 +1,25 @@
module Text.InflectionsSpec (spec) where
import Test.Hspec
import Text.Inflections (toUnderscore, toDashed, toCamelCased)
spec :: Spec
spec = do
camelCaseToSnakeCase
camelCaseToDashed
snakeCaseToCamelCase
camelCaseToSnakeCase :: Spec
camelCaseToSnakeCase =
it "converts camel case snake case" $
toUnderscore "camelCasedText" `shouldBe` "camel_cased_text"
camelCaseToDashed :: Spec
camelCaseToDashed =
it "converts camel case to dashed" $
toDashed "camelCasedText" `shouldBe` "camel-cased-text"
snakeCaseToCamelCase :: Spec
snakeCaseToCamelCase =
it "converts snake case to camel case" $
toCamelCased False "underscored_text" `shouldBe` "underscoredText"

View File

@ -1,32 +0,0 @@
module Text.InflectionsTest where
import Test.HUnit hiding (Test)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework (Test, testGroup)
import Text.Inflections (toUnderscore, toDashed, toCamelCased)
{-# ANN module "HLint: ignore Use camelCase" #-}
tests :: [Test]
tests = [ testGroup "toUnderscore"
[ testCase "camelCasedText -> camel_cased_text" test_to_underscore
]
, testGroup "toDashed"
[ testCase "camelCasedText -> camel-cased-text" test_to_dashed
]
, testGroup "toCamelCased"
[ testCase "underscored_text -> camelCasedText" test_to_camel_cased
]
]
test_to_underscore :: Assertion
test_to_underscore = "camel_cased_text" @?= toUnderscore "camelCasedText"
test_to_dashed :: Assertion
test_to_dashed = "camel-cased-text" @?= toDashed "camelCasedText"
test_to_camel_cased :: Assertion
test_to_camel_cased = "underscoredText" @?= toCamelCased False "underscored_text"