module Codec.MIME.String.QuotedPrintable (encode, decode) where
import Codec.MIME.String.Internal.Utils
import Data.Bits
import Data.Char
import Data.List
encode :: [String] -> String
encode = enc 0
enc :: Int -> [String] -> String
enc _ [] = ""
enc _ [[]] = ""
enc _ ([]:ls) = '\n':enc 0 ls
enc n ls | n > 72 = '=':'\n':enc 0 ls
enc n ((c:cs):ls)
| (33 <= o && o <= 126 && o /= 61) ||
(not (null cs) && (o == 9 || o == 32)) = c:enc (n+1) (cs:ls)
| otherwise = '=':x1:x2:enc (n+3) (cs:ls)
where o = ord c
x1 = toUpper $ intToDigit (o `shiftR` 4)
x2 = toUpper $ intToDigit (o .&. 0xF)
decode :: [String] -> String
decode = dec . intercalate "\n"
. removeSoftLinebreaks
. map (dropFromEndWhile is_tab_space)
where is_tab_space ' ' = True
is_tab_space '\t' = True
is_tab_space _ = False
breakLast "" = ("", "")
breakLast [x] = ("", [x])
breakLast (x:xs) = case breakLast xs of
(ys, zs) -> (x:ys, zs)
removeSoftLinebreaks [] = []
removeSoftLinebreaks (x:xs)
= case breakLast x of
(x', "=") ->
case removeSoftLinebreaks xs of
[] -> [x']
(y:ys) -> (x' ++ y):ys
_ -> x:removeSoftLinebreaks xs
dec :: String -> String
dec ('=':c1:c2:cs)
| isAsciiHexDigit c1 && isAsciiHexDigit c2
= chr ((digitToInt c1 `shiftL` 4) + digitToInt c2):dec cs
dec (c:cs) = c:dec cs
dec "" = ""