aboutsummaryrefslogtreecommitdiff
path: root/Email.hs
diff options
context:
space:
mode:
authorRaúl Benencia <rul@kalgan.cc>2013-09-01 13:16:54 -0300
committerRaúl Benencia <rul@kalgan.cc>2013-09-01 13:16:54 -0300
commit917de9c6df342d032e2b05238c7ea923da2772db (patch)
tree78b8f56b03ed07f4d9f055149a0e974d47609057 /Email.hs
parent39f53d2775f38514a537f03c7b72281ec31a3c0e (diff)
towards mime library
Diffstat (limited to 'Email.hs')
-rw-r--r--Email.hs91
1 files changed, 66 insertions, 25 deletions
diff --git a/Email.hs b/Email.hs
index 4601aa5..c1c524f 100644
--- a/Email.hs
+++ b/Email.hs
@@ -7,16 +7,75 @@
-}
module Email where
-import Network.Email.Mailbox(Flag(..), Flags)
+import Codec.MIME.Type(MIMEValue(..), MIMEContent(..))
+import Data.Char(toLower)
+import Data.List(find)
-import Text.Parsec.Error(ParseError)
+getBody :: MIMEValue -> String
+getBody msg =
+ case mime_val_content msg of
+ Single c -> c
+ _ -> "Buggity Buggity Buggity!"
+
+getHeaders :: MIMEValue -> [(String,String)]
+getHeaders = mime_val_headers
+
+-- | Convert a String to multiple Strings, cropped by the maximum column
+-- size if necessary.
+formatBody :: String -> Int -> [String]
+formatBody body maxColumns = format [] [] body where
+ format parsed acc [] = parsed ++ [acc]
+ format parsed acc ('\r':'\n':xs) = format (parsed ++ [acc]) [] xs
+ format parsed acc rest@(x:xs) | length acc < maxColumns = format parsed (acc ++ [x]) xs
+ | otherwise = format (parsed ++ [acc]) "+" rest
+
+
+-- The following function is a verbatim copy of the unexported function in
+-- Codec.MIME.Parse.
+-- case in-sensitive lookup of field names or attributes\/parameters.
+lookupField' :: String -> [(String,a)] -> Maybe a
+lookupField' n ns =
+ -- assume that inputs have been mostly normalized already
+ -- (i.e., lower-cased), but should the lookup fail fall back
+ -- to a second try where we do normalize before giving up.
+ case lookup n ns of
+ x@Just{} -> x
+ Nothing ->
+ let nl = map toLower n in
+ case find (\ (y,_) -> nl == map toLower y) ns of
+ Nothing -> Nothing
+ Just (_,x) -> Just x
+
+unwrapField = maybe "" id
+
+lookupField n ns = unwrapField $ lookupField' n ns
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+{-import Text.Parsec.Error(ParseError)
import Text.ParserCombinators.Parsec (parse)
import Text.ParserCombinators.Parsec.Rfc2822
-data Email = Email { emailPath :: String
- , parsedEmail :: Message
- }
-
parseEmail :: String -> Message
parseEmail msg = unwrapEmail $ parse message "<stdin>" $ fixEol msg
@@ -49,27 +108,9 @@ getResentMessageID fs = do { ResentMessageID f <- fs; f }
getBody (Message _ []) = "Empty body"
getBody (Message _ body) = body
--- | Convert a String to multiple Strings, cropped by the maximum column
--- size if necessary.
-formatBody :: String -> Int -> [String]
-formatBody body maxColumns = format [] [] body where
- format parsed acc [] = parsed ++ [acc]
- format parsed acc ('\r':'\n':xs) = format (parsed ++ [acc]) [] xs
- format parsed acc rest@(x:xs) | length acc < maxColumns = format parsed (acc ++ [x]) xs
- | otherwise = format (parsed ++ [acc]) "+" rest
-
-- Make sure all lines are terminated by CRLF.
fixEol :: String -> String
fixEol ('\r':'\n':xs) = '\r' : '\n' : fixEol xs
fixEol ('\n':xs) = '\r' : '\n' : fixEol xs
fixEol (x:xs) = x : fixEol xs
-fixEol [] = []
-
---data DescriptionPP = DescriptionPP {
--- ppOrder :: [String] -> [String]
--- }
-
-
--- emailDescription = emailDescriptionWithPP defaultDescriptionPP
-
--- emailDescriptionWithPP pp \ No newline at end of file
+fixEol [] = []-}
nihil fit ex nihilo