Merge pull request #40 from stackbuilders/improve-tests

Improve tests, make them more idiomatic
This commit is contained in:
Mark Karpov 2016-07-13 16:46:31 +04:00 committed by GitHub
commit 5b718ca4f3
10 changed files with 133 additions and 190 deletions

View File

@ -32,17 +32,17 @@ library
, Text.Inflections.Parse.Types
other-modules: Text.Inflections.Data
, Text.Inflections.Parameterize
, Text.Inflections.Humanize
, Text.Inflections.Underscore
, Text.Inflections.Camelize
, Text.Inflections.Dasherize
, Text.Inflections.Humanize
, Text.Inflections.Ordinal
, Text.Inflections.Parameterize
, Text.Inflections.Parse.Acronym
, Text.Inflections.Parse.CamelCase
, Text.Inflections.Parse.SnakeCase
, Text.Inflections.Titleize
, Text.Inflections.Transliterate
, Text.Inflections.Parse.Acronym
, Text.Inflections.Parse.SnakeCase
, Text.Inflections.Parse.CamelCase
, Text.Inflections.Underscore
if flag(dev)
ghc-options: -Wall -Werror
@ -70,9 +70,11 @@ test-suite test
else
ghc-options: -O2 -Wall
default-language: Haskell2010
other-modules: Text.Inflections.HumanizeSpec
other-modules: Text.Inflections.DasherizeSpec
, Text.Inflections.HumanizeSpec
, Text.Inflections.OrdinalSpec
, Text.Inflections.PropertiesSpec
, Text.Inflections.ParametrizeSpec
, Text.Inflections.TitleizeSpec
, Text.Inflections.TransliterateSpec
, Text.Inflections.UnderscoreSpec
, Text.InflectionsSpec

View File

@ -0,0 +1,15 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.DasherizeSpec
( spec )
where
import Test.Hspec
import Text.Inflections (dasherize)
import Text.Inflections.Parse.Types (Word (..))
spec :: Spec
spec = describe "dasherize" $
it "dasherizes a collection of words sentence" $
dasherize [Word "foo", Word "bar"] `shouldBe` "foo-bar"

View File

@ -8,16 +8,10 @@ import Text.Inflections (humanize)
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec = do
snakeCaseHumanize
capitalizeFirstWord
snakeCaseHumanize :: Spec
snakeCaseHumanize =
spec = describe "humazine" $ do
it "converts snake case to a human-readable string" $
humanize [Word "employee", Word "salary"] `shouldBe` "Employee salary"
capitalizeFirstWord :: Spec
capitalizeFirstWord =
it "turns underscores into spaces" $
humanize [Word "employee", Word "has_salary"] `shouldBe` "Employee has salary"
it "capitalizes the first word of a sentence" $
humanize [Word "underground"] `shouldBe` "Underground"

View File

@ -17,55 +17,26 @@ import Control.Applicative
spec :: Spec
spec = do
describe "ordinal" $ do
one
two
thousands
negatives
ordinalReturnsNotEmpty
it "returns the ordinal for 1" $
ordinal (1 :: Integer) `shouldBe` "st"
it "returns the ordinal for 2" $
ordinal (2 :: Integer) `shouldBe` "nd"
it "returns the ordinal for 1002" $
ordinal (1002 :: Integer) `shouldBe` "nd"
it "returns the ordinal for 1003" $
ordinal (1003 :: Integer) `shouldBe` "rd"
it "returns the ordinal for -11" $
ordinal (-11 :: Integer) `shouldBe` "th"
it "returns the ordinal for -1021" $
ordinal (-1021 :: Integer) `shouldBe` "st"
it "never returns empty output" $ property $
property <$> not . T.null . (ordinal :: Integer -> Text)
describe "ordinalize" $ do
fullOrdinals
ordinalizeContainsTheSameNumber
one :: Spec
one =
it "returns the ordinal for 1" $
ordinal (1 :: Integer) `shouldBe` "st"
two :: Spec
two =
it "returns the ordinal for 2" $
ordinal (2 :: Integer) `shouldBe` "nd"
thousands :: Spec
thousands = do
it "returns the ordinal for 1002" $
ordinal (1002 :: Integer) `shouldBe` "nd"
it "returns the ordinal for 1003" $
ordinal (1003 :: Integer) `shouldBe` "rd"
negatives :: Spec
negatives = do
it "returns the ordinal for -11" $
ordinal (-11 :: Integer) `shouldBe` "th"
it "returns the ordinal for -1021" $
ordinal (-1021 :: Integer) `shouldBe` "st"
fullOrdinals :: Spec
fullOrdinals = do
it "returns the full ordinal for 1" $
ordinalize (1 :: Integer) `shouldBe` "1st"
it "returns the full ordinal for -1021" $
ordinalize (-1021 :: Integer) `shouldBe` "-1021st"
ordinalReturnsNotEmpty :: Spec
ordinalReturnsNotEmpty =
it "never returns empty" $ property $
property <$> not . T.null . (ordinal :: Integer -> Text)
ordinalizeContainsTheSameNumber :: Spec
ordinalizeContainsTheSameNumber =
it "always returns the number as part of the result" $ property ordinalizeSamePrefix
ordinalizeSamePrefix :: Integer -> Bool
ordinalizeSamePrefix n = T.pack s == T.take (length s) (ordinalize n)
where s = show n
it "returns the full ordinal for 1" $
ordinalize (1 :: Integer) `shouldBe` "1st"
it "returns the full ordinal for -1021" $
ordinalize (-1021 :: Integer) `shouldBe` "-1021st"
it "always returns the number as prefix of the result" $
property $ \n ->
let s = show (n :: Integer)
in T.pack s == T.take (length s) (ordinalize n)

