Merge pull request #48 from rcook/rcook-to-humanized

Implement humanizeCustom and toHumanized helper functions
This commit is contained in:
Cristhian Motoche 2017-07-24 07:45:33 -05:00 committed by GitHub
commit 32e69f8545
4 changed files with 101 additions and 24 deletions

View File

@ -96,6 +96,7 @@ module Text.Inflections
, camelizeCustom
, dasherize
, humanize
, humanizeCustom
, underscore
, titleize
, Transliterations
@ -110,6 +111,7 @@ module Text.Inflections
, toUnderscore
, toDashed
, toCamelCased
, toHumanized
, betterThrow )
where
@ -118,7 +120,7 @@ import Data.Text (Text)
import Text.Inflections.Camelize (camelize, camelizeCustom)
import Text.Inflections.Dasherize (dasherize)
import Text.Inflections.Data (Transliterations, defaultTransliterations)
import Text.Inflections.Humanize (humanize)
import Text.Inflections.Humanize (humanize, humanizeCustom)
import Text.Inflections.Ordinal (ordinal, ordinalize)
import Text.Inflections.Parameterize (parameterize, parameterizeCustom)
import Text.Inflections.Parse.CamelCase (parseCamelCase)
@ -152,20 +154,39 @@ toDashed :: Text -> Either (ParseError Char Dec) Text
toDashed = fmap dasherize . parseCamelCase []
-- | Transforms underscored_text to CamelCasedText. If first argument is
-- 'True' then FirstCharacter in result string will be in upper case. If
-- 'False' then firstCharacter will be in lower case.
-- 'True' then the first character in the result string will be in upper case. If
-- 'False' then the first character will be in lower case.
--
-- > toCamelCased t = fmap (camelizeCustom t) . parseSnakeCase []
-- > toCamelCased c = fmap (camelizeCustom c) . parseSnakeCase []
--
-- >>> toCamelCased True "foo_bar_bazz"
-- "FooBarBazz"
-- >>> toCamelCased False "foo_bar_bazz"
-- "fooBarBazz"
toCamelCased
:: Bool -- ^ Capitalize the first character
-> Text -- ^ Input
-> Either (ParseError Char Dec) Text -- ^ Ouput
toCamelCased t = fmap (camelizeCustom t) . parseSnakeCase []
:: Bool -- ^ Capitalize the first character
-> Text -- ^ Input
-> Either (ParseError Char Dec) Text -- ^ Output
toCamelCased c = fmap (camelizeCustom c) . parseSnakeCase []
-- | Transforms underscored_text to space-separated human-readable text.
-- If first argument is 'True' then the first character in the result
-- string will be in upper case. If 'False' then the first character will be
-- in lower case.
--
-- > toHumanized c = fmap (humanizeCustom c) . parseSnakeCase []
--
-- >>> toHumanized True "foo_bar_bazz"
-- "Foo bar bazz"
-- >>> toHumanized False "foo_bar_bazz"
-- "foo bar bazz"
--
-- /since 0.3.0.0/
toHumanized
:: Bool -- ^ Capitalize the first character
-> Text -- ^ Input
-> Either (ParseError Char Dec) Text -- ^ Output
toHumanized c = fmap (humanizeCustom c) . parseSnakeCase []
-- | Lift something of type @'Either' ('ParseError' 'Char' 'Dec') a@ to
-- an instance of 'MonadThrow'. Useful when you want to shortcut on parsing

View File

@ -13,7 +13,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.Humanize
( humanize )
( humanize
, humanizeCustom )
where
import Data.Text (Text)
@ -36,7 +37,27 @@ import Control.Applicative
humanize
:: [SomeWord] -- ^ List of words, first of which will be capitalized
-> Text -- ^ The humanized output
humanize xs' =
humanize = humanizeCustom True
-- | Separate words with spaces, optionally capitalizing the first word. Like
-- 'Text.Inflections.Titleize.titleize', this is meant for creating pretty
-- output.
--
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
-- >>> bazz <- SomeWord <$> mkWord "bazz"
-- >>> humanizeCustom True [foo,bar,bazz]
-- "Foo bar bazz"
-- >>> humanizeCustom False [foo,bar,bazz]
-- "foo bar bazz"
--
-- /since 0.3.0.0/
humanizeCustom
:: Bool -- ^ Whether to capitalize the first character in the output String
-> [SomeWord] -- ^ List of words, first of which will be capitalized
-> Text -- ^ The humanized output
humanizeCustom c xs' =
case unSomeWord (T.replace "_" " ") <$> xs' of
[] -> ""
(x:xs) -> T.unwords $ T.toTitle x : (T.toLower <$> xs)
(x:xs) -> T.unwords $ (if c then T.toTitle else T.toLower) x : (T.toLower <$> xs)

