/deps/gen_smtp/src/mimemail.erl

http://github.com/zotonic/zotonic · Erlang · 1818 lines · 1580 code · 90 blank · 148 comment · 46 complexity · 2bc63ce0c840d1e05c216b867ee1bcae MD5 · raw file

Large files are truncated click here to view the full file

  1. %%% Copyright 2009 Andrew Thompson <andrew@hijacked.us>. All rights reserved.
  2. %%%
  3. %%% Redistribution and use in source and binary forms, with or without
  4. %%% modification, are permitted provided that the following conditions are met:
  5. %%%
  6. %%% 1. Redistributions of source code must retain the above copyright notice,
  7. %%% this list of conditions and the following disclaimer.
  8. %%% 2. Redistributions in binary form must reproduce the above copyright
  9. %%% notice, this list of conditions and the following disclaimer in the
  10. %%% documentation and/or other materials provided with the distribution.
  11. %%%
  12. %%% THIS SOFTWARE IS PROVIDED BY THE FREEBSD PROJECT ``AS IS'' AND ANY EXPRESS OR
  13. %%% IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
  14. %%% MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO
  15. %%% EVENT SHALL THE FREEBSD PROJECT OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT,
  16. %%% INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
  17. %%% (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
  18. %%% LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
  19. %%% ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
  20. %%% (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
  21. %%% SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
  22. %% @doc A module for decoding/encoding MIME 1.0 email.
  23. %% The encoder and decoder operate on the same datastructure, which is as follows:
  24. %% A 5-tuple with the following elements: `{Type, SubType, Headers, Parameters, Body}'.
  25. %%
  26. %% `Type' and `SubType' are the MIME type of the email, examples are `text/plain' or
  27. %% `multipart/alternative'. The decoder splits these into 2 fields so you can filter by
  28. %% the main type or by the subtype.
  29. %%
  30. %% `Headers' consists of a list of key/value pairs of binary values eg.
  31. %% `{<<"From">>, <<"Andrew Thompson <andrew@hijacked.us>">>}'. There is no parsing of
  32. %% the header aside from un-wrapping the lines and splitting the header name from the
  33. %% header value.
  34. %%
  35. %% `Parameters' is a list of 3 key/value tuples. The 3 keys are `<<"content-type-params">>',
  36. %% `<<"dispisition">>' and `<<"disposition-params">>'.
  37. %% `content-type-params' is a key/value list of parameters on the content-type header, this
  38. %% usually consists of things like charset and the format parameters. `disposition' indicates
  39. %% how the data wants to be displayed, this is usually 'inline'. `disposition-params' is a list of
  40. %% disposition information, eg. the filename this section should be saved as, the modification
  41. %% date the file should be saved with, etc.
  42. %%
  43. %% Finally, `Body' can be one of several different types, depending on the structure of the email.
  44. %% For a simple email, the body will usually be a binary consisting of the message body, In the
  45. %% case of a multipart email, its a list of these 5-tuple MIME structures. The third possibility,
  46. %% in the case of a message/rfc822 attachment, body can be a single 5-tuple MIME structure.
  47. %%
  48. %% You should see the relevant RFCs (2045, 2046, 2047, etc.) for more information.
  49. -module(mimemail).
  50. -ifdef(TEST).
  51. -include_lib("eunit/include/eunit.hrl").
  52. -endif.
  53. -export([encode/1, decode/2, decode/1, get_header_value/2, get_header_value/3, parse_headers/1]).
  54. -define(DEFAULT_OPTIONS, [
  55. {encoding, get_default_encoding()}, % default encoding is utf-8 if we can find the iconv module
  56. {decode_attachments, true} % should we decode any base64/quoted printable attachments?
  57. ]).
  58. -type(mimetuple() :: {binary(), binary(), [{binary(), binary()}], [{binary(), binary()}], binary() | [{binary(), binary(), [{binary(), binary()}], [{binary(), binary()}], binary() | [tuple()]}] | tuple()}).
  59. -type(options() :: [{'encoding', binary()} | {'decode_attachment', boolean()}]).
  60. -spec(decode/1 :: (Email :: binary()) -> mimetuple()).
  61. %% @doc Decode a MIME email from a binary.
  62. decode(All) ->
  63. {Headers, Body} = parse_headers(All),
  64. decode(Headers, Body, ?DEFAULT_OPTIONS).
  65. -spec(decode/2 :: (Email :: binary(), Options :: options()) -> mimetuple()).
  66. %% @doc Decode with custom options
  67. decode(All, Options) when is_binary(All), is_list(Options) ->
  68. {Headers, Body} = parse_headers(All),
  69. decode(Headers, Body, Options).
  70. decode(OrigHeaders, Body, Options) ->
  71. %io:format("headers: ~p~n", [Headers]),
  72. Encoding = proplists:get_value(encoding, Options, none),
  73. case whereis(iconv) of
  74. undefined when Encoding =/= none ->
  75. {ok, _Pid} = iconv:start();
  76. _ ->
  77. ok
  78. end,
  79. %FixedHeaders = fix_headers(Headers),
  80. Headers = decode_headers(OrigHeaders, [], Encoding),
  81. case parse_with_comments(get_header_value(<<"MIME-Version">>, Headers)) of
  82. undefined ->
  83. case parse_content_type(get_header_value(<<"Content-Type">>, Headers)) of
  84. {<<"multipart">>, _SubType, _Parameters} ->
  85. erlang:error(non_mime_multipart);
  86. {Type, SubType, Parameters} ->
  87. NewBody = decode_body(get_header_value(<<"Content-Transfer-Encoding">>, Headers),
  88. Body, proplists:get_value(<<"charset">>, Parameters), Encoding),
  89. {Type, SubType, Headers, Parameters, NewBody};
  90. undefined ->
  91. Parameters = [{<<"content-type-params">>, [{<<"charset">>, <<"us-ascii">>}]}, {<<"disposition">>, <<"inline">>}, {<<"disposition-params">>, []}],
  92. {<<"text">>, <<"plain">>, Headers, Parameters, decode_body(get_header_value(<<"Content-Transfer-Encoding">>, Headers), Body)}
  93. end;
  94. Other ->
  95. decode_component(Headers, Body, Other, Options)
  96. end.
  97. -spec(encode/1 :: (MimeMail :: mimetuple()) -> binary()).
  98. %% @doc Encode a MIME tuple to a binary.
  99. encode({Type, Subtype, Headers, ContentTypeParams, Parts}) ->
  100. {FixedParams, FixedHeaders} = ensure_content_headers(Type, Subtype, ContentTypeParams, Headers, Parts, true),
  101. FixedHeaders2 = check_headers(FixedHeaders),
  102. list_to_binary([binstr:join(
  103. encode_headers(
  104. FixedHeaders2
  105. ),
  106. "\r\n"),
  107. "\r\n\r\n",
  108. binstr:join(encode_component(Type, Subtype, FixedHeaders2, FixedParams, Parts),
  109. "\r\n")]);
  110. encode(_) ->
  111. io:format("Not a mime-decoded DATA~n"),
  112. erlang:error(non_mime).
  113. decode_headers(Headers, _, none) ->
  114. Headers;
  115. decode_headers([], Acc, _Charset) ->
  116. lists:reverse(Acc);
  117. decode_headers([{Key, Value} | Headers], Acc, Charset) ->
  118. decode_headers(Headers, [{Key, decode_header(Value, Charset)} | Acc], Charset).
  119. decode_header(Value, Charset) ->
  120. case re:run(Value, "=\\?([-A-Za-z0-9_]+)\\?([qQbB])\\?([^\s]+)\\?=", [ungreedy]) of
  121. nomatch ->
  122. Value;
  123. {match,[{AllStart, AllLen},{EncodingStart, EncodingLen},{TypeStart, _},{DataStart, DataLen}]} ->
  124. Encoding = binstr:substr(Value, EncodingStart+1, EncodingLen),
  125. Type = binstr:to_lower(binstr:substr(Value, TypeStart+1, 1)),
  126. Data = binstr:substr(Value, DataStart+1, DataLen),
  127. CD = case iconv:open(Charset, fix_encoding(Encoding)) of
  128. {ok, Res} -> Res;
  129. {error, einval} -> throw({bad_charset, fix_encoding(Encoding)})
  130. end,
  131. DecodedData = case Type of
  132. <<"q">> ->
  133. {ok, S} = iconv:conv(CD, decode_quoted_printable(re:replace(Data, "_", " ", [{return, binary}, global]))),
  134. S;
  135. <<"b">> ->
  136. {ok, S} = iconv:conv(CD, decode_base64(re:replace(Data, "_", " ", [{return, binary}, global]))),
  137. S
  138. end,
  139. iconv:close(CD),
  140. Offset = case re:run(binstr:substr(Value, AllStart + AllLen + 1), "^([\s\t\n\r]+)=\\?[-A-Za-z0-9_]+\\?[^\s]\\?[^\s]+\\?=", [ungreedy]) of
  141. nomatch ->
  142. % no 2047 block immediately following
  143. 1;
  144. {match,[{_, _},{_, WhiteSpaceLen}]} ->
  145. 1+ WhiteSpaceLen
  146. end,
  147. NewValue = list_to_binary([binstr:substr(Value, 1, AllStart), DecodedData, binstr:substr(Value, AllStart + AllLen + Offset)]),
  148. decode_header(NewValue, Charset)
  149. end.
  150. decode_component(Headers, Body, MimeVsn, Options) when MimeVsn =:= <<"1.0">> ->
  151. case parse_content_disposition(get_header_value(<<"Content-Disposition">>, Headers)) of
  152. {Disposition, DispositionParams} ->
  153. ok;
  154. _ -> % defaults
  155. Disposition = <<"inline">>,
  156. DispositionParams = []
  157. end,
  158. case parse_content_type(get_header_value(<<"Content-Type">>, Headers)) of
  159. {<<"multipart">>, SubType, Parameters} ->
  160. case proplists:get_value(<<"boundary">>, Parameters) of
  161. undefined ->
  162. erlang:error(no_boundary);
  163. Boundary ->
  164. % io:format("this is a multipart email of type: ~s and boundary ~s~n", [SubType, Boundary]),
  165. Parameters2 = [{<<"content-type-params">>, Parameters}, {<<"disposition">>, Disposition}, {<<"disposition-params">>, DispositionParams}],
  166. {<<"multipart">>, SubType, Headers, Parameters2, split_body_by_boundary(Body, list_to_binary(["--", Boundary]), MimeVsn, Options)}
  167. end;
  168. {<<"message">>, <<"rfc822">>, Parameters} ->
  169. {NewHeaders, NewBody} = parse_headers(Body),
  170. Parameters2 = [{<<"content-type-params">>, Parameters}, {<<"disposition">>, Disposition}, {<<"disposition-params">>, DispositionParams}],
  171. {<<"message">>, <<"rfc822">>, Headers, Parameters2, decode(NewHeaders, NewBody, Options)};
  172. {Type, SubType, Parameters} ->
  173. %io:format("body is ~s/~s~n", [Type, SubType]),
  174. Parameters2 = [{<<"content-type-params">>, Parameters}, {<<"disposition">>, Disposition}, {<<"disposition-params">>, DispositionParams}],
  175. {Type, SubType, Headers, Parameters2, decode_body(get_header_value(<<"Content-Transfer-Encoding">>, Headers), Body, proplists:get_value(<<"charset">>, Parameters), proplists:get_value(encoding, Options, none))};
  176. undefined -> % defaults
  177. Type = <<"text">>,
  178. SubType = <<"plain">>,
  179. Parameters = [{<<"content-type-params">>, [{<<"charset">>, <<"us-ascii">>}]}, {<<"disposition">>, Disposition}, {<<"disposition-params">>, DispositionParams}],
  180. {Type, SubType, Headers, Parameters, decode_body(get_header_value(<<"Content-Transfer-Encoding">>, Headers), Body)}
  181. end;
  182. decode_component(_Headers, _Body, Other, _Options) ->
  183. erlang:error({mime_version, Other}).
  184. -spec(get_header_value/3 :: (Needle :: binary(), Headers :: [{binary(), binary()}], Default :: any()) -> binary() | any()).
  185. %% @doc Do a case-insensitive header lookup to return that header's value, or the specified default.
  186. get_header_value(Needle, Headers, Default) ->
  187. %io:format("Headers: ~p~n", [Headers]),
  188. F =
  189. fun({Header, _Value}) ->
  190. binstr:to_lower(Header) =:= binstr:to_lower(Needle)
  191. end,
  192. case lists:filter(F, Headers) of
  193. % TODO if there's duplicate headers, should we use the first or the last?
  194. [{_Header, Value}|_T] ->
  195. Value;
  196. _ ->
  197. Default
  198. end.
  199. -spec(get_header_value/2 :: (Needle :: binary(), Headers :: [{binary(), binary()}]) -> binary() | 'undefined').
  200. %% @doc Do a case-insensitive header lookup to return the header's value, or `undefined'.
  201. get_header_value(Needle, Headers) ->
  202. get_header_value(Needle, Headers, undefined).
  203. -spec parse_with_comments(Value :: binary()) -> binary() | no_return();
  204. (Value :: atom()) -> atom().
  205. parse_with_comments(Value) when is_binary(Value) ->
  206. parse_with_comments(Value, [], 0, false);
  207. parse_with_comments(Value) ->
  208. Value.
  209. -spec parse_with_comments(Value :: binary(), Acc :: list(), Depth :: non_neg_integer(), Quotes :: boolean()) -> binary() | no_return().
  210. parse_with_comments(<<>>, _Acc, _Depth, Quotes) when Quotes ->
  211. erlang:error(unterminated_quotes);
  212. parse_with_comments(<<>>, _Acc, Depth, _Quotes) when Depth > 0 ->
  213. erlang:error(unterminated_comment);
  214. parse_with_comments(<<>>, Acc, _Depth, _Quotes) ->
  215. binstr:strip(list_to_binary(lists:reverse(Acc)));
  216. parse_with_comments(<<$\\, H, Tail/binary>>, Acc, Depth, Quotes) when Depth > 0, H > 32, H < 127 ->
  217. parse_with_comments(Tail, Acc, Depth, Quotes);
  218. parse_with_comments(<<$\\, Tail/binary>>, Acc, Depth, Quotes) when Depth > 0 ->
  219. parse_with_comments(Tail, Acc, Depth, Quotes);
  220. parse_with_comments(<<$\\, H, Tail/binary>>, Acc, Depth, Quotes) when H > 32, H < 127 ->
  221. parse_with_comments(Tail, [H | Acc], Depth, Quotes);
  222. parse_with_comments(<<$\\, Tail/binary>>, Acc, Depth, Quotes) ->
  223. parse_with_comments(Tail, [$\\ | Acc], Depth, Quotes);
  224. parse_with_comments(<<$(, Tail/binary>>, Acc, Depth, Quotes) when not Quotes ->
  225. parse_with_comments(Tail, Acc, Depth + 1, Quotes);
  226. parse_with_comments(<<$), Tail/binary>>, Acc, Depth, Quotes) when Depth > 0, not Quotes ->
  227. parse_with_comments(Tail, Acc, Depth - 1, Quotes);
  228. parse_with_comments(<<_, Tail/binary>>, Acc, Depth, Quotes) when Depth > 0 ->
  229. parse_with_comments(Tail, Acc, Depth, Quotes);
  230. parse_with_comments(<<$", T/binary>>, Acc, Depth, true) -> %"
  231. parse_with_comments(T, Acc, Depth, false);
  232. parse_with_comments(<<$", T/binary>>, Acc, Depth, false) -> %"
  233. parse_with_comments(T, Acc, Depth, true);
  234. parse_with_comments(<<H, Tail/binary>>, Acc, Depth, Quotes) ->
  235. parse_with_comments(Tail, [H | Acc], Depth, Quotes).
  236. -spec(parse_content_type/1 :: (Value :: 'undefined') -> 'undefined';
  237. (Value :: binary()) -> {binary(), binary(), [{binary(), binary()}]}).
  238. parse_content_type(undefined) ->
  239. undefined;
  240. parse_content_type(String) ->
  241. try parse_content_disposition(String) of
  242. {RawType, Parameters} ->
  243. case binstr:strchr(RawType, $/) of
  244. Index when Index < 2 ->
  245. throw(bad_content_type);
  246. Index ->
  247. Type = binstr:substr(RawType, 1, Index - 1),
  248. SubType = binstr:substr(RawType, Index + 1),
  249. {binstr:to_lower(Type), binstr:to_lower(SubType), Parameters}
  250. end
  251. catch
  252. bad_disposition ->
  253. throw(bad_content_type)
  254. end.
  255. -spec(parse_content_disposition/1 :: (Value :: 'undefined') -> 'undefined';
  256. (String :: binary()) -> {binary(), [{binary(), binary()}]}).
  257. parse_content_disposition(undefined) ->
  258. undefined;
  259. parse_content_disposition(String) ->
  260. [Disposition | Parameters] = binstr:split(parse_with_comments(String), <<";">>),
  261. F =
  262. fun(X) ->
  263. Y = binstr:strip(binstr:strip(X), both, $\t),
  264. case binstr:strchr(Y, $=) of
  265. Index when Index < 2 ->
  266. throw(bad_disposition);
  267. Index ->
  268. Key = binstr:substr(Y, 1, Index - 1),
  269. Value = binstr:substr(Y, Index + 1),
  270. {binstr:to_lower(Key), Value}
  271. end
  272. end,
  273. Params = lists:map(F, Parameters),
  274. {binstr:to_lower(Disposition), Params}.
  275. split_body_by_boundary(Body, Boundary, MimeVsn, Options) ->
  276. % find the indices of the first and last boundary
  277. case [binstr:strpos(Body, Boundary), binstr:strpos(Body, list_to_binary([Boundary, "--"]))] of
  278. [0, _] ->
  279. erlang:error(missing_boundary);
  280. [_, 0] ->
  281. erlang:error(missing_last_boundary);
  282. [Start, End] ->
  283. NewBody = binstr:substr(Body, Start + byte_size(Boundary), End - Start),
  284. % from now on, we can be sure that each boundary is preceeded by a CRLF
  285. Parts = split_body_by_boundary_(NewBody, list_to_binary(["\r\n", Boundary]), []),
  286. [decode_component(Headers, Body2, MimeVsn, Options) || {Headers, Body2} <- [V || {_, Body3} = V <- Parts, byte_size(Body3) =/= 0]]
  287. end.
  288. split_body_by_boundary_(<<>>, _Boundary, Acc) ->
  289. lists:reverse(Acc);
  290. split_body_by_boundary_(Body, Boundary, Acc) ->
  291. % trim the incomplete first line
  292. TrimmedBody = binstr:substr(Body, binstr:strpos(Body, "\r\n") + 2),
  293. case binstr:strpos(TrimmedBody, Boundary) of
  294. 0 ->
  295. lists:reverse([{[], TrimmedBody} | Acc]);
  296. Index ->
  297. split_body_by_boundary_(binstr:substr(TrimmedBody, Index + byte_size(Boundary)), Boundary,
  298. [parse_headers(binstr:substr(TrimmedBody, 1, Index - 1)) | Acc])
  299. end.
  300. -spec(parse_headers/1 :: (Body :: binary()) -> {[{binary(), binary()}], binary()}).
  301. %% @doc Parse the headers off of a message and return a list of headers and the trailing body.
  302. parse_headers(Body) ->
  303. case binstr:strpos(Body, "\r\n") of
  304. 0 ->
  305. {[], Body};
  306. 1 ->
  307. {[], binstr:substr(Body, 3)};
  308. Index ->
  309. parse_headers(binstr:substr(Body, Index+2), binstr:substr(Body, 1, Index - 1), [])
  310. end.
  311. parse_headers(Body, <<H, Tail/binary>>, []) when H =:= $\s; H =:= $\t ->
  312. % folded headers
  313. {[], list_to_binary([H, Tail, "\r\n", Body])};
  314. parse_headers(Body, <<H, T/binary>>, Headers) when H =:= $\s; H =:= $\t ->
  315. % folded headers
  316. [{FieldName, OldFieldValue} | OtherHeaders] = Headers,
  317. FieldValue = list_to_binary([OldFieldValue, T]),
  318. %io:format("~p = ~p~n", [FieldName, FieldValue]),
  319. case binstr:strpos(Body, "\r\n") of
  320. 0 ->
  321. {lists:reverse([{FieldName, FieldValue} | OtherHeaders]), Body};
  322. 1 ->
  323. {lists:reverse([{FieldName, FieldValue} | OtherHeaders]), binstr:substr(Body, 3)};
  324. Index2 ->
  325. parse_headers(binstr:substr(Body, Index2 + 2), binstr:substr(Body, 1, Index2 - 1), [{FieldName, FieldValue} | OtherHeaders])
  326. end;
  327. parse_headers(Body, Line, Headers) ->
  328. %io:format("line: ~p, nextpart ~p~n", [Line, binstr:substr(Body, 1, 10)]),
  329. case binstr:strchr(Line, $:) of
  330. 0 ->
  331. {lists:reverse(Headers), list_to_binary([Line, "\r\n", Body])};
  332. Index ->
  333. FieldName = binstr:substr(Line, 1, Index - 1),
  334. F = fun(X) -> X > 32 andalso X < 127 end,
  335. case binstr:all(F, FieldName) of
  336. true ->
  337. F2 = fun(X) -> (X > 31 andalso X < 127) orelse X == 9 end,
  338. FValue = binstr:strip(binstr:substr(Line, Index+1)),
  339. FieldValue = case binstr:all(F2, FValue) of
  340. true ->
  341. FValue;
  342. _ ->
  343. % I couldn't figure out how to use a pure binary comprehension here :(
  344. list_to_binary([ filter_non_ascii(C) || <<C:8>> <= FValue])
  345. end,
  346. case binstr:strpos(Body, "\r\n") of
  347. 0 ->
  348. {lists:reverse([{FieldName, FieldValue} | Headers]), Body};
  349. 1 ->
  350. {lists:reverse([{FieldName, FieldValue} | Headers]), binstr:substr(Body, 3)};
  351. Index2 ->
  352. parse_headers(binstr:substr(Body, Index2 + 2), binstr:substr(Body, 1, Index2 - 1), [{FieldName, FieldValue} | Headers])
  353. end;
  354. false ->
  355. {lists:reverse(Headers), list_to_binary([Line, "\r\n", Body])}
  356. end
  357. end.
  358. filter_non_ascii(C) when (C > 31 andalso C < 127); C == 9 ->
  359. <<C>>;
  360. filter_non_ascii(_C) ->
  361. <<"?">>.
  362. decode_body(Type, Body, _InEncoding, none) ->
  363. decode_body(Type, << <<X/integer>> || <<X>> <= Body, X < 128 >>);
  364. decode_body(Type, Body, undefined, _OutEncoding) ->
  365. decode_body(Type, << <<X/integer>> || <<X>> <= Body, X < 128 >>);
  366. decode_body(Type, Body, InEncoding, OutEncoding) ->
  367. NewBody = decode_body(Type, Body),
  368. CD = case iconv:open(OutEncoding, fix_encoding(InEncoding)) of
  369. {ok, Res} -> Res;
  370. {error, einval} -> throw({bad_charset, fix_encoding(InEncoding)})
  371. end,
  372. {ok, Result} = try iconv:conv_chunked(CD, NewBody) of
  373. {ok, _} = Res2 -> Res2
  374. catch
  375. _:_ ->
  376. iconv:conv(CD, NewBody)
  377. end,
  378. iconv:close(CD),
  379. Result.
  380. -spec(decode_body/2 :: (Type :: binary() | 'undefined', Body :: binary()) -> binary()).
  381. decode_body(undefined, Body) ->
  382. Body;
  383. decode_body(Type, Body) ->
  384. case binstr:to_lower(Type) of
  385. <<"quoted-printable">> ->
  386. decode_quoted_printable(Body);
  387. <<"base64">> ->
  388. decode_base64(Body);
  389. _Other ->
  390. Body
  391. end.
  392. decode_base64(Body) ->
  393. base64:mime_decode(Body).
  394. decode_quoted_printable(Body) ->
  395. case binstr:strpos(Body, "\r\n") of
  396. 0 ->
  397. decode_quoted_printable(Body, <<>>, []);
  398. Index ->
  399. decode_quoted_printable(binstr:substr(Body, 1, Index +1), binstr:substr(Body, Index + 2), [])
  400. end.
  401. decode_quoted_printable(<<>>, <<>>, Acc) ->
  402. list_to_binary(lists:reverse(Acc));
  403. decode_quoted_printable(Line, Rest, Acc) ->
  404. case binstr:strpos(Rest, "\r\n") of
  405. 0 ->
  406. decode_quoted_printable(Rest, <<>>, [decode_quoted_printable_line(Line, []) | Acc]);
  407. Index ->
  408. %io:format("next line ~p~nnext rest ~p~n", [binstr:substr(Rest, 1, Index +1), binstr:substr(Rest, Index + 2)]),
  409. decode_quoted_printable(binstr:substr(Rest, 1, Index +1), binstr:substr(Rest, Index + 2),
  410. [decode_quoted_printable_line(Line, []) | Acc])
  411. end.
  412. decode_quoted_printable_line(<<>>, Acc) ->
  413. lists:reverse(Acc);
  414. decode_quoted_printable_line(<<$\r, $\n>>, Acc) ->
  415. lists:reverse(["\r\n" | Acc]);
  416. decode_quoted_printable_line(<<$=, C, T/binary>>, Acc) when C =:= $\s; C =:= $\t ->
  417. case binstr:all(fun(X) -> X =:= $\s orelse X =:= $\t end, T) of
  418. true ->
  419. lists:reverse(Acc);
  420. false ->
  421. throw(badchar)
  422. end;
  423. decode_quoted_printable_line(<<$=, $\r, $\n>>, Acc) ->
  424. lists:reverse(Acc);
  425. decode_quoted_printable_line(<<$=, A:2/binary, T/binary>>, Acc) ->
  426. %<<X:1/binary, Y:1/binary>> = A,
  427. case binstr:all(fun(C) -> (C >= $0 andalso C =< $9) orelse (C >= $A andalso C =< $F) orelse (C >= $a andalso C =< $f) end, A) of
  428. true ->
  429. {ok, [C | []], []} = io_lib:fread("~16u", binary_to_list(A)),
  430. decode_quoted_printable_line(T, [C | Acc]);
  431. false ->
  432. throw(badchar)
  433. end;
  434. decode_quoted_printable_line(<<$=>>, Acc) ->
  435. % soft newline
  436. lists:reverse(Acc);
  437. decode_quoted_printable_line(<<H, T/binary>>, Acc) when H >= $!, H =< $< ->
  438. decode_quoted_printable_line(T, [H | Acc]);
  439. decode_quoted_printable_line(<<H, T/binary>>, Acc) when H >= $>, H =< $~ ->
  440. decode_quoted_printable_line(T, [H | Acc]);
  441. decode_quoted_printable_line(<<H, T/binary>>, Acc) when H =:= $\s; H =:= $\t ->
  442. % if the rest of the line is whitespace, truncate it
  443. case binstr:all(fun(X) -> X =:= $\s orelse X =:= $\t end, T) of
  444. true ->
  445. lists:reverse(Acc);
  446. false ->
  447. decode_quoted_printable_line(T, [H | Acc])
  448. end;
  449. decode_quoted_printable_line(<<H, T/binary>>, Acc) ->
  450. decode_quoted_printable_line(T, [H| Acc]).
  451. check_headers(Headers) ->
  452. Checked = [<<"MIME-Version">>, <<"Date">>, <<"From">>, <<"Message-ID">>, <<"References">>, <<"Subject">>],
  453. check_headers(Checked, lists:reverse(Headers)).
  454. check_headers([], Headers) ->
  455. lists:reverse(Headers);
  456. check_headers([Header | Tail], Headers) ->
  457. case get_header_value(Header, Headers) of
  458. undefined when Header == <<"MIME-Version">> ->
  459. check_headers(Tail, [{<<"MIME-Version">>, <<"1.0">>} | Headers]);
  460. undefined when Header == <<"Date">> ->
  461. check_headers(Tail, [{<<"Date">>, list_to_binary(smtp_util:rfc5322_timestamp())} | Headers]);
  462. undefined when Header == <<"From">> ->
  463. erlang:error(missing_from);
  464. undefined when Header == <<"Message-ID">> ->
  465. check_headers(Tail, [{<<"Message-ID">>, list_to_binary(smtp_util:generate_message_id())} | Headers]);
  466. undefined when Header == <<"References">> ->
  467. case get_header_value(<<"In-Reply-To">>, Headers) of
  468. undefined ->
  469. check_headers(Tail, Headers); % ok, whatever
  470. ReplyID ->
  471. check_headers(Tail, [{<<"References">>, ReplyID} | Headers])
  472. end;
  473. References when Header == <<"References">> ->
  474. % check if the in-reply-to header, if present, is in references
  475. case get_header_value(<<"In-Reply-To">>, Headers) of
  476. undefined ->
  477. check_headers(Tail, Headers); % ok, whatever
  478. ReplyID ->
  479. case binstr:strpos(binstr:to_lower(References), binstr:to_lower(ReplyID)) of
  480. 0 ->
  481. % okay, tack on the reply-to to the end of References
  482. check_headers(Tail, [{<<"References">>, list_to_binary([References, " ", ReplyID])} | proplists:delete(<<"References">>, Headers)]);
  483. _Index ->
  484. check_headers(Tail, Headers) % nothing to do
  485. end
  486. end;
  487. _ ->
  488. check_headers(Tail, Headers)
  489. end.
  490. ensure_content_headers(Type, SubType, Parameters, Headers, Body, Toplevel) ->
  491. CheckHeaders = [<<"Content-Type">>, <<"Content-Disposition">>, <<"Content-Transfer-Encoding">>],
  492. ensure_content_headers(CheckHeaders, Type, SubType, Parameters, lists:reverse(Headers), Body, Toplevel).
  493. ensure_content_headers([], _, _, Parameters, Headers, _, _) ->
  494. {Parameters, lists:reverse(Headers)};
  495. ensure_content_headers([Header | Tail], Type, SubType, Parameters, Headers, Body, Toplevel) ->
  496. case get_header_value(Header, Headers) of
  497. undefined when Header == <<"Content-Type">>, ((Type == <<"text">> andalso SubType =/= <<"plain">>) orelse Type =/= <<"text">>) ->
  498. % no content-type header, and its not text/plain
  499. CT = io_lib:format("~s/~s", [Type, SubType]),
  500. CTP = case Type of
  501. <<"multipart">> ->
  502. Boundary = case proplists:get_value(<<"boundary">>, proplists:get_value(<<"content-type-params">>, Parameters, [])) of
  503. undefined ->
  504. list_to_binary(smtp_util:generate_message_boundary());
  505. B ->
  506. B
  507. end,
  508. [{<<"boundary">>, Boundary} | proplists:delete(<<"boundary">>, proplists:get_value(<<"content-type-params">>, Parameters, []))];
  509. <<"text">> ->
  510. Charset = case proplists:get_value(<<"charset">>, proplists:get_value(<<"content-type-params">>, Parameters, [])) of
  511. undefined ->
  512. guess_charset(Body);
  513. C ->
  514. C
  515. end,
  516. [{<<"charset">>, Charset} | proplists:delete(<<"charset">>, proplists:get_value(<<"content-type-params">>, Parameters, []))];
  517. _ ->
  518. proplists:get_value(<<"content-type-params">>, Parameters, [])
  519. end,
  520. %CTP = proplists:get_value(<<"content-type-params">>, Parameters, [guess_charset(Body)]),
  521. CTH = binstr:join([CT | encode_parameters(CTP)], ";"),
  522. NewParameters = [{<<"content-type-params">>, CTP} | proplists:delete(<<"content-type-params">>, Parameters)],
  523. ensure_content_headers(Tail, Type, SubType, NewParameters, [{<<"Content-Type">>, CTH} | Headers], Body, Toplevel);
  524. undefined when Header == <<"Content-Type">> ->
  525. % no content-type header and its text/plain
  526. Charset = case proplists:get_value(<<"charset">>, proplists:get_value(<<"content-type-params">>, Parameters, [])) of
  527. undefined ->
  528. guess_charset(Body);
  529. C ->
  530. C
  531. end,
  532. case Charset of
  533. <<"us-ascii">> ->
  534. % the default
  535. ensure_content_headers(Tail, Type, SubType, Parameters, Headers, Body, Toplevel);
  536. _ ->
  537. CTP = [{<<"charset">>, Charset} | proplists:delete(<<"charset">>, proplists:get_value(<<"content-type-params">>, Parameters, []))],
  538. CTH = binstr:join([<<"text/plain">> | encode_parameters(CTP)], ";"),
  539. NewParameters = [{<<"content-type-params">>, CTP} | proplists:delete(<<"content-type-params">>, Parameters)],
  540. ensure_content_headers(Tail, Type, SubType, NewParameters, [{<<"Content-Type">>, CTH} | Headers], Body, Toplevel)
  541. end;
  542. undefined when Header == <<"Content-Transfer-Encoding">>, Type =/= <<"multipart">> ->
  543. Enc = case proplists:get_value(<<"transfer-encoding">>, Parameters) of
  544. undefined ->
  545. guess_best_encoding(Body);
  546. Value ->
  547. Value
  548. end,
  549. case Enc of
  550. <<"7bit">> ->
  551. ensure_content_headers(Tail, Type, SubType, Parameters, Headers, Body, Toplevel);
  552. _ ->
  553. ensure_content_headers(Tail, Type, SubType, Parameters, [{<<"Content-Transfer-Encoding">>, Enc} | Headers], Body, Toplevel)
  554. end;
  555. undefined when Header == <<"Content-Disposition">>, Toplevel == false ->
  556. CD = proplists:get_value(<<"disposition">>, Parameters, <<"inline">>),
  557. CDP = proplists:get_value(<<"disposition-params">>, Parameters, []),
  558. CDH = binstr:join([CD | encode_parameters(CDP)], ";"),
  559. ensure_content_headers(Tail, Type, SubType, Parameters, [{<<"Content-Disposition">>, CDH} | Headers], Body, Toplevel);
  560. _ ->
  561. ensure_content_headers(Tail, Type, SubType, Parameters, Headers, Body, Toplevel)
  562. end.
  563. guess_charset(Body) ->
  564. case binstr:all(fun(X) -> X < 128 end, Body) of
  565. true -> <<"us-ascii">>;
  566. false -> <<"utf-8">>
  567. end.
  568. guess_best_encoding(<<Body:200/binary, Rest/binary>>) when Rest =/= <<>> ->
  569. guess_best_encoding(Body);
  570. guess_best_encoding(Body) ->
  571. Size = byte_size(Body),
  572. % get only the allowed ascii characters
  573. % TODO - this might not be the complete list
  574. FilteredSize = length([X || <<X>> <= Body, ((X > 31 andalso X < 127) orelse X == $\r orelse X == $\n)]),
  575. Percent = round((FilteredSize / Size) * 100),
  576. %based on the % of printable characters, choose an encoding
  577. if
  578. Percent == 100 ->
  579. <<"7bit">>;
  580. Percent > 80 ->
  581. <<"quoted-printable">>;
  582. true ->
  583. <<"base64">>
  584. end.
  585. encode_parameters([[]]) ->
  586. [];
  587. encode_parameters(Parameters) ->
  588. [encode_parameter(Parameter) || Parameter <- Parameters].
  589. encode_parameter({X, Y}) ->
  590. case escape_tspecial(Y, false, <<>>) of
  591. {true, Special} -> [X, $=, $", Special, $"];
  592. false -> [X, $=, Y]
  593. end.
  594. % See also: http://www.ietf.org/rfc/rfc2045.txt section 5.1
  595. escape_tspecial(<<>>, false, _Acc) ->
  596. false;
  597. escape_tspecial(<<>>, IsSpecial, Acc) ->
  598. {IsSpecial, Acc};
  599. escape_tspecial(<<C, Rest/binary>>, _IsSpecial, Acc) when C =:= $" ->
  600. escape_tspecial(Rest, true, <<Acc/binary, $\\, $">>);
  601. escape_tspecial(<<C, Rest/binary>>, _IsSpecial, Acc) when C =:= $\\ ->
  602. escape_tspecial(Rest, true, <<Acc/binary, $\\, $\\>>);
  603. escape_tspecial(<<C, Rest/binary>>, _IsSpecial, Acc)
  604. when C =:= $(; C =:= $); C =:= $<; C =:= $>; C =:= $@;
  605. C =:= $,; C =:= $;; C =:= $:; C =:= $/; C =:= $[;
  606. C =:= $]; C =:= $?; C =:= $=; C =:= $\s ->
  607. escape_tspecial(Rest, true, <<Acc/binary, C>>);
  608. escape_tspecial(<<C, Rest/binary>>, IsSpecial, Acc) ->
  609. escape_tspecial(Rest, IsSpecial, <<Acc/binary, C>>).
  610. encode_headers(Headers) ->
  611. encode_headers(Headers, []).
  612. encode_headers([], EncodedHeaders) ->
  613. EncodedHeaders;
  614. encode_headers([{Key, Value}|T] = _Headers, EncodedHeaders) ->
  615. encode_headers(T, encode_folded_header(list_to_binary([Key,": ",Value]),
  616. EncodedHeaders)).
  617. encode_folded_header(Header, HeaderLines) ->
  618. case binstr:strchr(Header, $;) of
  619. 0 ->
  620. HeaderLines ++ [Header];
  621. Index ->
  622. Remainder = binstr:substr(Header, Index+1),
  623. TabbedRemainder = case Remainder of
  624. <<$\t,_Rest/binary>> ->
  625. Remainder;
  626. _ ->
  627. list_to_binary(["\t", Remainder])
  628. end,
  629. % TODO - not tail recursive
  630. HeaderLines ++ [ binstr:substr(Header, 1, Index) ] ++
  631. encode_folded_header(TabbedRemainder, [])
  632. end.
  633. encode_component(_Type, _SubType, Headers, Params, Body) ->
  634. if
  635. is_list(Body) -> % is this a multipart component?
  636. Boundary = proplists:get_value(<<"boundary">>, proplists:get_value(<<"content-type-params">>, Params)),
  637. [<<>>] ++ % blank line before start of component
  638. lists:flatmap(
  639. fun(Part) ->
  640. [list_to_binary([<<"--">>, Boundary])] ++ % start with the boundary
  641. encode_component_part(Part)
  642. end,
  643. Body
  644. ) ++ [list_to_binary([<<"--">>, Boundary, <<"--">>])] % final boundary (with /--$/)
  645. ++ [<<>>]; % blank line at the end of the multipart component
  646. true -> % or an inline component?
  647. %encode_component_part({Type, SubType, Headers, Params, Body})
  648. encode_body(
  649. get_header_value(<<"Content-Transfer-Encoding">>, Headers),
  650. [Body]
  651. )
  652. end.
  653. encode_component_part(Part) ->
  654. case Part of
  655. {<<"multipart">>, SubType, Headers, PartParams, Body} ->
  656. {FixedParams, FixedHeaders} = ensure_content_headers(<<"multipart">>, SubType, PartParams, Headers, Body, false),
  657. encode_headers(FixedHeaders) ++ [<<>>] ++
  658. encode_component(<<"multipart">>, SubType, FixedHeaders, FixedParams, Body);
  659. {Type, SubType, Headers, PartParams, Body} ->
  660. PartData = case Body of
  661. {_,_,_,_,_} -> encode_component_part(Body);
  662. String -> [String]
  663. end,
  664. {_FixedParams, FixedHeaders} = ensure_content_headers(Type, SubType, PartParams, Headers, Body, false),
  665. encode_headers(FixedHeaders) ++ [<<>>] ++
  666. encode_body(
  667. get_header_value(<<"Content-Transfer-Encoding">>, FixedHeaders),
  668. PartData
  669. );
  670. _ ->
  671. io:format("encode_component_part couldn't match Part to: ~p~n", [Part]),
  672. []
  673. end.
  674. encode_body(undefined, Body) ->
  675. Body;
  676. encode_body(Type, Body) ->
  677. case binstr:to_lower(Type) of
  678. <<"quoted-printable">> ->
  679. [InnerBody] = Body,
  680. encode_quoted_printable(InnerBody);
  681. <<"base64">> ->
  682. [InnerBody] = Body,
  683. wrap_to_76(base64:encode(InnerBody));
  684. _ -> Body
  685. end.
  686. wrap_to_76(String) ->
  687. [wrap_to_76(String, [])].
  688. wrap_to_76(<<>>, Acc) ->
  689. list_to_binary(lists:reverse(Acc));
  690. wrap_to_76(<<Head:76/binary, Tail/binary>>, Acc) ->
  691. wrap_to_76(Tail, [<<"\r\n">>, Head | Acc]);
  692. wrap_to_76(Head, Acc) ->
  693. list_to_binary(lists:reverse([<<"\r\n">>, Head | Acc])).
  694. encode_quoted_printable(Body) ->
  695. [encode_quoted_printable(Body, [], 0)].
  696. encode_quoted_printable(Body, Acc, L) when L >= 75 ->
  697. LastLine = case string:str(Acc, "\n") of
  698. 0 ->
  699. Acc;
  700. Index ->
  701. string:substr(Acc, 1, Index-1)
  702. end,
  703. %Len = length(LastLine),
  704. case string:str(LastLine, " ") of
  705. 0 when L =:= 75 ->
  706. % uh-oh, no convienient whitespace, just cram a soft newline in
  707. encode_quoted_printable(Body, [$\n, $\r, $= | Acc], 0);
  708. 1 when L =:= 75 ->
  709. % whitespace is the last character we wrote
  710. encode_quoted_printable(Body, [$\n, $\r, $= | Acc], 0);
  711. SIndex when (L - 75) < SIndex ->
  712. % okay, we can safely stick some whitespace in
  713. Prefix = string:substr(Acc, 1, SIndex-1),
  714. Suffix = string:substr(Acc, SIndex),
  715. NewAcc = lists:concat([Prefix, "\n\r=", Suffix]),
  716. encode_quoted_printable(Body, NewAcc, 0);
  717. _ ->
  718. % worst case, we're over 75 characters on the line
  719. % and there's no obvious break points, just stick one
  720. % in at position 75 and call it good. However, we have
  721. % to be very careful not to stick the soft newline in
  722. % the middle of an existing quoted-printable escape.
  723. % TODO - fix this to be less stupid
  724. I = 3, % assume we're at most 3 over our cutoff
  725. Prefix = string:substr(Acc, 1, I),
  726. Suffix = string:substr(Acc, I+1),
  727. NewAcc = lists:concat([Prefix, "\n\r=", Suffix]),
  728. encode_quoted_printable(Body, NewAcc, 0)
  729. end;
  730. encode_quoted_printable(<<>>, Acc, _L) ->
  731. list_to_binary(lists:reverse(Acc));
  732. encode_quoted_printable(<<$=, T/binary>> , Acc, L) ->
  733. encode_quoted_printable(T, [$D, $3, $= | Acc], L+3);
  734. encode_quoted_printable(<<$\r, $\n, T/binary>> , Acc, _L) ->
  735. encode_quoted_printable(T, [$\n, $\r | Acc], 0);
  736. encode_quoted_printable(<<H, T/binary>>, Acc, L) when H >= $!, H =< $< ->
  737. encode_quoted_printable(T, [H | Acc], L+1);
  738. encode_quoted_printable(<<H, T/binary>>, Acc, L) when H >= $>, H =< $~ ->
  739. encode_quoted_printable(T, [H | Acc], L+1);
  740. encode_quoted_printable(<<H, $\r, $\n, T/binary>>, Acc, _L) when H == $\s; H == $\t ->
  741. [[A, B]] = io_lib:format("~2.16.0B", [H]),
  742. encode_quoted_printable(T, [$\n, $\r, B, A, $= | Acc], 0);
  743. encode_quoted_printable(<<H, T/binary>>, Acc, L) when H == $\s; H == $\t ->
  744. encode_quoted_printable(T, [H | Acc], L+1);
  745. encode_quoted_printable(<<H, T/binary>>, Acc, L) ->
  746. [[A, B]] = io_lib:format("~2.16.0B", [H]),
  747. encode_quoted_printable(T, [B, A, $= | Acc], L+3).
  748. get_default_encoding() ->
  749. case code:ensure_loaded(iconv) of
  750. {error, _} ->
  751. none;
  752. {module, iconv} ->
  753. <<"utf-8//IGNORE">>
  754. end.
  755. % convert some common invalid character names into the correct ones
  756. fix_encoding(Encoding) when Encoding == <<"utf8">>; Encoding == <<"UTF8">> ->
  757. <<"UTF-8">>;
  758. fix_encoding(Encoding) ->
  759. Encoding.
  760. -ifdef(TEST).
  761. parse_with_comments_test_() ->
  762. [
  763. {"bleh",
  764. fun() ->
  765. ?assertEqual(<<"1.0">>, parse_with_comments(<<"1.0">>)),
  766. ?assertEqual(<<"1.0">>, parse_with_comments(<<"1.0 (produced by MetaSend Vx.x)">>)),
  767. ?assertEqual(<<"1.0">>, parse_with_comments(<<"(produced by MetaSend Vx.x) 1.0">>)),
  768. ?assertEqual(<<"1.0">>, parse_with_comments(<<"1.(produced by MetaSend Vx.x)0">>))
  769. end
  770. },
  771. {"comments that parse as empty",
  772. fun() ->
  773. ?assertEqual(<<>>, parse_with_comments(<<"(comment (nested (deeply)) (and (oh no!) again))">>)),
  774. ?assertEqual(<<>>, parse_with_comments(<<"(\\)\\\\)">>)),
  775. ?assertEqual(<<>>, parse_with_comments(<<"(by way of Whatever <redir@my.org>) (generated by Eudora)">>))
  776. end
  777. },
  778. {"some more",
  779. fun() ->
  780. ?assertEqual(<<":sysmail@ group. org, Muhammed. Ali @Vegas.WBA">>, parse_with_comments(<<"\":sysmail\"@ group. org, Muhammed.(the greatest) Ali @(the)Vegas.WBA">>)),
  781. ?assertEqual(<<"Pete <pete@silly.test>">>, parse_with_comments(<<"Pete(A wonderful \\) chap) <pete(his account)@silly.test(his host)>">>))
  782. end
  783. },
  784. {"non list values",
  785. fun() ->
  786. ?assertEqual(undefined, parse_with_comments(undefined)),
  787. ?assertEqual(17, parse_with_comments(17))
  788. end
  789. },
  790. {"Parens within quotes ignored",
  791. fun() ->
  792. ?assertEqual(<<"Height (from xkcd).eml">>, parse_with_comments(<<"\"Height (from xkcd).eml\"">>)),
  793. ?assertEqual(<<"Height (from xkcd).eml">>, parse_with_comments(<<"\"Height \(from xkcd\).eml\"">>))
  794. end
  795. },
  796. {"Escaped quotes are handled correctly",
  797. fun() ->
  798. ?assertEqual(<<"Hello \"world\"">>, parse_with_comments(<<"Hello \\\"world\\\"">>)),
  799. ?assertEqual(<<"<boss@nil.test>, Giant; \"Big\" Box <sysservices@example.net>">>, parse_with_comments(<<"<boss@nil.test>, \"Giant; \\\"Big\\\" Box\" <sysservices@example.net>">>))
  800. end
  801. },
  802. {"backslash not part of a quoted pair",
  803. fun() ->
  804. ?assertEqual(<<"AC \\ DC">>, parse_with_comments(<<"AC \\ DC">>)),
  805. ?assertEqual(<<"AC DC">>, parse_with_comments(<<"AC ( \\ ) DC">>))
  806. end
  807. },
  808. {"Unterminated quotes or comments",
  809. fun() ->
  810. ?assertError(unterminated_quotes, parse_with_comments(<<"\"Hello there ">>)),
  811. ?assertError(unterminated_quotes, parse_with_comments(<<"\"Hello there \\\"">>)),
  812. ?assertError(unterminated_comment, parse_with_comments(<<"(Hello there ">>)),
  813. ?assertError(unterminated_comment, parse_with_comments(<<"(Hello there \\\)">>))
  814. end
  815. }
  816. ].
  817. parse_content_type_test_() ->
  818. [
  819. {"parsing content types",
  820. fun() ->
  821. ?assertEqual({<<"text">>, <<"plain">>, [{<<"charset">>, <<"us-ascii">>}]}, parse_content_type(<<"text/plain; charset=us-ascii (Plain text)">>)),
  822. ?assertEqual({<<"text">>, <<"plain">>, [{<<"charset">>, <<"us-ascii">>}]}, parse_content_type(<<"text/plain; charset=\"us-ascii\"">>)),
  823. ?assertEqual({<<"text">>, <<"plain">>, [{<<"charset">>, <<"us-ascii">>}]}, parse_content_type(<<"Text/Plain; Charset=\"us-ascii\"">>)),
  824. ?assertEqual({<<"multipart">>, <<"mixed">>, [{<<"boundary">>, <<"----_=_NextPart_001_01C9DCAE.1F2CB390">>}]},
  825. parse_content_type(<<"multipart/mixed; boundary=\"----_=_NextPart_001_01C9DCAE.1F2CB390\"">>))
  826. end
  827. },
  828. {"parsing content type with a tab in it",
  829. fun() ->
  830. ?assertEqual({<<"text">>, <<"plain">>, [{<<"charset">>, <<"us-ascii">>}]}, parse_content_type(<<"text/plain;\tcharset=us-ascii">>)),
  831. ?assertEqual({<<"text">>, <<"plain">>, [{<<"charset">>, <<"us-ascii">>}, {<<"foo">>, <<"bar">>}]}, parse_content_type(<<"text/plain;\tcharset=us-ascii;\tfoo=bar">>))
  832. end
  833. },
  834. {"invalid content types",
  835. fun() ->
  836. ?assertThrow(bad_content_type, parse_content_type(<<"text\\plain; charset=us-ascii">>)),
  837. ?assertThrow(bad_content_type, parse_content_type(<<"text/plain; charset us-ascii">>))
  838. end
  839. }
  840. ].
  841. parse_content_disposition_test_() ->
  842. [
  843. {"parsing valid dispositions",
  844. fun() ->
  845. ?assertEqual({<<"inline">>, []}, parse_content_disposition(<<"inline">>)),
  846. ?assertEqual({<<"inline">>, []}, parse_content_disposition(<<"inline;">>)),
  847. ?assertEqual({<<"attachment">>, [{<<"filename">>, <<"genome.jpeg">>}, {<<"modification-date">>, <<"Wed, 12 Feb 1997 16:29:51 -0500">>}]}, parse_content_disposition(<<"attachment; filename=genome.jpeg;modification-date=\"Wed, 12 Feb 1997 16:29:51 -0500\";">>)),
  848. ?assertEqual({<<"text/plain">>, [{<<"charset">>, <<"us-ascii">>}]}, parse_content_disposition(<<"text/plain; charset=us-ascii (Plain text)">>))
  849. end
  850. },
  851. {"invalid dispositions",
  852. fun() ->
  853. ?assertThrow(bad_disposition, parse_content_disposition(<<"inline; =bar">>)),
  854. ?assertThrow(bad_disposition, parse_content_disposition(<<"inline; bar">>))
  855. end
  856. }
  857. ].
  858. various_parsing_test_() ->
  859. [
  860. {"split_body_by_boundary test",
  861. fun() ->
  862. ?assertEqual([{[], <<"foo bar baz">>}], split_body_by_boundary_(<<"stuff\r\nfoo bar baz">>, <<"--bleh">>, [])),
  863. ?assertEqual([{[], <<"foo\r\n">>}, {[], <<>>}, {[], <<>>}, {[], <<"bar baz">>}], split_body_by_boundary_(<<"stuff\r\nfoo\r\n--bleh\r\n--bleh\r\n--bleh-- stuff\r\nbar baz">>, <<"--bleh">>, [])),
  864. %?assertEqual([{[], []}, {[], []}, {[], "bar baz"}], split_body_by_boundary_("\r\n--bleh\r\n--bleh\r\n", "--bleh", [])),
  865. %?assertMatch([{"text", "plain", [], _,"foo\r\n"}], split_body_by_boundary("stuff\r\nfoo\r\n--bleh\r\n--bleh\r\n--bleh-- stuff\r\nbar baz", "--bleh", "1.0"))
  866. ?assertEqual({[], <<"foo: bar\r\n">>}, parse_headers(<<"\r\nfoo: bar\r\n">>)),
  867. ?assertEqual({[{<<"foo">>, <<"barbaz">>}], <<>>}, parse_headers(<<"foo: bar\r\n baz\r\n">>)),
  868. ?assertEqual({[], <<" foo bar baz\r\nbam">>}, parse_headers(<<"\sfoo bar baz\r\nbam">>)),
  869. ok
  870. end
  871. },
  872. {"Headers with non-ASCII characters",
  873. fun() ->
  874. ?assertEqual({[{<<"foo">>, <<"bar ?? baz">>}], <<>>}, parse_headers(<<"foo: bar ø baz\r\n">>)),
  875. ?assertEqual({[], <<"bär: bar baz\r\n">>}, parse_headers(<<"bär: bar baz\r\n">>))
  876. end
  877. },
  878. {"Headers with tab characters",
  879. fun() ->
  880. ?assertEqual({[{<<"foo">>, <<"bar baz">>}], <<>>}, parse_headers(<<"foo: bar baz\r\n">>))
  881. end
  882. }
  883. ].
  884. -define(IMAGE_MD5, <<110,130,37,247,39,149,224,61,114,198,227,138,113,4,198,60>>).
  885. parse_example_mails_test_() ->
  886. Getmail = fun(File) ->
  887. {ok, Email} = file:read_file(string:concat("../testdata/", File)),
  888. %Email = binary_to_list(Bin),
  889. decode(Email)
  890. end,
  891. [
  892. {"parse a plain text email",
  893. fun() ->
  894. Decoded = Getmail("Plain-text-only.eml"),
  895. ?assertEqual(5, tuple_size(Decoded)),
  896. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  897. ?assertEqual({<<"text">>, <<"plain">>}, {Type, SubType}),
  898. ?assertEqual(<<"This message contains only plain text.\r\n">>, Body)
  899. end
  900. },
  901. {"parse a plain text email with no content type",
  902. fun() ->
  903. Decoded = Getmail("Plain-text-only-no-content-type.eml"),
  904. ?assertEqual(5, tuple_size(Decoded)),
  905. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  906. ?assertEqual({<<"text">>, <<"plain">>}, {Type, SubType}),
  907. ?assertEqual(<<"This message contains only plain text.\r\n">>, Body)
  908. end
  909. },
  910. {"parse a plain text email with no MIME header",
  911. fun() ->
  912. {Type, SubType, _Headers, _Properties, Body} =
  913. Getmail("Plain-text-only-no-MIME.eml"),
  914. ?assertEqual({<<"text">>, <<"plain">>}, {Type, SubType}),
  915. ?assertEqual(<<"This message contains only plain text.\r\n">>, Body)
  916. end
  917. },
  918. {"parse an email that says it is multipart but contains no boundaries",
  919. fun() ->
  920. ?assertError(missing_boundary, Getmail("Plain-text-only-with-boundary-header.eml"))
  921. end
  922. },
  923. {"parse a multipart email with no MIME header",
  924. fun() ->
  925. ?assertError(non_mime_multipart, Getmail("rich-text-no-MIME.eml"))
  926. end
  927. },
  928. {"rich text",
  929. fun() ->
  930. %% pardon my naming here. apparently 'rich text' in mac mail
  931. %% means 'html'.
  932. Decoded = Getmail("rich-text.eml"),
  933. ?assertEqual(5, tuple_size(Decoded)),
  934. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  935. ?assertEqual({<<"multipart">>, <<"alternative">>}, {Type, SubType}),
  936. ?assertEqual(2, length(Body)),
  937. [Plain, Html] = Body,
  938. ?assertEqual({5, 5}, {tuple_size(Plain), tuple_size(Html)}),
  939. ?assertMatch({<<"text">>, <<"plain">>, _, _, <<"This message contains rich text.">>}, Plain),
  940. ?assertMatch({<<"text">>, <<"html">>, _, _, <<"<html><body style=\"word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; \"><b>This </b><i>message </i><span class=\"Apple-style-span\" style=\"text-decoration: underline;\">contains </span>rich text.</body></html>">>}, Html)
  941. end
  942. },
  943. {"rich text no boundary",
  944. fun() ->
  945. ?assertError(no_boundary, Getmail("rich-text-no-boundary.eml"))
  946. end
  947. },
  948. {"rich text missing first boundary",
  949. fun() ->
  950. % TODO - should we handle this more elegantly?
  951. Decoded = Getmail("rich-text-missing-first-boundary.eml"),
  952. ?assertEqual(5, tuple_size(Decoded)),
  953. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  954. ?assertEqual({<<"multipart">>, <<"alternative">>}, {Type, SubType}),
  955. ?assertEqual(1, length(Body)),
  956. [Html] = Body,
  957. ?assertEqual(5, tuple_size(Html)),
  958. ?assertMatch({<<"text">>, <<"html">>, _, _, <<"<html><body style=\"word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; \"><b>This </b><i>message </i><span class=\"Apple-style-span\" style=\"text-decoration: underline;\">contains </span>rich text.</body></html>">>}, Html)
  959. end
  960. },
  961. {"rich text missing last boundary",
  962. fun() ->
  963. ?assertError(missing_last_boundary, Getmail("rich-text-missing-last-boundary.eml"))
  964. end
  965. },
  966. {"rich text wrong last boundary",
  967. fun() ->
  968. ?assertError(missing_last_boundary, Getmail("rich-text-broken-last-boundary.eml"))
  969. end
  970. },
  971. {"rich text missing text content type",
  972. fun() ->
  973. %% pardon my naming here. apparently 'rich text' in mac mail
  974. %% means 'html'.
  975. Decoded = Getmail("rich-text-no-text-contenttype.eml"),
  976. ?assertEqual(5, tuple_size(Decoded)),
  977. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  978. ?assertEqual({<<"multipart">>, <<"alternative">>}, {Type, SubType}),
  979. ?assertEqual(2, length(Body)),
  980. [Plain, Html] = Body,
  981. ?assertEqual({5, 5}, {tuple_size(Plain), tuple_size(Html)}),
  982. ?assertMatch({<<"text">>, <<"plain">>, _, _, <<"This message contains rich text.">>}, Plain),
  983. ?assertMatch({<<"text">>, <<"html">>, _, _, <<"<html><body style=\"word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; \"><b>This </b><i>message </i><span class=\"Apple-style-span\" style=\"text-decoration: underline;\">contains </span>rich text.</body></html>">>}, Html)
  984. end
  985. },
  986. {"text attachment only",
  987. fun() ->
  988. Decoded = Getmail("text-attachment-only.eml"),
  989. ?assertEqual(5, tuple_size(Decoded)),
  990. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  991. ?assertEqual({<<"multipart">>, <<"mixed">>}, {Type, SubType}),
  992. ?assertEqual(1, length(Body)),
  993. Rich = <<"{\\rtf1\\ansi\\ansicpg1252\\cocoartf949\\cocoasubrtf460\r\n{\\fonttbl\\f0\\fswiss\\fcharset0 Helvetica;}\r\n{\\colortbl;\\red255\\green255\\blue255;}\r\n\\margl1440\\margr1440\\vieww9000\\viewh8400\\viewkind0\r\n\\pard\\tx720\\tx1440\\tx2160\\tx2880\\tx3600\\tx4320\\tx5040\\tx5760\\tx6480\\tx7200\\tx7920\\tx8640\\ql\\qnatural\\pardirnatural\r\n\r\n\\f0\\fs24 \\cf0 This is a basic rtf file.}">>,
  994. ?assertMatch([{<<"text">>, <<"rtf">>, _, _, Rich}], Body)
  995. end
  996. },
  997. {"image attachment only",
  998. fun() ->
  999. Decoded = Getmail("image-attachment-only.eml"),
  1000. ?assertEqual(5, tuple_size(Decoded)),
  1001. {Type, SubType, _Headers, _Properties, Body} = Decoded,
  1002. ?assertEqual({<<"multipart">>, <<"mixed">>}, {Type, SubType}),
  1003. ?assertEqual(1, length(Body)),
  1004. ?assertMatch([{<<"image">>, <<"jpeg">>, _, _, _}], Body),
  1005. [H | _] = Body,
  1006. [{<<"image">>, <<"jpeg">>, _, Parameters, _Image}] = Body,
  1007. ?assertEqual(?IMAGE_MD5, erlang:md5(element(5, H))),
  1008. ?assertEqual(<<"inline">>, proplists:get_value(<<"disposition">>, Parameters)),
  1009. ?assertEqual(<<"chili-pepper.jpg">>, proplists:get_value(<<"filename">>, proplists:get_value(<<"disposition-params">>, Parameters))),
  1010. ?assertEqual(<<"chili-pepper.jpg">>, proplists:get_value(<<"name">>, proplists:get_value(<<"content-type-params">>, Parameters)))
  1011. end
  1012. },
  1013. {"message attachment only",
  1014. fun() ->
  1015. Decoded = Getmail("message-as-attachment.eml"),
  1016. ?assertMatch({<<"multipart">>, <<"mixed">>, _, _, _}, Decoded),
  1017. [Body] = element(5, Decoded),
  1018. ?assertMatch({<<"message">>, <<"rfc822">>, _, _, _}, Body),
  1019. Subbody = element(5, Body),
  1020. ?assertMatch({<<"text">>, <<"plain">>, _, _, _}, Subbody),
  1021. ?assertEqual(<<"This message contains only plain text.\r\n">>, element(5, Subbody))
  1022. end
  1023. },
  1024. {"message, image, and rtf attachments.",
  1025. fun() ->
  1026. Decoded = Getmail("message-image-text-attachments.eml"),
  1027. ?assertMatch({<<"multipart">>, <<"mixed">>, _, _, _}, Decoded),
  1028. ?assertEqual(3, length(element(5, Decoded))),
  1029. [Message, Rtf, Image] = element(5, Decoded),
  1030. ?assertMatch({<<"message">>, <<"rfc822">>, _, _, _}, Message),
  1031. Submessage = element(5, Message),
  1032. ?assertMatch({<<"text">>, <<"plain">>, _, _, <<"This message contains only plain text.\r\n">>}, Submessage),
  1033. ?assertMatch({<<"text">>, <<"rtf">>, _, _, _}, Rtf),
  1034. ?assertEqual(<<"{\\rtf1\\ansi\\ansicpg1252\\cocoartf949\\cocoasubrtf460\r\n{\\fonttbl\\f0\\fswiss\\fcharset0 Helvetica;}\r\n{\\colortbl;\\red255\\green255\\blue255;}\r\n\\margl1440\\margr1440\\vieww9000\\viewh8400\\viewkind0\r\n\\pard\\tx720\\tx1440\\tx2160\\tx2880\\tx3600\\tx4320\\tx5040\\tx5760\\tx6480\\tx7200\\tx7920\\tx8640\\ql\\qnatural\\pardirnatural\r\n\r\n\\f0\\fs24 \\cf0 This is a basic rtf file.}">>, element(5, Rtf)),
  1035. ?assertMatch({<<"image">>, <<"jpeg">>, _, _, _}, Image),
  1036. ?assertEqual(?IMAGE_MD5, erlang:md5(element(5, Image)))
  1037. end
  1038. },
  1039. {"Outlook 2007 with leading tabs in quoted-printable.",
  1040. fun() ->
  1041. Decoded = Getmail("outlook-2007.eml"),
  1042. ?assertMatch({<<"multipart">>, <<"alternative">>, _, _, _}, Decoded)
  1043. end
  1044. },
  1045. {"The gamut",
  1046. fun() ->
  1047. % multipart/alternative
  1048. % text/plain
  1049. % multipart/mixed
  1050. % text/html
  1051. % message/rf822
  1052. % multipart/mixed
  1053. % message/rfc822
  1054. % text/plain
  1055. % text/html
  1056. % message/rtc822
  1057. % text/plain
  1058. % text/html
  1059. % image/jpeg
  1060. % text/html
  1061. % text/rtf
  1062. % text/html
  1063. Decoded = Getmail("the-gamut.eml"),
  1064. ?assertMatch({<<"multipart">>, <<"alternative">>, _, _, _}, Decoded),
  1065. ?assertEqual(2, length(element(5, Decoded))),
  1066. [Toptext, Topmultipart] = element(5, Decoded),
  1067. ?assertMatch({<<"text">>, <<"plain">>, _, _, _}, Toptext),
  1068. ?assertEqual(<<"This is rich text.\r\n\r\nThe list is html.\r\n\r\nAttchments:\r\nan email containing an attachment of an email.\r\nan email of only plain text.\r\nan image\r\nan rtf file.\r\n">>, element(5, Toptext)),
  1069. ?assertEqual(9, length(element(5, Topmultipart))),
  1070. [Html, Messagewithin, _Brhtml, _Message, _Brhtml, Image, _Brhtml, Rtf, _Brhtml] = element(5, Topmultipart),
  1071. ?assertMatch({<<"text">>, <<"html">>, _, _, _}, Html),
  1072. ?assertEqual(<<"<html><body style=\"word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; \"><b>This</b> is <i>rich</i> text.<div><br></div><div>The list is html.</div><div><br></div><div>Attchments:</div><div><ul class=\"MailOutline\"><li>an email containing an attachment of an email.</li><li>an email of only plain text.</li><li>an image</li><li>an rtf file.</li></ul></div><div></div></body></html>">>, element(5, Html)),
  1073. ?assertMatch({<<"message">>, <<"rfc822">>, _, _, _}, Messagewithin),
  1074. %?assertEqual(1, length(element(5, Messagewithin))),
  1075. ?assertMatch({<<"multipart">>, <<"mixed">>, _, _, [{<<"message">>, <<"rfc822">>, _, _, {<<"text">>, <<"plain">>, _, _, <<"This mess…