View File

@ -0,0 +1,39 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.ParametrizeSpec (spec) where
import Data.Char (toLower)
import Data.List (group)
import Test.Hspec
import Test.QuickCheck
import Text.Inflections
import qualified Data.Text as T
spec :: Spec
spec =
describe "parameterize" $ do
it "returns only valid characters" $ property $ \sf ->
T.all (`elem` (alphaNumerics ++ "-_")) $ parameterize (T.pack sf)
it "never returns a string beginning with a separator" $ property $ \s ->
let parameterized = parameterize (T.pack s)
in (not . T.null) parameterized ==> T.head parameterized /= '-'
it "never returns a string ending with a separator" $ property $ \s ->
let parameterized = parameterize (T.pack s) in
(not . T.null) parameterized ==> T.last parameterized /= '-'
it "returns every alphanumeric character from the input" $ property $ \s ->
let parameterized = parameterize (T.pack s)
in all (\c -> c `notElem` alphaNumerics ||
c `elem` (alphaNumerics ++ "-") &&
c `elem` T.unpack parameterized) $ map toLower s
it "never returns a string with a sequence of dashes" $ property $ \s ->
let parameterized = parameterize (T.pack s)
in longestSequenceOf '-' (T.unpack 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,94 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.PropertiesSpec (spec) where
import Data.Char (toLower)
import Data.List (group)
import Test.Hspec
import Test.QuickCheck
import qualified Data.Text as T
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
= T.all (`elem` (alphaNumerics ++ "-_")) $ parameterize (T.pack sf)
notBeginWithSeparator :: Spec
notBeginWithSeparator =
it "never returns a string beginning ending with a separator" (property notBeginWithSeparatorPredicate)
where
notBeginWithSeparatorPredicate s =
let parameterized = parameterize (T.pack s) in
(not . T.null) parameterized ==> T.head parameterized /= '-'
notEndWithSeparator :: Spec
notEndWithSeparator =
it "never returns a string beginning with a separator" (property notBeginWithSeparatorPredicate)
where
notBeginWithSeparatorPredicate s =
let parameterized = parameterize (T.pack s) in
(not . T.null) parameterized ==> T.last parameterized /= '-'
noMissingAlphanumerics :: Spec
noMissingAlphanumerics =
it "returns every alphanumeric character from the input" (property noMissingAlphanumericsPredicate)
where noMissingAlphanumericsPredicate s =
let parameterized = parameterize (T.pack s) in
all (\c -> c `notElem` alphaNumerics ||
c `elem` (alphaNumerics ++ "-") &&
c `elem` T.unpack 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 (T.pack s)
in longestSequenceOf '-' (T.unpack 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

@ -8,16 +8,8 @@ import Text.Inflections (titleize)
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec = do
twoWordsToTitleCase
oneWordToTitleCase
twoWordsToTitleCase :: Spec
twoWordsToTitleCase =
spec = describe "titleize" $ do
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

@ -0,0 +1,29 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.TransliterateSpec
( spec )
where
import Test.Hspec
import Text.Inflections (transliterate)
spec :: Spec
spec = describe "transliterate" $ do
withSubstitutions
withoutSubstitutions
missingSubstitutions
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!"

View File

@ -7,6 +7,6 @@ import Text.Inflections (underscore)
import Text.Inflections.Parse.Types (Word(..))
spec :: Spec
spec =
spec = describe "underscore" $
it "converts a word list to snake case" $
underscore [Word "test", Word "this"] `shouldBe` "test_this"

View File

@ -7,21 +7,16 @@ import Text.Inflections (toUnderscore, toDashed, toCamelCased)
spec :: Spec
spec = do
camelCaseToSnakeCase
camelCaseToDashed
snakeCaseToCamelCase
camelCaseToSnakeCase :: Spec
camelCaseToSnakeCase =
it "converts camel case snake case" $
toUnderscore "camelCasedText" `shouldReturn` "camel_cased_text"
camelCaseToDashed :: Spec
camelCaseToDashed =
it "converts camel case to dashed" $
toDashed "camelCasedText" `shouldReturn` "camel-cased-text"
snakeCaseToCamelCase :: Spec
snakeCaseToCamelCase =
it "converts snake case to camel case" $
toCamelCased False "underscored_text" `shouldReturn` "underscoredText"
describe "toUnderscore" $
it "converts camel case to snake case" $
toUnderscore "camelCasedText" `shouldReturn` "camel_cased_text"
describe "toDashed" $
it "converts camel case to dashed" $
toDashed "camelCasedText" `shouldReturn` "camel-cased-text"
describe "toCamelCased" $ do
context "when the first argument is False" $
it "converts snake case to camel case" $
toCamelCased False "underscored_text" `shouldReturn` "underscoredText"
context "when the first argument is True" $
it "converts snake case to camel case" $
toCamelCased True "underscored_text" `shouldReturn` "UnderscoredText"