View File

@ -12,16 +12,43 @@ import Control.Applicative
#endif
spec :: Spec
spec = describe "humazine" $ do
it "converts snake case to a human-readable string" $ do
employee <- SomeWord <$> mkWord "employee"
salary <- SomeWord <$> mkWord "salary"
humanize [employee,salary] `shouldBe` "Employee salary"
it "turns underscores into spaces" $ do
employee <- SomeWord <$> mkWord "employee"
has <- SomeWord <$> mkWord "has"
salary <- SomeWord <$> mkWord "salary"
humanize [employee, has, salary] `shouldBe` "Employee has salary"
it "capitalizes the first word of a sentence" $ do
underground <- SomeWord <$> mkWord "underground"
humanize [underground] `shouldBe` "Underground"
spec = do
describe "humanize" $ do
it "converts snake case to a human-readable string" $ do
employee <- SomeWord <$> mkWord "employee"
salary <- SomeWord <$> mkWord "salary"
humanize [employee,salary] `shouldBe` "Employee salary"
it "turns underscores into spaces" $ do
employee <- SomeWord <$> mkWord "employee"
has <- SomeWord <$> mkWord "has"
salary <- SomeWord <$> mkWord "salary"
humanize [employee, has, salary] `shouldBe` "Employee has salary"
it "capitalizes the first word of a sentence" $ do
underground <- SomeWord <$> mkWord "underground"
humanize [underground] `shouldBe` "Underground"
describe "humanizeCustom False" $ do
it "converts snake case to a human-readable string" $ do
employee <- SomeWord <$> mkWord "employee"
salary <- SomeWord <$> mkWord "salary"
humanizeCustom False [employee,salary] `shouldBe` "employee salary"
it "turns underscores into spaces" $ do
employee <- SomeWord <$> mkWord "employee"
has <- SomeWord <$> mkWord "has"
salary <- SomeWord <$> mkWord "salary"
humanizeCustom False [employee, has, salary] `shouldBe` "employee has salary"
it "lower-cases the first word of a sentence" $ do
underground <- SomeWord <$> mkWord "underground"
humanizeCustom False [underground] `shouldBe` "underground"
describe "humanizeCustom True" $ do
it "converts snake case to a human-readable string" $ do
employee <- SomeWord <$> mkWord "employee"
salary <- SomeWord <$> mkWord "salary"
humanizeCustom True [employee,salary] `shouldBe` "Employee salary"
it "turns underscores into spaces" $ do
employee <- SomeWord <$> mkWord "employee"
has <- SomeWord <$> mkWord "has"
salary <- SomeWord <$> mkWord "salary"
humanizeCustom True [employee, has, salary] `shouldBe` "Employee has salary"
it "capitalizes the first word of a sentence" $ do
underground <- SomeWord <$> mkWord "underground"
humanizeCustom True [underground] `shouldBe` "Underground"

View File

@ -27,6 +27,14 @@ spec = do
it "converts snake case to camel case with the first word capitalized" $
toCamelCased True "underscored_text" `shouldBe` Right "UnderscoredText"
describe "toHumanized" $ do
context "when the first argument is False" $
it "converts snake case to human-readable form with lower-case initial letter" $
toHumanized False "underscored_text" `shouldBe` Right "underscored text"
context "when the first argument is True" $
it "converts snake case to human-readable form with the first word capitalized" $
toHumanized True "underscored_text" `shouldBe` Right "Underscored text"
describe "betterThrow" $ do
context "when given a parse error" $
it "throws the correct exception" $