module Text.Inflections.Parameterize
( parameterize
, parameterizeCustom
, Transliterations )
where
import qualified Data.Map as Map
import Control.Monad (guard)
import Data.Maybe (mapMaybe)
import Data.Char (toLower)
import Data.List (group)
import qualified Text.Parsec as P
import Text.Inflections.Data (defaultMap)
import Text.Inflections.Parse.Parameterizable ( PChar(..)
, parser
, isValidParamChar )
type Transliterations = Map.Map Char String
parameterize :: String -> String
parameterize = parameterizeCustom defaultMap
parameterizeCustom :: Transliterations -> String -> String
parameterizeCustom ts s =
case parsed of
Right ast -> (concatMap pCharToC . squeezeSeparators .
trimUnwanted wanted . mapMaybe (parameterizeChar ts))
ast
Left err -> fail $ "Parse failed, please report a bug! Error: " ++
show err
where parsed = P.parse parser "" s
wanted :: [PChar]
wanted = Underscore :
map (Acceptable . (: [])) (['a'..'z'] ++ ['0'..'9'])
transliteratePCharCustom :: Transliterations -> Char -> Maybe PChar
transliteratePCharCustom ts c = do
v <- Map.lookup c ts
guard (all isValidParamChar v)
return (Acceptable v)
parameterizeChar :: Transliterations -> PChar -> Maybe PChar
parameterizeChar _ (UCase c) = Just $ Acceptable [toLower c]
parameterizeChar _ (Acceptable c) = Just $ Acceptable c
parameterizeChar _ Separator = Just Separator
parameterizeChar _ Underscore = Just Underscore
parameterizeChar _ (OtherAscii _) = Just Separator
parameterizeChar ts (NonAscii c) = transliteratePCharCustom ts c
pCharToC :: PChar -> String
pCharToC (UCase c) = [c]
pCharToC (Acceptable str) = str
pCharToC Separator = "-"
pCharToC Underscore = "_"
pCharToC (OtherAscii c) = [c]
pCharToC (NonAscii c) = [c]
squeezeSeparators :: [PChar] -> [PChar]
squeezeSeparators ps = concatMap squashSeparatorGroup $ group ps
where squashSeparatorGroup g = case head g of
Separator -> [Separator]
_ -> g
trimUnwanted :: Eq a => [a] -> [a] -> [a]
trimUnwanted wanted = dropWhile notWanted . reverse . dropWhile notWanted
. reverse
where notWanted = (`notElem` wanted)