summaryrefslogtreecommitdiffstats
path: root/Codec/MIME/Decode.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@galois.com>2008-01-04 16:23:04 -0800
committerDon Stewart <dons@galois.com>2008-01-04 16:23:04 -0800
commit35f0f40cfabeb49b468c6ae3c68fedded145a022 (patch)
tree0d4fa2b367a987c86ef5c14a06b7b91aee2dc6a7 /Codec/MIME/Decode.hs
parent62e3911810c18e77a13794cb5899a9ebc6b0bbb3 (diff)
Move MIME stuff into proper Codec.* namespace.
Add copyrights where missing.
Diffstat (limited to 'Codec/MIME/Decode.hs')
-rw-r--r--Codec/MIME/Decode.hs56
1 files changed, 56 insertions, 0 deletions
diff --git a/Codec/MIME/Decode.hs b/Codec/MIME/Decode.hs
new file mode 100644
index 0000000..f23454a
--- /dev/null
+++ b/Codec/MIME/Decode.hs
@@ -0,0 +1,56 @@
+module MIME.Decode where
+
+import Data.Char
+import MIME.QuotedPrintable as QP
+import MIME.Base64 as Base64
+
+decodeBody :: String -> String -> String
+decodeBody enc body =
+ case map toLower enc of
+ "base64" -> map (chr.fromIntegral) $ Base64.decode body
+ "quoted-printable" -> QP.decode body
+ _ -> body
+
+-- Decoding of RFC 2047's "encoded-words' production
+-- (as used in email-headers and some HTTP header cases
+-- (AtomPub's Slug: header))
+decodeWord :: String -> Maybe (String, String)
+decodeWord str =
+ case str of
+ '=':'?':xs ->
+ case dropLang $ break (\ch -> ch =='?' || ch == '*') xs of
+ (cs,_:x:'?':bs)
+ | isKnownCharset (map toLower cs) ->
+ case toLower x of
+ 'q' -> decodeQ cs (break (=='?') bs)
+ 'b' -> decodeB cs (break (=='?') bs)
+ _ -> Nothing
+ _ -> Nothing
+ _ -> Nothing
+ where
+ isKnownCharset cs = cs `elem` ["iso-8859-1", "us-ascii"]
+
+ -- ignore RFC 2231 extension of permitting a language tag to be supplied
+ -- after the charset.
+ dropLang (as,'*':bs) = (as,dropWhile (/='?') bs)
+ dropLang (as,bs) = (as,bs)
+
+ decodeQ cset (fs,'?':'=':rs) = Just (fromCharset cset (QP.decode fs),rs)
+ decodeQ _ _ = Nothing
+
+ decodeB cset (fs,'?':'=':rs) =
+ Just (fromCharset cset (Base64.decodeToString fs),rs)
+ decodeB _ _ = Nothing
+
+ fromCharset _cset cs = cs
+
+decodeWords :: String -> String
+decodeWords "" = ""
+decodeWords (x:xs)
+ | isSpace x = x : decodeWords xs
+ | otherwise =
+ case decodeWord (x:xs) of
+ Nothing -> x : decodeWords xs
+ Just (as,bs) -> as ++ decodeWords bs
+
+