{-| module to convert string to hexadecimally endoces strings and vice versa -} module Hex where import Data.Char import Data.Map.Strict hiding (map) import Data.Maybe {-| list of integer in the range from 0 to 15. So one hex digit -} nums :: [Int] nums = [0 .. 15] {-| list of single digit hex numbers in ascending order -} chars :: [Char] chars = (['0' .. '9'] ++ ['A' .. 'F']) {-| map from integer to hex digit -} fromm :: Map Int Char fromm = fromList $ zip nums chars {-| map from hex digit to integer -} tom :: Map Char Int tom = fromList $ zip chars nums {-| function to convert a single unicode character (Char) to a hex encodes string -} hexChar :: Char -> String hexChar c = concat (map (\ i -> fromMaybe "" ((Data.Map.Strict.lookup ((if (i == 0) then (ord c) else (ord c) `div` (16 ^ i)) `mod` (16 :: Int)) fromm) >>= (\ x -> return [x]))) (reverse [0 .. 7] :: [Int])) {-| function to convert a string of unicode characters to a hex encoded version of it -} hex :: String -> String hex s = concat (map hexChar s) {-| function to decode a hex encoded unicode string -} unhex :: String -> String unhex (a : (b : (c : (d : (e : (f : (g : (h : xs)))))))) = (chr (sum (map (\ (i, cc) -> (16 ^ i) * (fromMaybe 0 (Data.Map.Strict.lookup cc tom))) (zip (reverse [0 .. 7] :: [Int]) [a, b, c, d, e, f, g, h])))) : (unhex xs) unhex _ = []