Implement humanizeCustom to enable optional capitalization of first word

This commit is contained in:
Richard Cook 2017-07-22 09:22:13 -06:00
parent f103a07970
commit a902fa0e7a
3 changed files with 66 additions and 17 deletions

View File

@ -96,6 +96,7 @@ module Text.Inflections
, camelizeCustom
, dasherize
, humanize
, humanizeCustom
, underscore
, titleize
, Transliterations
@ -118,7 +119,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)

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"