Better define what a word is, tests for ‘Types.hs’

This commit is contained in:
mrkkrp 2016-12-21 20:01:14 +03:00
parent 4d3bb48d7b
commit 2348bb717c
4 changed files with 68 additions and 13 deletions

View File

@ -31,7 +31,7 @@ module Text.Inflections.Types
where where
import Control.Monad.Catch import Control.Monad.Catch
import Data.Char (isSpace) import Data.Char (isAlphaNum)
import Data.Data (Data) import Data.Data (Data)
import Data.Text (Text) import Data.Text (Text)
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
@ -43,28 +43,30 @@ import qualified Data.Text as T
import Prelude hiding (Word) import Prelude hiding (Word)
#endif #endif
-- | Create a word from given 'Text'. The input should not contain spaces or -- | Create a word from given 'Text'. The input should consist of only
-- alpha-numeric characters (no white spaces or punctuation)
-- 'InflectionInvalidWord' will be thrown. -- 'InflectionInvalidWord' will be thrown.
-- --
-- /since 0.3.0.0/ -- /since 0.3.0.0/
mkWord :: MonadThrow m => Text -> m (Word 'Normal) mkWord :: MonadThrow m => Text -> m (Word 'Normal)
mkWord txt = mkWord txt =
if T.any isSpace txt if T.all isAlphaNum txt
then throwM (InflectionInvalidWord txt) then return (Word txt)
else return (Word txt) else throwM (InflectionInvalidWord txt)
-- | Create an acronym from given 'Text'. The input should not contain -- | Create an acronym from given 'Text'. The input should consist of only
-- spaces or 'InflectionInvalidAcronym' will be thrown. Acronym is different -- alpha-numeric characters 'InflectionInvalidAcronym' will be thrown.
-- from normal word by that it may not be transformed by inflections. -- Acronym is different from normal word by that it may not be transformed
-- by inflections (also see 'unSomeWord').
-- --
-- /since 0.3.0.0/ -- /since 0.3.0.0/
mkAcronym :: MonadThrow m => Text -> m (Word 'Acronym) mkAcronym :: MonadThrow m => Text -> m (Word 'Acronym)
mkAcronym txt = mkAcronym txt =
if T.any isSpace txt if T.all isAlphaNum txt
then throwM (InflectionInvalidAcronym txt) then return (Word txt)
else return (Word txt) else throwM (InflectionInvalidAcronym txt)
-- | A 'Text' value that should be kept whole through applied inflections. -- | A 'Text' value that should be kept whole through applied inflections.

View File

@ -78,5 +78,6 @@ test-suite test
, Text.Inflections.Parse.SnakeCaseSpec , Text.Inflections.Parse.SnakeCaseSpec
, Text.Inflections.TitleizeSpec , Text.Inflections.TitleizeSpec
, Text.Inflections.TransliterateSpec , Text.Inflections.TransliterateSpec
, Text.Inflections.TypesSpec
, Text.Inflections.UnderscoreSpec , Text.Inflections.UnderscoreSpec
, Text.InflectionsSpec , Text.InflectionsSpec

View File

@ -19,8 +19,9 @@ spec = describe "humazine" $ do
humanize [employee,salary] `shouldBe` "Employee salary" humanize [employee,salary] `shouldBe` "Employee salary"
it "turns underscores into spaces" $ do it "turns underscores into spaces" $ do
employee <- SomeWord <$> mkWord "employee" employee <- SomeWord <$> mkWord "employee"
hasSalary <- SomeWord <$> mkWord "has_salary" has <- SomeWord <$> mkWord "has"
humanize [employee, hasSalary] `shouldBe` "Employee has salary" salary <- SomeWord <$> mkWord "salary"
humanize [employee, has, salary] `shouldBe` "Employee has salary"
it "capitalizes the first word of a sentence" $ do it "capitalizes the first word of a sentence" $ do
underground <- SomeWord <$> mkWord "underground" underground <- SomeWord <$> mkWord "underground"
humanize [underground] `shouldBe` "Underground" humanize [underground] `shouldBe` "Underground"

View File

@ -0,0 +1,51 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.TypesSpec
( spec )
where
import Test.Hspec
import Text.Inflections
import qualified Data.Text as T
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
spec :: Spec
spec = do
describe "mkWord" $ do
context "when provided a correct Text value" $
it "creates a normal word" $ do
x <- mkWord "foo"
unWord x `shouldBe` "foo"
context "when provided an incorrect Text value" $
it "throws the correct exception" $ do
mkWord "foo bar" `shouldThrow` (== InflectionInvalidWord "foo bar")
mkWord "foo_" `shouldThrow` (== InflectionInvalidWord "foo_")
mkWord "&$?%" `shouldThrow` (== InflectionInvalidWord "&$?%")
describe "mkAcronym" $ do
context "when provided a correct Text value" $
it "creates an acronym" $ do
x <- mkAcronym "foo"
unWord x `shouldBe` "foo"
context "when providde an incorrect Text value" $
it "throws the correct exception" $ do
mkAcronym "foo bar" `shouldThrow` (== InflectionInvalidAcronym "foo bar")
mkAcronym "foo_" `shouldThrow` (== InflectionInvalidAcronym "foo_")
mkAcronym "&$?%" `shouldThrow` (== InflectionInvalidAcronym "&$?%")
describe "unWord" $
it "extracts the inner Text value" $ do
(unWord <$> mkWord "foo") `shouldReturn` "foo"
(unWord <$> mkWord "bar") `shouldReturn` "bar"
(unWord <$> mkAcronym "baz") `shouldReturn` "baz"
describe "unSomeWord" $ do
context "when inner value is a normal word" $
it "Text is extracted and the given function applied" $ do
x <- SomeWord <$> mkWord "word"
unSomeWord T.toUpper x `shouldBe` "WORD"
context "when inner value is an acronym" $
it "Text is extracted, but the function is not applied" $ do
x <- SomeWord <$> mkAcronym "acronym"
unSomeWord T.toUpper x `shouldBe` "acronym"