-- module XPrintable where import Numeric import Data.Char import System.Environment main :: IO () main = do args <- getArgs case args of ["encode"] -> interact encode ["decode"] -> interact decode _ -> error "Usage: x-printable [encode|decode]" encode, decode :: String -> String encode = concatMap (f . ord) where f x | x > 255 = error "impossible" | x > 128 = 'x' : showHex x [] | x == ord 'x' = "xx" | otherwise = [chr x] decode = f where f [] = [] f ('x' : i : j : xs) | isHexDigit i && isHexDigit j = case readHex [i, j] of [(n, [])] -> chr n : f xs _ -> 'x' : i : j : f xs f ('x' : 'x' : xs) = 'x' : f xs f (x : xs) = x : f xs -- decode_encode_prop x = x == decode (encode x) -- quickCheckWith stdArgs{maxSuccess=1000,maxSize=1000} decode_encode_prop