{-# LANGUAGE OverloadedStrings #-}
module Quokka.Text.Countable
( pluralize
, pluralizeWith
, singularize
, singularizeWith
, inflect
, inflectWith
, makeMatchMapping
, makeIrregularMapping
, makeUncountableMapping
)
where
import Data.Maybe (catMaybes, fromMaybe, isJust)
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Quokka.Text.Data (defaultUncountables', defaultIrregulars', defaultSingulars', defaultPlurals')
import Text.Regex.PCRE.ByteString (Regex, execBlank, compCaseless, compile, execute)
import Text.Regex.PCRE.ByteString.Utils (substitute')
import System.IO.Unsafe (unsafePerformIO)
type RegexPattern = Text
type RegexReplace = Text
type Singular = Text
type Plural = Text
data Inflection
= Simple (Singular, Plural)
| Match (Maybe Regex, RegexReplace)
pluralize :: Text -> Text
pluralize = pluralizeWith mapping
where
mapping = defaultIrregulars ++ defaultUncountables ++ defaultPlurals
singularize :: Text -> Text
singularize = singularizeWith mapping
where
mapping = defaultIrregulars ++ defaultUncountables ++ defaultSingulars
pluralizeWith :: [Inflection] -> Text -> Text
pluralizeWith = lookupWith pluralLookup
singularizeWith :: [Inflection] -> Text -> Text
singularizeWith = lookupWith singularLookup
inflect :: Text -> Int -> Text
inflect t i = case i of
1 -> singularize t
_ -> pluralize t
inflectWith :: [Inflection] -> Text -> Int -> Text
inflectWith l t i = case i of
1 -> singularizeWith l t
_ -> pluralizeWith l t
lookupWith :: (Text -> Inflection -> Maybe Text) -> [Inflection] -> Text -> Text
lookupWith f mapping target = fromMaybe target $ headMaybe matches
where
matches = catMaybes $ fmap (f target) (Prelude.reverse mapping)
makeMatchMapping :: [(RegexPattern, RegexReplace)] -> [Inflection]
makeMatchMapping = fmap (\(pat, rep) -> Match (regexPattern pat, rep))
makeIrregularMapping :: [(Singular, Plural)] -> [Inflection]
makeIrregularMapping = fmap Simple
makeUncountableMapping :: [Text] -> [Inflection]
makeUncountableMapping = fmap (\a -> Simple (a,a))
defaultPlurals :: [Inflection]
defaultPlurals = makeMatchMapping defaultPlurals'
defaultSingulars :: [Inflection]
defaultSingulars = makeMatchMapping defaultSingulars'
defaultIrregulars :: [Inflection]
defaultIrregulars = makeIrregularMapping defaultIrregulars'
defaultUncountables :: [Inflection]
defaultUncountables = makeUncountableMapping defaultUncountables'
pluralLookup :: Text -> Inflection -> Maybe Text
pluralLookup t (Match (r1,r2)) = runSub (r1,r2) t
pluralLookup t (Simple (a,b)) = if t == a then Just b else Nothing
singularLookup :: Text -> Inflection -> Maybe Text
singularLookup t (Match (r1,r2)) = runSub (r1,r2) t
singularLookup t (Simple (a,b)) = if t == b then Just a else Nothing
runSub :: (Maybe Regex, RegexReplace) -> Text -> Maybe Text
runSub (Nothing, _) _ = Nothing
runSub (Just reg, rep) t = matchWithReplace (reg, rep) t
matchWithReplace :: (Regex, RegexReplace) -> Text -> Maybe Text
matchWithReplace (reg, rep) t =
if regexMatch t reg
then toMaybe $ substitute' reg (encodeUtf8 t) (encodeUtf8 rep)
else Nothing
where
toMaybe = either (const Nothing) (Just . decodeUtf8)
regexMatch :: Text -> Regex -> Bool
regexMatch t r = case match of
Left _ -> False
Right m -> isJust m
where match = unsafePerformIO $ execute r (encodeUtf8 t)
regexPattern :: Text -> Maybe Regex
regexPattern pat = toMaybe reg
where toMaybe = either (const Nothing) Just
reg = unsafePerformIO $ compile compCaseless execBlank (encodeUtf8 pat)
headMaybe :: [a] -> Maybe a
headMaybe [] = Nothing
headMaybe (x:_) = Just x