Achieve 100% Haddock coverage

This commit is contained in:
mrkkrp 2016-06-23 17:54:50 +03:00
parent c655520942
commit 3f9e15b664
14 changed files with 181 additions and 21 deletions

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Camelize
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Conversion to CamelCased phrases.
module Text.Inflections.Camelize ( camelize, camelizeCustom ) where
import Text.Inflections.Parse.Types (Word(..))
@ -10,7 +21,6 @@ import Prelude (String, Bool(..), concatMap, (.), zip, ($), repeat)
--
-- >>> camelize [ Word "foo", Acronym "bar", Word "bazz" ]
-- "FoobarBazz"
camelize
:: [Word] -- ^ Input Words to separate with underscores
-> String -- ^ The camelized String
@ -20,14 +30,12 @@ camelize = camelizeCustom True
--
-- >>> camelizeCustom False [ Word "foo", Acronym "bar", Word "bazz" ]
-- "foobarBazz"
camelizeCustom
:: Bool -- ^ Whether to capitalize the first character in the output String
-> [Word] -- ^ The input Words
-> String -- ^ The camelized String
camelizeCustom isFirstCap = concatMap (caseForWord isFirstCap) . isFirstList
caseForWord :: Bool -> (Word, Bool) -> String
caseForWord True (Word (c:cs), True) = toUpper c : cs
caseForWord False (Word (c:cs), True) = toLower c : cs

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Dasherize
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Conversion to dasherized phrases.
module Text.Inflections.Dasherize ( dasherize ) where
import Text.Inflections.Parse.Types (Word(..))
@ -7,8 +18,7 @@ import Data.List (intercalate)
import Prelude (String, (.), map)
-- | Replaces underscores in a snake_cased string with dashes (hyphens).
-- |
--
-- >>> dasherize [ Word "foo", Acronym "bar", Word "bazz" ]
-- "foo-bar-bazz"
@ -17,6 +27,7 @@ dasherize
-> String -- ^ The dasherized String
dasherize = intercalate "-" . map toString
-- | Covert a 'Word' into its 'String' representation.
toString :: Word -> String
toString (Acronym s) = s
toString (Word s) = s

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Data
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Auxiliary data used in the library.
module Text.Inflections.Data where
import Data.Map (Map, fromList)

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Humanize
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Conversion to “humanized” phrases.
module Text.Inflections.Humanize (humanize) where
import Text.Inflections.Parse.Types (Word(..))
@ -20,6 +31,8 @@ humanize = unwords . map caseForWord . isFirstList
isFirstList :: [a] -> [(a, Bool)]
isFirstList xs = zip xs $ True : repeat False
-- | Convert given 'Word' to capitalized 'String' when associated Boolean
-- value is 'True'.
caseForWord :: (Word, Bool) -> String
caseForWord (Word (c:cs), True) = toUpper c : cs
caseForWord (Word s, False) = s

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Ordinal
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Conversion to spelled ordinal numbers.
module Text.Inflections.Ordinal (ordinal, ordinalize)
where
@ -32,4 +43,3 @@ ordinal number
-- "10th"
ordinalize :: Integer -> String
ordinalize n = show n ++ ordinal n

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Parametrize
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Parametrization for strings, useful for transliteration.
module Text.Inflections.Parameterize
( parameterize
, parameterizeCustom

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Parse.Acronym
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Parser for acronyms.
{-# LANGUAGE FlexibleContexts, NoMonomorphismRestriction #-}
module Text.Inflections.Parse.Acronym ( acronym ) where
@ -12,5 +23,7 @@ import Control.Applicative ((<$>))
import Prelude (Char, String, (.), map)
-- | Parser that accepts a string from given collection and turns it into
-- an 'Acronym'.
acronym :: P.Stream s m Char => [String] -> P.ParsecT s u m Word
acronym as = Acronym <$> P.choice (map (Prim.try . C.string) as)

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Parse.CamelCase
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Parser for camel case “symbols”.
{-# LANGUAGE FlexibleContexts, NoMonomorphismRestriction #-}
module Text.Inflections.Parse.CamelCase ( parseCamelCase )
@ -20,7 +31,6 @@ import Prelude (Char, String, Either, return, ($))
parseCamelCase :: [String] -> String -> Either ParseError [Word]
parseCamelCase acronyms = parse (parser acronyms) "(unknown)"
-- |Recognizes an input String in CamelCase.
parser :: Stream s m Char => [String] -> ParsecT s u m [Word]
parser acronyms = do
@ -28,6 +38,7 @@ parser acronyms = do
eof
return ws
-- | Parser that accepts lower-cased and capitalized words.
word :: Stream s m Char => ParsecT s u m Word
word = do
firstChar <- upper <|> lower

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Parse.Parameterizable
-- Copyright : © 20142016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Parametrizable characters and parser for them.
{-# LANGUAGE CPP, FlexibleContexts, NoMonomorphismRestriction #-}
module Text.Inflections.Parse.Parameterizable
@ -14,16 +25,19 @@ import qualified Text.ParserCombinators.Parsec.Char as C
import Control.Applicative
#endif
data PChar = UCase Char
-- Since some of the transliterating approximations expand from
-- one Unicode to two ASCII chars (eg., œ to oe), we represent
-- this as a String.
| Acceptable String
| Separator
| Underscore
| OtherAscii Char
| NonAscii Char
deriving (Eq, Show)
-- | Parametrizable character.
data PChar
= UCase Char -- ^ Uppercase charater
| Acceptable String
-- ^ Since some of the transliterating approximations expand from one
-- Unicode to two ASCII chars (eg., œ to oe), we represent this as a
-- String.
| Separator
| Underscore
| OtherAscii Char
| NonAscii Char
deriving (Eq, Show)
-- |Matches 'acceptable' characters for parameterization purposes.
acceptableParser :: P.Stream s m Char => P.ParsecT s u m PChar
@ -31,6 +45,7 @@ acceptableParser = do
c <- C.satisfy isValidParamChar
return $ Acceptable [c]
-- | Parser that accepts rows of parametrizable characters.
parser :: P.Stream s m Char => P.ParsecT s u m [PChar]
parser = P.many $ P.choice [
acceptableParser
@ -41,5 +56,7 @@ parser = P.many $ P.choice [
, NonAscii <$> C.satisfy (not . isAscii)
]
-- | Check if given char is “acceptable”, that is, it's lowercase ASCII
-- letter or digit.
isValidParamChar :: Char -> Bool
isValidParamChar c = isAsciiLower c || isDigit c

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Parse.SnakeCase
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Parser for snake case “symbols”.
{-# LANGUAGE FlexibleContexts, NoMonomorphismRestriction #-}
module Text.Inflections.Parse.SnakeCase ( parseSnakeCase )
@ -21,7 +32,6 @@ import Prelude (Char, String, Either, return)
parseSnakeCase :: [String] -> String -> Either ParseError [Word]
parseSnakeCase acronyms = parse (parser acronyms) "(unknown)"
parser :: Stream s m Char => [String] -> ParsecT s u m [Word]
parser acronyms = do
ws <- (acronym acronyms <|> word) `sepBy` char '_'

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Parse.Types
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Types used in the library.
module Text.Inflections.Parse.Types ( Word(..), mapWord ) where
import Prelude (String, Show, Eq, ($))
@ -13,6 +24,7 @@ data Word
deriving (Show, Eq)
-- | Apply 'String' transforming function to a 'Word'.
mapWord :: (String -> String) -> Word -> Word
mapWord f (Word s) = Word $ f s
mapWord f (Acronym s) = Acronym $ f s

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Titleize
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Conversion to titleized phrases.
module Text.Inflections.Titleize (titleize) where
import Text.Inflections.Parse.Types (Word(..))
@ -6,7 +17,7 @@ import Data.Char (toUpper)
import Prelude (String, unwords, map, ($))
-- | Capitalizes all the Words in the input 'Data.List'.
-- | Capitalizes all the Words in the input list.
--
-- >>> titleize [ Word "foo", Acronym "bar", Word "bazz" ]
-- "Foo bar Bazz"
@ -15,6 +26,7 @@ titleize
-> String -- ^ The titleized String
titleize s = unwords $ map upperCaseWord s
-- | Transform 'Word' into an upper-cased 'String'.
upperCaseWord :: Word -> String
upperCaseWord (Word (c:cs)) = toUpper c : cs
upperCaseWord (Word []) = []

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Transliterate
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Support for transliteration.
module Text.Inflections.Transliterate
( transliterate
, transliterateCustom

View File

@ -1,3 +1,14 @@
-- |
-- Module : Text.Inflections.Underscore
-- Copyright : © 2016 Justin Leitgeb
-- License : MIT
--
-- Maintainer : Justin Leitgeb <justin@stackbuilders.com>
-- Stability : experimental
-- Portability : portable
--
-- Conversion to phrases separated by underscores.
module Text.Inflections.Underscore ( underscore ) where
import Text.Inflections.Parse.Types (Word(..))
@ -11,13 +22,12 @@ import Prelude (String, (.), map)
--
-- >>> underscore [ Word "foo", Acronym "bar", Word "bazz" ]
-- "foo_bar_bazz"
underscore
:: [Word] -- ^ Input Words to separate with underscores
-> String -- ^ The underscored String
underscore = intercalate "_" . map toDowncasedString
-- | Transform 'Word' into a down-cased 'String'.
toDowncasedString :: Word -> String
toDowncasedString (Acronym s) = map toLower s
toDowncasedString (Word s) = map toLower s