{-# OPTIONS_GHC -cpp #-} {-# LANGUAGE CPP #-} module Darcs.Email ( make_email, read_email ) where import Data.Char ( digitToInt, isHexDigit ) import Printer ( Doc, ($$), (<+>), (<>), text, empty, packedString, renderPS) import ByteStringUtils (dropSpace, linesPS, betweenLinesPS ) import qualified Data.ByteString as B (ByteString, length, null, tail, drop, head) import qualified Data.ByteString.Char8 as BC (index, head, pack) #if __GLASGOW_HASKELL__ > 606 import Data.ByteString.Internal as B (c2w, createAndTrim) #else import Data.ByteString.Base as B (c2w, createAndTrim) #endif import System.IO.Unsafe ( unsafePerformIO ) import Foreign.Ptr ( Ptr, plusPtr ) import Foreign.Storable ( poke ) import Data.Word ( Word8 ) line_max :: Int line_max = 75 -- TODO is this doing mime encoding?? qpencode :: B.ByteString -> B.ByteString qpencode s = unsafePerformIO -- Really only (3 + 2/75) * length or something in the worst case $ B.createAndTrim (4 * B.length s) (\buf -> encode s line_max buf 0) encode :: B.ByteString -> Int -> Ptr Word8 -> Int -> IO Int encode ps _ _ bufi | B.null ps = return bufi encode ps n buf bufi = case B.head ps of c | c == newline -> do poke (buf `plusPtr` bufi) newline encode ps' line_max buf (bufi+1) | n == 0 && B.length ps > 1 -> do poke (buf `plusPtr` bufi) equals poke (buf `plusPtr` (bufi+1)) newline encode ps line_max buf (bufi + 2) | (c == tab || c == space) -> if B.null ps' || B.head ps' == newline then do poke (buf `plusPtr` bufi) c poke (buf `plusPtr` (bufi+1)) equals poke (buf `plusPtr` (bufi+2)) newline encode ps' line_max buf (bufi + 3) else do poke (buf `plusPtr` bufi) c encode ps' (n - 1) buf (bufi + 1) | (c >= bang && c /= equals && c <= tilde) -> do poke (buf `plusPtr` bufi) c encode ps' (n - 1) buf (bufi + 1) | n < 3 -> encode ps 0 buf bufi | otherwise -> do let (x, y) = c `divMod` 16 h1 = intToUDigit x h2 = intToUDigit y poke (buf `plusPtr` bufi) equals poke (buf `plusPtr` (bufi+1)) h1 poke (buf `plusPtr` (bufi+2)) h2 encode ps' (n - 3) buf (bufi + 3) where ps' = B.tail ps newline = B.c2w '\n' tab = B.c2w '\t' space = B.c2w ' ' bang = B.c2w '!' tilde = B.c2w '~' equals = B.c2w '=' intToUDigit i | i >= 0 && i <= 9 = B.c2w '0' + i | i >= 10 && i <= 15 = B.c2w 'A' + i - 10 | otherwise = error $ "intToUDigit: '"++show i++"'not a digit" qpdecode :: B.ByteString -> B.ByteString qpdecode s = unsafePerformIO -- Add 1 as linesPS "\n" -> ["", ""] -> "\n\n" $ B.createAndTrim (B.length s + 1) (\buf -> decode (linesPS s) buf 0) decode :: [B.ByteString] -> Ptr Word8 -> Int -> IO Int decode [] _ bufi = return bufi decode (ps:pss) buf bufi | B.null (dropSpace ps) = do poke (buf `plusPtr` bufi) newline decode pss buf (bufi+1) | is_equals && B.length ps >= 3 && isHexDigit c1 && isHexDigit c2 = do poke (buf `plusPtr` bufi) (toWord8 $ digitToInt c1 * 16 + digitToInt c2) decode (B.drop 3 ps:pss) buf (bufi+1) | is_equals && B.null (dropSpace (B.tail ps)) = decode pss buf bufi | otherwise = do poke (buf `plusPtr` bufi) (B.head ps) decode (B.tail ps:pss) buf (bufi+1) where is_equals = BC.head ps == '=' c1 = BC.index ps 1 c2 = BC.index ps 2 newline = B.c2w '\n' toWord8 :: Int -> Word8 toWord8 = fromIntegral make_email :: String -> [(String, String)] -> (Maybe Doc) -> Doc -> (Maybe String) -> Doc make_email repodir headers mcontents bundle mfilename = text "DarcsURL:" <+> text repodir $$ foldl (\m (h,v) -> m $$ (text (h ++ ":") <+> text v)) empty headers $$ text "MIME-Version: 1.0" $$ text "Content-Type: multipart/mixed; boundary=\"=_\"" $$ text "" $$ text "--=_" $$ (case mcontents of Just contents -> text "Content-Type: text/plain" $$ text "Content-Transfer-Encoding: quoted-printable" $$ text "" $$ packedString (qpencode (renderPS contents)) $$ text "" $$ text "--=_" Nothing -> empty) $$ text "Content-Type: text/x-darcs-patch" <> (case mfilename of Just filename -> text "; name=\"" <> text filename <> text "\"" Nothing -> empty) $$ text "Content-Transfer-Encoding: quoted-printable" $$ text "Content-Description: A darcs patch for your repository!" $$ text "" $$ packedString (qpencode (renderPS bundle)) $$ text "--=_--" $$ text "" $$ text "." $$ text "" $$ text "" read_email :: B.ByteString -> B.ByteString read_email s = case betweenLinesPS (BC.pack "Content-Description: A darcs patch for your repository!") (BC.pack "--=_--") s of Nothing -> s -- if it wasn't an email in the first place, just pass along. Just s' -> qpdecode s'