module Text.HPaco.Writers.Run.Encode where import Data.Char import Data.Maybe import Data.List.Split import Numeric htmlEncode :: String -> String htmlEncode = encode mapping where mapping x = lookup x [ ('<', "<") , ('>', ">") , ('&', "&") , ('"', """) , ('\'', "'") ] urlEncode :: String -> String urlEncode = encode mapping where mapping x | (ord x > 127) || (ord x <= 32) = Just $ fixHexStr (flip showHex "" . ord $ x) | isAlphaNum x = Nothing | otherwise = Just $ fixHexStr (flip showHex "" . ord $ x) encode _ [] = "" encode mapping (x:xs) = let mapped = mapping x xs' = encode mapping xs in maybe (x:xs') (++xs') mapped fixHexStr :: String -> String fixHexStr str = if odd $ length str then fixHexStr $ '0':str else concat . map ('%':) . splitEvery 2 $ str padLeft :: a -> Int -> [a] -> [a] padLeft p c xs = if length xs < c then (take (c - length xs) $ repeat p) ++ xs else take c xs