module Data.Elocrypt.Utils where
import Data.Char (isAlphaNum, isSpace)
import Data.Maybe (fromMaybe)
import Data.Ratio
import qualified Data.Map as M
import Control.Monad.Random (MonadRandom(), fromList)
numeralConversions = M.fromList [
('o', ['0']),
('l', ['1']),
('z', ['2']),
('e', ['3']),
('a', ['4']),
('s', ['5']),
('g', ['6', '9']),
('t', ['7']),
('b', ['8'])]
symbolConversions = M.fromList [
('a', ['@']),
('l', ['!']),
('s', ['$'])]
toDigit :: Char -> String
toDigit c = fromMaybe [c] (numeralConversions M.!? c)
toSymbol :: Char -> String
toSymbol c = fromMaybe [c] (symbolConversions M.!? c)
isSymbol :: Char -> Bool
isSymbol c = not (isAlphaNum c || isSpace c)
updateR
:: MonadRandom m
=> (Char -> m Char)
-> Rational
-> String
-> m String
updateR f prob = mapM f'
where f' ch = do
ch' <- f ch
fromList [
(ch, toRational $ denominator prob),
(ch', toRational $ numerator prob)]
update1
:: Monad m
=> (Char -> m Char)
-> String
-> Int
-> m String
update1 _ "" _ = return ""
update1 f s pos = (\ch' -> prefix ++ ch' : suffix) <$> f ch
where (prefix, ch : suffix) = splitAt pos s