Update the docs to reflect the current state of the code

This commit is contained in:
mrkkrp 2016-12-21 15:15:47 +03:00
parent da792fdfec
commit 8560ec9fce
12 changed files with 155 additions and 124 deletions

View File

@ -1,92 +1,103 @@
{- |
Module : Text.Inflections
Description : Rails-like inflections library for common String transformations.
Copyright : (c) Justin Leitgeb
License : MIT
-- |
-- Module : Text.Inflections
-- Description : Rails-like inflections library for common String transformations.
-- Copyright : (c) Justin Leitgeb
-- License : MIT
--
-- Maintainer : justin@stackbuilders.com
-- Stability : unstable
-- Portability : portable
--
-- This module provides methods for common String transformations, similar
-- to the Inflections library found in Rails:
--
-- <http://api.rubyonrails.org/classes/ActiveSupport/Inflector.html>
--
-- While many of the functions in this library are the same as in
-- implementations in Rails' ActiveSupport, the philosophy of this library
-- is fundamentally different. Where Rails tries to be as permissive as
-- possible, and return a String when given any input, this library tries to
-- output strings that make sense according to the function that is called.
--
-- When you look closely at many of the functions in Rails' inflections
-- library, you will notice that many of them are partial. That is, they
-- only have well-defined output for some of the possible inputs to the
-- function allowed by the type system. As an example, let's take the
-- @underscore@ function. In Rails, it works like this:
--
-- >>> "fooBar".underscore
-- "foo_bar"
--
-- Looks OK so far. However, it's also easy to produce less expected results:
--
-- >>> "foo bar".underscore
-- "foo bar"
--
-- The output isn't underscored - it contains a space! It turns out that
-- some of the functions from Inflections in ActiveSupport are /partial/.
-- I.e., the outputs are really only specified for a certain range of the
-- inputs allowed by the String type.
--
-- In the Haskell inflections library, we aim to deliver more predictable
-- results by separating the parsing of strings into tokens from the
-- application of transformations. Let's see an example.
--
-- First, we tokenize an underscored String using 'parseSnakeCase':
--
-- >>> parseSnakeCase [] "foo_bar"
-- Right [Word "foo",Word "bar"]
--
-- We can chain together the tokenization of the input String and the
-- transformation to CamelCase by using 'Control.Monad.LiftM':
--
-- >>> import Control.Monad (liftM)
-- >>> liftM camelize $ parseSnakeCase "foo_bar"
-- Right "FooBar"
--
-- By separating out the tokenization from the application of inflections,
-- we also end up with useful libraries for validating input which can be
-- used independently:
--
-- >>> parseSnakeCase [] "fooBar"
-- 1:4:
-- unexpected 'B'
-- expecting '_', end of input, or lowercase letter
--
-- As of version 0.3.0.0, we don't permit creation of invalid 'Word's by
-- using of the smart constructors 'mkWord' and 'mkAcronym'. This is done
-- because not every 'Text' value is a valid 'Word', as it should not
-- contain whitespace, for example. Normal words have the type @'Word'
-- 'Normal'@, while acronyms have the type @'Word' 'Acronym'@. If you need
-- to have several words\/acronyms in a single list, use the existential
-- wrapper 'SomeWord'. Parsing functions now produce 'SomeWord's.
--
-- This library is still a work-in-progress, and contributions are welcome
-- for missing pieces and to fix bugs. Please see the Github page to
-- contribute with code or bug reports:
--
-- <https://github.com/stackbuilders/inflections-hs>
Maintainer : justin@stackbuilders.com
Stability : unstable
Portability : portable
This module provides methods for common String transformations, similar to the
"Inflections" library found in Rails:
<http://api.rubyonrails.org/classes/ActiveSupport/Inflector.html>
While many of the functions in this library are the same as in implementations
in Rails' ActiveSupport, the philosophy of this library is fundamentally
different. Where Rails tries to be as permissive as possible, and return a
String when given any input, this library tries to output strings that make
sense according to the function that is called.
When you look closely at many of the functions in Rails' inflections
library, you will notice that many of them are partial. That is, they only
have well-defined output for some of the possible inputs to the function allowed
by the type system. As an example, let's take the @underscore@ function. In
Rails, it works like this:
>>> "fooBar".underscore
"foo_bar"
Looks ok so far. However, it's also easy to produce less expected results:
>>> "foo bar".underscore
"foo bar"
The output isn't underscored - it contains a space! It turns out that some of
the functions from Inflections in ActiveSupport are /partial/. Ie., the outputs
are really only specified for a certain range of the inputs allowed by the
String type.
In the Haskell inflections library, we aim to deliver more predictable results
by separating the parsing of strings into tokens from the application of
transformations. Let's see an example.
First, we tokenize an underscored String using 'parseSnakeCase':
>>> parseSnakeCase [] "foo_bar"
Right [Word "foo",Word "bar"]
We can chain together the tokenization of the input String and the
transformation to CamelCase by using 'Control.Monad.LiftM':
>>> import Control.Monad (liftM)
>>> liftM camelize $ parseSnakeCase "foo_bar"
By separating out the tokenization from the application of inflections, we also
end up with useful libraries for validating input which can be used
independently:
>>> parseSnakeCase [] "fooBar"
Left "(unknown)" (line 1, column 4):
unexpected 'B'
expecting lowercase letter, "_" or end of input
This library is still a work-in-progress, and contributions are welcome for
missing pieces and to fix bugs. Please see the Github page to contribute with
code or bug reports:
<https://github.com/stackbuilders/inflections-hs>
-}
{-# LANGUAGE CPP #-}
module Text.Inflections
( camelize
( -- * Parsing
parseSnakeCase
, parseCamelCase
-- * Rendering
, camelize
, camelizeCustom
, dasherize
, humanize
, underscore
, titleize
, Transliterations
, defaultMap
, defaultTransliterations
, parameterize
, parameterizeCustom
, transliterate
, transliterateCustom
, ordinal
, ordinalize
, parseSnakeCase
, parseCamelCase
, ordinal
-- * Types and helpers
, Word
, WordType (..)
@ -107,7 +118,7 @@ import Control.Monad.Catch (MonadThrow (..))
import Data.Text (Text)
import Text.Inflections.Camelize (camelize, camelizeCustom)
import Text.Inflections.Dasherize (dasherize)
import Text.Inflections.Data (Transliterations, defaultMap)
import Text.Inflections.Data (Transliterations, defaultTransliterations)
import Text.Inflections.Humanize (humanize)
import Text.Inflections.Ordinal (ordinal, ordinalize)
import Text.Inflections.Parameterize (parameterize, parameterizeCustom)

View File

@ -27,7 +27,10 @@ import Control.Applicative
-- | Turn an input word list in into CamelCase.
--
-- >>> camelize [ Word "foo", Acronym "bar", Word "bazz" ]
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
-- >>> bazz <- SomeWord <$> mkAcronym "bazz"
-- >>> camelize [foo,bar,bazz]
-- "FoobarBazz"
camelize
:: [SomeWord] -- ^ Input words
@ -36,7 +39,10 @@ camelize = camelizeCustom True
-- | Turn an input word list into a CamelCase String.
--
-- >>> camelizeCustom False [ Word "foo", Acronym "bar", Word "bazz" ]
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
-- >>> bazz <- SomeWord <$> mkAcronym "bazz"
-- >>> camelizeCustom False [foo,bar,bazz]
-- "foobarBazz"
camelizeCustom
:: Bool -- ^ Whether to capitalize the first character in the output String

View File

@ -19,7 +19,7 @@ import Data.Text (Text)
import Text.Inflections.Types
import qualified Data.Text as T
-- | Replaces underscores in a snake_cased string with dashes (hyphens).
-- | Produce a string with words separated by dashes (hyphens).
--
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
@ -27,6 +27,6 @@ import qualified Data.Text as T
-- >>> dasherize [foo,bar,bazz]
-- "foo-bar-bazz"
dasherize
:: [SomeWord] -- ^ Input Words to separate with dashes
-> Text -- ^ The dasherized String
:: [SomeWord] -- ^ Input words to separate with dashes
-> Text -- ^ The dasherized 'Text'
dasherize = T.intercalate "-" . fmap (unSomeWord T.toLower)

View File

@ -9,19 +9,25 @@
--
-- Auxiliary data used in the library.
module Text.Inflections.Data where
module Text.Inflections.Data
( Transliterations
, defaultTransliterations )
where
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as M
-- |A 'Data.Map.Map' containing mappings from international characters to
-- | A 'HashMap' containing mappings from international characters to
-- sequences approximating these characters within the ASCII range.
type Transliterations = HashMap Char String
-- |These default transliterations stolen from the Ruby i18n library - see
-- | These default transliterations are stolen from the Ruby i18n library -
-- see
-- <https://github.com/svenfuchs/i18n/blob/master/lib/i18n/backend/transliterator.rb#L41:L69>.
defaultMap :: Transliterations
defaultMap = M.fromList [
--
-- NOTE: before version 0.3.0.0 this was called @defaultMap@.
defaultTransliterations :: Transliterations
defaultTransliterations = M.fromList [
('À', "A"), ('Á', "A"), ('Â', "A"), ('Ã', "A"), ('Ä', "A"), ('Å', "A"),
('Æ', "AE"), ('Ç', "C"), ('È', "E"), ('É', "E"), ('Ê', "E"), ('Ë', "E"),
('Ì', "I"), ('Í', "I"), ('Î', "I"), ('Ï', "I"), ('Ð', "D"), ('Ñ', "N"),

View File

@ -24,17 +24,17 @@ import qualified Data.Text as T
import Control.Applicative
#endif
-- |Capitalizes the first word and turns underscores into spaces. Like
-- | Capitalize the first word and separate words with spaces. Like
-- 'Text.Inflections.Titleize.titleize', this is meant for creating pretty
-- output.
--
-- >>> humanize [Word "foo", Acronym "bar", Word "bazz"]
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
-- >>> bazz <- SomeWord <$> mkWord "bazz"
-- >>> humanize [foo,bar,bazz]
-- "Foo bar bazz"
--
-- Note that as of version 0.3.0.0 @Word@ and @Acronym@ constructors are
-- hidden, but you still can construct them with 'mkWord' and 'mkAcronym'.
humanize
:: [SomeWord] -- ^ List of Words, first of which will be capitalized
:: [SomeWord] -- ^ List of words, first of which will be capitalized
-> Text -- ^ The humanized output
humanize xs' =
case unSomeWord (T.replace "_" " ") <$> xs' of

View File

@ -12,14 +12,26 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Inflections.Ordinal
( ordinal
, ordinalize )
( ordinalize
, ordinal )
where
import Data.Monoid ((<>))
import Data.Text (Text)
import qualified Data.Text as T
-- |Turns a number into an ordinal string used to denote the position in an
-- ordered sequence such as 1st, 2nd, 3rd, 4th.
--
-- >>> ordinalize 1
-- "1st"
-- >>> ordinalize 2
-- "2nd"
-- >>> ordinalize 10
-- "10th"
ordinalize :: (Integral a, Show a) => a -> Text
ordinalize n = T.pack (show n) <> ordinal n
-- |Returns the suffix that should be added to a number to denote the position
-- in an ordered sequence such as 1st, 2nd, 3rd, 4th.
--
@ -39,16 +51,3 @@ ordinal number
where abs_number = abs number
remainder10 = abs_number `mod` 10
remainder100 = abs_number `mod` 100
-- |Turns a number into an ordinal string used to denote the position in an
-- ordered sequence such as 1st, 2nd, 3rd, 4th.
--
-- >>> ordinalize 1
-- "1st"
-- >>> ordinalize 2
-- "2nd"
-- >>> ordinalize 10
-- "10th"
ordinalize :: (Integral a, Show a) => a -> Text
ordinalize n = T.pack (show n) <> ordinal n
{-# INLINE ordinalize #-}

View File

@ -27,13 +27,13 @@ import qualified Data.Text as T
import Control.Applicative
#endif
-- |Replaces special characters in a string so that it may be used as part of a
-- 'pretty' URL. Uses the default transliterations in this library.
-- | Replace special characters in a string so that it may be used as part
-- of a 'pretty' URL. Uses the 'defaultTransliterations'.
parameterize :: Text -> Text
parameterize = parameterizeCustom defaultMap
parameterize = parameterizeCustom defaultTransliterations
{-# INLINE parameterize #-}
-- |Transliterate 'Text' with a custom transliteration table.
-- | Transliterate 'Text' with a custom transliteration table.
parameterizeCustom :: Transliterations -> Text -> Text
parameterizeCustom m txt = (T.intercalate "-" . T.words) (T.unfoldr f ("", txt))
where

View File

@ -30,11 +30,14 @@ import Prelude hiding (Word)
-- | Parse a CamelCase string.
--
-- >>> parseCamelCase ["Bar"] "FooBarBazz"
-- >>> bar <- mkAcronym "bar"
-- >>> parseCamelCase [bar] "FooBarBazz"
-- Right [Word "Foo",Acronym "Bar",Word "Bazz"]
--
-- >>> parseCamelCase [] "foo_bar_bazz"
-- Left "(unknown)" (line 1, column 4):
-- 1:4:
-- unexpected '_'
-- expecting end of input, lowercase letter, or uppercase letter
parseCamelCase
:: [Word 'Acronym] -- ^ Collection of acronyms
-> Text -- ^ Input

View File

@ -34,8 +34,9 @@ import Prelude hiding (Word)
-- Right [Word "foo",Acronym "bar",Word "bazz"]
--
-- >>> parseSnakeCase [] "fooBarBazz"
-- Left "(unknown)" (line 1, column 4):
-- 1:4:
-- unexpected 'B'
-- expecting '_', end of input, or lowercase letter
parseSnakeCase
:: [Word 'Acronym] -- ^ Collection of acronyms
-> Text -- ^ Input

View File

@ -19,9 +19,12 @@ import qualified Data.Text as T
-- | Capitalize all the Words in the input list.
--
-- >>> titleize [ Word "foo", Acronym "bar", Word "bazz" ]
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
-- >>> bazz <- SomeWord <$> mkWord "bazz"
-- >>> titleize [foo,bar,bazz]
-- "Foo bar Bazz"
titleize
:: [SomeWord] -- ^ List of Words, first of which will be capitalized
-> Text -- ^ The titleized String
:: [SomeWord] -- ^ List of words, first of which will be capitalized
-> Text -- ^ The titleized 'Text'
titleize = T.unwords . fmap (unSomeWord T.toTitle)

View File

@ -27,15 +27,14 @@ import qualified Data.Text as T
import Control.Applicative
#endif
-- |Returns a String after default approximations for changing Unicode
-- | Returns a 'Text' after default approximations for changing Unicode
-- characters to a valid ASCII range are applied. If you want to supplement
-- the default approximations with your own, you should use the
-- 'transliterateCustom' function instead of 'transliterate'.
transliterate :: Text -> Text
transliterate = transliterateCustom "?" defaultMap
{-# INLINE transliterate #-}
transliterate = transliterateCustom "?" defaultTransliterations
-- |Returns a String after default approximations for changing Unicode
-- | Returns a 'Text' after default approximations for changing Unicode
-- characters to a valid ASCII range are applied.
transliterateCustom
:: String -- ^ The default replacement

View File

@ -19,11 +19,14 @@ import Data.Text (Text)
import Text.Inflections.Types
import qualified Data.Text as T
-- |Turns a CamelCase string into an underscore_separated 'Text'.
-- | Separate given words by underscores.
--
-- >>> underscore [ Word "foo", Acronym "bar", Word "bazz" ]
-- >>> foo <- SomeWord <$> mkWord "foo"
-- >>> bar <- SomeWord <$> mkAcronym "bar"
-- >>> bazz <- SomeWord <$> mkWord "bazz"
-- >>> underscore [foo,bar,bazz]
-- "foo_bar_bazz"
underscore
:: [SomeWord] -- ^ Input Words to separate with underscores
:: [SomeWord] -- ^ Input words to separate with underscores
-> Text -- ^ The underscored String
underscore = T.intercalate "_" . fmap (unSomeWord T.toLower)