PageRenderTime 139ms CodeModel.GetById 23ms RepoModel.GetById 2ms app.codeStats 1ms

/deps/gen_smtp/src/gen_smtp_server_session.erl

http://github.com/zotonic/zotonic
Erlang | 2228 lines | 1962 code | 55 blank | 211 comment | 9 complexity | 52f8623d50fba83d7192aa47de908b6b MD5 | raw file
Possible License(s): Apache-2.0, CC-BY-SA-4.0, MIT, LGPL-2.1, BSD-3-Clause
  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 Process representing a SMTP session, extensible via a callback module. This
  23. %% module is implemented as a behaviour that the callback module should
  24. %% implement. To see the details of the required callback functions to provide,
  25. %% please see `smtp_server_example'.
  26. %% @see smtp_server_example
  27. -module(gen_smtp_server_session).
  28. -behaviour(gen_server).
  29. -ifdef(TEST).
  30. -include_lib("eunit/include/eunit.hrl").
  31. -endif.
  32. -define(MAXIMUMSIZE, 10485760). %10mb
  33. -define(BUILTIN_EXTENSIONS, [{"SIZE", "10485670"}, {"8BITMIME", true}, {"PIPELINING", true}]).
  34. -define(TIMEOUT, 180000). % 3 minutes
  35. %% External API
  36. -export([start_link/3, start/3]).
  37. %% gen_server callbacks
  38. -export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2,
  39. code_change/3]).
  40. -export([behaviour_info/1]).
  41. -record(envelope,
  42. {
  43. from :: binary() | 'undefined',
  44. to = [] :: [binary()],
  45. data = <<>> :: binary(),
  46. expectedsize = 0 :: pos_integer() | 0,
  47. auth = {<<>>, <<>>} :: {binary(), binary()} % {"username", "password"}
  48. }
  49. ).
  50. -record(state,
  51. {
  52. socket = erlang:error({undefined, socket}) :: port() | tuple(),
  53. module = erlang:error({undefined, module}) :: atom(),
  54. envelope = undefined :: 'undefined' | #envelope{},
  55. extensions = [] :: [{string(), string()}],
  56. waitingauth = false :: 'false' | 'plain' | 'login' | 'cram-md5',
  57. authdata :: 'undefined' | binary(),
  58. readmessage = false :: boolean(),
  59. tls = false :: boolean(),
  60. callbackstate :: any(),
  61. options = [] :: [tuple()]
  62. }
  63. ).
  64. %% @hidden
  65. -spec behaviour_info(atom()) -> [{atom(), non_neg_integer()}] | 'undefined'.
  66. behaviour_info(callbacks) ->
  67. [{init,4},
  68. {terminate,2},
  69. {code_change,3},
  70. {handle_HELO,2},
  71. {handle_EHLO,3},
  72. {handle_MAIL,2},
  73. {handle_MAIL_extension,2},
  74. {handle_RCPT,2},
  75. {handle_RCPT_extension,2},
  76. {handle_DATA,4},
  77. {handle_RSET,1},
  78. {handle_VRFY,2},
  79. {handle_other,3}];
  80. behaviour_info(_Other) ->
  81. undefined.
  82. %% @doc Start a SMTP session linked to the calling process.
  83. %% @see start/3
  84. -spec(start_link/3 :: (Socket :: port(), Module :: atom(), Options :: [tuple()]) -> {'ok', pid()} | 'ignore' | {'error', any()}).
  85. start_link(Socket, Module, Options) ->
  86. gen_server:start_link(?MODULE, [Socket, Module, Options], []).
  87. %% @doc Start a SMTP session. Arguments are `Socket' (probably opened via
  88. %% `gen_smtp_server' or an analogue), which is an abstract socket implemented
  89. %% via the `socket' module, `Module' is the name of the callback module
  90. %% implementing the SMTP session behaviour that you'd like to use and `Options'
  91. %% is the optional arguments provided by the accept server.
  92. -spec(start/3 :: (Socket :: port(), Module :: atom(), Options :: [tuple()]) -> {'ok', pid()} | 'ignore' | {'error', any()}).
  93. start(Socket, Module, Options) ->
  94. gen_server:start(?MODULE, [Socket, Module, Options], []).
  95. %% @private
  96. -spec(init/1 :: (Args :: list()) -> {'ok', #state{}, ?TIMEOUT} | {'stop', any()} | 'ignore').
  97. init([Socket, Module, Options]) ->
  98. {ok, {PeerName, _Port}} = socket:peername(Socket),
  99. case Module:init(proplists:get_value(hostname, Options, smtp_util:guess_FQDN()), proplists:get_value(sessioncount, Options, 0), PeerName, proplists:get_value(callbackoptions, Options, [])) of
  100. {ok, Banner, CallbackState} ->
  101. socket:send(Socket, ["220 ", Banner, "\r\n"]),
  102. socket:active_once(Socket),
  103. {ok, #state{socket = Socket, module = Module, options = Options, callbackstate = CallbackState}, ?TIMEOUT};
  104. {stop, Reason, Message} ->
  105. socket:send(Socket, [Message, "\r\n"]),
  106. socket:close(Socket),
  107. {stop, Reason};
  108. ignore ->
  109. socket:close(Socket),
  110. ignore
  111. end.
  112. %% @hidden
  113. -spec handle_call(Message :: any(), From :: {pid(), reference()}, #state{}) -> {'stop', 'normal', 'ok', #state{}} | {'reply', {'unknown_call', any()}, #state{}}.
  114. handle_call(stop, _From, State) ->
  115. {stop, normal, ok, State};
  116. handle_call(Request, _From, State) ->
  117. {reply, {unknown_call, Request}, State}.
  118. %% @hidden
  119. -spec handle_cast(Message :: any(), State :: #state{}) -> {'noreply', #state{}}.
  120. handle_cast(_Msg, State) ->
  121. {noreply, State}.
  122. %% @hidden
  123. -spec handle_info(Message :: any(), State :: #state{}) -> {'noreply', #state{}} | {'stop', any(), #state{}}.
  124. handle_info({receive_data, {error, size_exceeded}}, #state{socket = Socket, readmessage = true} = State) ->
  125. socket:send(Socket, "552 Message too large\r\n"),
  126. socket:active_once(Socket),
  127. {noreply, State#state{readmessage = false, envelope = #envelope{}}, ?TIMEOUT};
  128. handle_info({receive_data, {error, bare_newline}}, #state{socket = Socket, readmessage = true} = State) ->
  129. socket:send(Socket, "451 Bare newline detected\r\n"),
  130. io:format("bare newline detected: ~p~n", [self()]),
  131. socket:active_once(Socket),
  132. {noreply, State#state{readmessage = false, envelope = #envelope{}}, ?TIMEOUT};
  133. handle_info({receive_data, Body, Rest}, #state{socket = Socket, readmessage = true, envelope = Env, module=Module,
  134. callbackstate = OldCallbackState, extensions = Extensions} = State) ->
  135. % send the remainder of the data...
  136. case Rest of
  137. <<>> -> ok; % no remaining data
  138. _ -> self() ! {socket:get_proto(Socket), Socket, Rest}
  139. end,
  140. socket:setopts(Socket, [{packet, line}]),
  141. Envelope = Env#envelope{data = Body},% size = length(Body)},
  142. Valid = case has_extension(Extensions, "SIZE") of
  143. {true, Value} ->
  144. case byte_size(Envelope#envelope.data) > list_to_integer(Value) of
  145. true ->
  146. socket:send(Socket, "552 Message too large\r\n"),
  147. socket:active_once(Socket),
  148. false;
  149. false ->
  150. true
  151. end;
  152. false ->
  153. true
  154. end,
  155. case Valid of
  156. true ->
  157. case Module:handle_DATA(Envelope#envelope.from, Envelope#envelope.to, Envelope#envelope.data, OldCallbackState) of
  158. {ok, Reference, CallbackState} ->
  159. socket:send(Socket, io_lib:format("250 queued as ~s\r\n", [Reference])),
  160. socket:active_once(Socket),
  161. {noreply, State#state{readmessage = false, envelope = #envelope{}, callbackstate = CallbackState}, ?TIMEOUT};
  162. {error, Message, CallbackState} ->
  163. socket:send(Socket, [Message, "\r\n"]),
  164. socket:active_once(Socket),
  165. {noreply, State#state{readmessage = false, envelope = #envelope{}, callbackstate = CallbackState}, ?TIMEOUT}
  166. end;
  167. false ->
  168. % might not even be able to get here anymore...
  169. {noreply, State#state{readmessage = false, envelope = #envelope{}}, ?TIMEOUT}
  170. end;
  171. handle_info({_SocketType, Socket, Packet}, State) ->
  172. case handle_request(parse_request(Packet), State) of
  173. {ok, #state{extensions = Extensions, options = Options, readmessage = true} = NewState} ->
  174. MaxSize = case has_extension(Extensions, "SIZE") of
  175. {true, Value} ->
  176. list_to_integer(Value);
  177. false ->
  178. ?MAXIMUMSIZE
  179. end,
  180. Session = self(),
  181. Size = 0,
  182. socket:setopts(Socket, [{packet, raw}]),
  183. spawn_opt(fun() -> receive_data([],
  184. Socket, 0, Size, MaxSize, Session, Options) end,
  185. [link, {fullsweep_after, 0}]),
  186. {noreply, NewState, ?TIMEOUT};
  187. {ok, NewState} ->
  188. socket:active_once(NewState#state.socket),
  189. {noreply, NewState, ?TIMEOUT};
  190. {stop, Reason, NewState} ->
  191. {stop, Reason, NewState}
  192. end;
  193. handle_info({tcp_closed, _Socket}, State) ->
  194. {stop, normal, State};
  195. handle_info({ssl_closed, _Socket}, State) ->
  196. {stop, normal, State};
  197. handle_info(timeout, #state{socket = Socket} = State) ->
  198. socket:send(Socket, "421 Error: timeout exceeded\r\n"),
  199. socket:close(Socket),
  200. {stop, normal, State};
  201. handle_info(Info, State) ->
  202. io:format("unhandled info message ~p~n", [Info]),
  203. {noreply, State}.
  204. %% @hidden
  205. -spec(terminate/2 :: (Reason :: any(), State :: #state{}) -> 'ok').
  206. terminate(Reason, State) ->
  207. socket:close(State#state.socket),
  208. (State#state.module):terminate(Reason, State#state.callbackstate).
  209. %% @hidden
  210. -spec code_change(OldVsn :: any(), State :: #state{}, Extra :: any()) -> {'ok', #state{}}.
  211. code_change(OldVsn, #state{module = Module} = State, Extra) ->
  212. % TODO - this should probably be the callback module's version or its checksum
  213. CallbackState =
  214. case catch Module:code_change(OldVsn, State#state.callbackstate, Extra) of
  215. {ok, NewCallbackState} -> NewCallbackState;
  216. _ -> State#state.callbackstate
  217. end,
  218. {ok, State#state{callbackstate = CallbackState}}.
  219. -spec(parse_request/1 :: (Packet :: binary()) -> {binary(), binary()}).
  220. parse_request(Packet) ->
  221. Request = binstr:strip(binstr:strip(binstr:strip(binstr:strip(Packet, right, $\n), right, $\r), right, $\s), left, $\s),
  222. case binstr:strchr(Request, $\s) of
  223. 0 ->
  224. % io:format("got a ~s request~n", [Request]),
  225. case binstr:to_upper(Request) of
  226. <<"QUIT">> = Res -> {Res, <<>>};
  227. <<"DATA">> = Res -> {Res, <<>>};
  228. % likely a base64-encoded client reply
  229. _ -> {Request, <<>>}
  230. end;
  231. Index ->
  232. Verb = binstr:substr(Request, 1, Index - 1),
  233. Parameters = binstr:strip(binstr:substr(Request, Index + 1), left, $\s),
  234. %io:format("got a ~s request with parameters ~s~n", [Verb, Parameters]),
  235. {binstr:to_upper(Verb), Parameters}
  236. end.
  237. -spec(handle_request/2 :: ({Verb :: binary(), Args :: binary()}, State :: #state{}) -> {'ok', #state{}} | {'stop', any(), #state{}}).
  238. handle_request({<<>>, _Any}, #state{socket = Socket} = State) ->
  239. socket:send(Socket, "500 Error: bad syntax\r\n"),
  240. {ok, State};
  241. handle_request({<<"HELO">>, <<>>}, #state{socket = Socket} = State) ->
  242. socket:send(Socket, "501 Syntax: HELO hostname\r\n"),
  243. {ok, State};
  244. handle_request({<<"HELO">>, Hostname}, #state{socket = Socket, options = Options, module = Module, callbackstate = OldCallbackState} = State) ->
  245. case Module:handle_HELO(Hostname, OldCallbackState) of
  246. {ok, MaxSize, CallbackState} when is_integer(MaxSize) ->
  247. socket:send(Socket,["250 ", proplists:get_value(hostname, Options, smtp_util:guess_FQDN()), "\r\n"]),
  248. {ok, State#state{extensions = [{"SIZE", integer_to_list(MaxSize)}], envelope = #envelope{}, callbackstate = CallbackState}};
  249. {ok, CallbackState} ->
  250. socket:send(Socket, ["250 ", proplists:get_value(hostname, Options, smtp_util:guess_FQDN()), "\r\n"]),
  251. {ok, State#state{envelope = #envelope{}, callbackstate = CallbackState}};
  252. {error, Message, CallbackState} ->
  253. socket:send(Socket, [Message, "\r\n"]),
  254. {ok, State#state{callbackstate = CallbackState}}
  255. end;
  256. handle_request({<<"EHLO">>, <<>>}, #state{socket = Socket} = State) ->
  257. socket:send(Socket, "501 Syntax: EHLO hostname\r\n"),
  258. {ok, State};
  259. handle_request({<<"EHLO">>, Hostname}, #state{socket = Socket, options = Options, module = Module, callbackstate = OldCallbackState, tls = Tls} = State) ->
  260. case Module:handle_EHLO(Hostname, ?BUILTIN_EXTENSIONS, OldCallbackState) of
  261. {ok, Extensions, CallbackState} ->
  262. case Extensions of
  263. [] ->
  264. socket:send(Socket, ["250 ", proplists:get_value(hostname, Options, smtp_util:guess_FQDN()), "\r\n"]),
  265. {ok, State#state{extensions = Extensions, callbackstate = CallbackState}};
  266. _Else ->
  267. F =
  268. fun({E, true}, {Pos, Len, Acc}) when Pos =:= Len ->
  269. {Pos, Len, [["250 ", E, "\r\n"] | Acc]};
  270. ({E, Value}, {Pos, Len, Acc}) when Pos =:= Len ->
  271. {Pos, Len, [["250 ", E, " ", Value, "\r\n"] | Acc]};
  272. ({E, true}, {Pos, Len, Acc}) ->
  273. {Pos+1, Len, [["250-", E, "\r\n"] | Acc]};
  274. ({E, Value}, {Pos, Len, Acc}) ->
  275. {Pos+1, Len, [["250-", E, " ", Value , "\r\n"] | Acc]}
  276. end,
  277. Extensions2 = case Tls of
  278. true ->
  279. Extensions -- [{"STARTTLS", true}];
  280. false ->
  281. Extensions
  282. end,
  283. {_, _, Response} = lists:foldl(F, {1, length(Extensions2), [["250-", proplists:get_value(hostname, Options, smtp_util:guess_FQDN()), "\r\n"]]}, Extensions2),
  284. %?debugFmt("Respponse ~p~n", [lists:reverse(Response)]),
  285. socket:send(Socket, lists:reverse(Response)),
  286. {ok, State#state{extensions = Extensions2, envelope = #envelope{}, callbackstate = CallbackState}}
  287. end;
  288. {error, Message, CallbackState} ->
  289. socket:send(Socket, [Message, "\r\n"]),
  290. {ok, State#state{callbackstate = CallbackState}}
  291. end;
  292. handle_request({<<"AUTH">>, _Args}, #state{envelope = undefined, socket = Socket} = State) ->
  293. socket:send(Socket, "503 Error: send EHLO first\r\n"),
  294. {ok, State};
  295. handle_request({<<"AUTH">>, Args}, #state{socket = Socket, extensions = Extensions, envelope = Envelope, options = Options} = State) ->
  296. case binstr:strchr(Args, $\s) of
  297. 0 ->
  298. AuthType = Args,
  299. Parameters = false;
  300. Index ->
  301. AuthType = binstr:substr(Args, 1, Index - 1),
  302. Parameters = binstr:strip(binstr:substr(Args, Index + 1), left, $\s)
  303. end,
  304. case has_extension(Extensions, "AUTH") of
  305. false ->
  306. socket:send(Socket, "502 Error: AUTH not implemented\r\n"),
  307. {ok, State};
  308. {true, AvailableTypes} ->
  309. case lists:member(string:to_upper(binary_to_list(AuthType)), string:tokens(AvailableTypes, " ")) of
  310. false ->
  311. socket:send(Socket, "504 Unrecognized authentication type\r\n"),
  312. {ok, State};
  313. true ->
  314. case binstr:to_upper(AuthType) of
  315. <<"LOGIN">> ->
  316. % socket:send(Socket, "334 " ++ base64:encode_to_string("Username:")),
  317. socket:send(Socket, "334 VXNlcm5hbWU6\r\n"),
  318. {ok, State#state{waitingauth = 'login', envelope = Envelope#envelope{auth = {<<>>, <<>>}}}};
  319. <<"PLAIN">> when Parameters =/= false ->
  320. % TODO - duplicated below in handle_request waitingauth PLAIN
  321. case binstr:split(base64:decode(Parameters), <<0>>) of
  322. [_Identity, Username, Password] ->
  323. try_auth('plain', Username, Password, State);
  324. [Username, Password] ->
  325. try_auth('plain', Username, Password, State);
  326. _ ->
  327. % TODO error
  328. {ok, State}
  329. end;
  330. <<"PLAIN">> ->
  331. socket:send(Socket, "334\r\n"),
  332. {ok, State#state{waitingauth = 'plain', envelope = Envelope#envelope{auth = {<<>>, <<>>}}}};
  333. <<"CRAM-MD5">> ->
  334. crypto:start(), % ensure crypto is started, we're gonna need it
  335. String = smtp_util:get_cram_string(proplists:get_value(hostname, Options, smtp_util:guess_FQDN())),
  336. socket:send(Socket, ["334 ", String, "\r\n"]),
  337. {ok, State#state{waitingauth = 'cram-md5', authdata=base64:decode(String), envelope = Envelope#envelope{auth = {<<>>, <<>>}}}}
  338. %"DIGEST-MD5" -> % TODO finish this? (see rfc 2831)
  339. %crypto:start(), % ensure crypto is started, we're gonna need it
  340. %Nonce = get_digest_nonce(),
  341. %Response = io_lib:format("nonce=\"~s\",realm=\"~s\",qop=\"auth\",algorithm=md5-sess,charset=utf-8", Nonce, State#state.hostname),
  342. %socket:send(Socket, "334 "++Response++"\r\n"),
  343. %{ok, State#state{waitingauth = "DIGEST-MD5", authdata=base64:decode_to_string(Nonce), envelope = Envelope#envelope{auth = {[], []}}}}
  344. end
  345. end
  346. end;
  347. % the client sends a response to auth-cram-md5
  348. handle_request({Username64, <<>>}, #state{waitingauth = 'cram-md5', envelope = #envelope{auth = {<<>>, <<>>}}, authdata = AuthData} = State) ->
  349. case binstr:split(base64:decode(Username64), <<" ">>) of
  350. [Username, Digest] ->
  351. try_auth('cram-md5', Username, {Digest, AuthData}, State#state{authdata=undefined});
  352. _ ->
  353. % TODO error
  354. {ok, State#state{waitingauth=false, authdata=undefined}}
  355. end;
  356. % the client sends a \0username\0password response to auth-plain
  357. handle_request({Username64, <<>>}, #state{waitingauth = 'plain', envelope = #envelope{auth = {<<>>,<<>>}}} = State) ->
  358. case binstr:split(base64:decode(Username64), <<0>>) of
  359. [_Identity, Username, Password] ->
  360. try_auth('plain', Username, Password, State);
  361. [Username, Password] ->
  362. try_auth('plain', Username, Password, State);
  363. _ ->
  364. % TODO error
  365. {ok, State#state{waitingauth=false}}
  366. end;
  367. % the client sends a username response to auth-login
  368. handle_request({Username64, <<>>}, #state{socket = Socket, waitingauth = 'login', envelope = #envelope{auth = {<<>>,<<>>}}} = State) ->
  369. Envelope = State#state.envelope,
  370. Username = base64:decode(Username64),
  371. % socket:send(Socket, "334 " ++ base64:encode_to_string("Password:")),
  372. socket:send(Socket, "334 UGFzc3dvcmQ6\r\n"),
  373. % store the provided username in envelope.auth
  374. NewState = State#state{envelope = Envelope#envelope{auth = {Username, <<>>}}},
  375. {ok, NewState};
  376. % the client sends a password response to auth-login
  377. handle_request({Password64, <<>>}, #state{waitingauth = 'login', envelope = #envelope{auth = {Username,<<>>}}} = State) ->
  378. Password = base64:decode(Password64),
  379. try_auth('login', Username, Password, State);
  380. handle_request({<<"MAIL">>, _Args}, #state{envelope = undefined, socket = Socket} = State) ->
  381. socket:send(Socket, "503 Error: send HELO/EHLO first\r\n"),
  382. {ok, State};
  383. handle_request({<<"MAIL">>, Args}, #state{socket = Socket, module = Module, envelope = Envelope, callbackstate = OldCallbackState, extensions = Extensions} = State) ->
  384. case Envelope#envelope.from of
  385. undefined ->
  386. case binstr:strpos(binstr:to_upper(Args), "FROM:") of
  387. 1 ->
  388. Address = binstr:strip(binstr:substr(Args, 6), left, $\s),
  389. case parse_encoded_address(Address) of
  390. error ->
  391. socket:send(Socket, "501 Bad sender address syntax\r\n"),
  392. {ok, State};
  393. {ParsedAddress, <<>>} ->
  394. %io:format("From address ~s (parsed as ~s)~n", [Address, ParsedAddress]),
  395. case Module:handle_MAIL(ParsedAddress, OldCallbackState) of
  396. {ok, CallbackState} ->
  397. socket:send(Socket, "250 sender Ok\r\n"),
  398. {ok, State#state{envelope = Envelope#envelope{from = ParsedAddress}, callbackstate = CallbackState}};
  399. {error, Message, CallbackState} ->
  400. socket:send(Socket, [Message, "\r\n"]),
  401. {ok, State#state{callbackstate = CallbackState}}
  402. end;
  403. {ParsedAddress, ExtraInfo} ->
  404. %io:format("From address ~s (parsed as ~s) with extra info ~s~n", [Address, ParsedAddress, ExtraInfo]),
  405. Options = [binstr:to_upper(X) || X <- binstr:split(ExtraInfo, <<" ">>)],
  406. %io:format("options are ~p~n", [Options]),
  407. F = fun(_, {error, Message}) ->
  408. {error, Message};
  409. (<<"SIZE=", Size/binary>>, InnerState) ->
  410. case has_extension(Extensions, "SIZE") of
  411. {true, Value} ->
  412. case list_to_integer(binary_to_list(Size)) > list_to_integer(Value) of
  413. true ->
  414. {error, ["552 Estimated message length ", Size, " exceeds limit of ", Value, "\r\n"]};
  415. false ->
  416. InnerState#state{envelope = Envelope#envelope{expectedsize = list_to_integer(binary_to_list(Size))}}
  417. end;
  418. false ->
  419. {error, "555 Unsupported option SIZE\r\n"}
  420. end;
  421. (<<"BODY=", _BodyType/binary>>, InnerState) ->
  422. case has_extension(Extensions, "8BITMIME") of
  423. {true, _} ->
  424. InnerState;
  425. false ->
  426. {error, "555 Unsupported option BODY\r\n"}
  427. end;
  428. (X, InnerState) ->
  429. case Module:handle_MAIL_extension(X, OldCallbackState) of
  430. {ok, CallbackState} ->
  431. InnerState#state{callbackstate = CallbackState};
  432. error ->
  433. {error, ["555 Unsupported option: ", ExtraInfo, "\r\n"]}
  434. end
  435. end,
  436. case lists:foldl(F, State, Options) of
  437. {error, Message} ->
  438. %io:format("error: ~s~n", [Message]),
  439. socket:send(Socket, Message),
  440. {ok, State};
  441. NewState ->
  442. %io:format("OK~n"),
  443. case Module:handle_MAIL(ParsedAddress, State#state.callbackstate) of
  444. {ok, CallbackState} ->
  445. socket:send(Socket, "250 sender Ok\r\n"),
  446. {ok, State#state{envelope = Envelope#envelope{from = ParsedAddress}, callbackstate = CallbackState}};
  447. {error, Message, CallbackState} ->
  448. socket:send(Socket, [Message, "\r\n"]),
  449. {ok, NewState#state{callbackstate = CallbackState}}
  450. end
  451. end
  452. end;
  453. _Else ->
  454. socket:send(Socket, "501 Syntax: MAIL FROM:<address>\r\n"),
  455. {ok, State}
  456. end;
  457. _Other ->
  458. socket:send(Socket, "503 Error: Nested MAIL command\r\n"),
  459. {ok, State}
  460. end;
  461. handle_request({<<"RCPT">>, _Args}, #state{envelope = undefined, socket = Socket} = State) ->
  462. socket:send(Socket, "503 Error: need MAIL command\r\n"),
  463. {ok, State};
  464. handle_request({<<"RCPT">>, Args}, #state{socket = Socket, envelope = Envelope, module = Module, callbackstate = OldCallbackState} = State) ->
  465. case binstr:strpos(binstr:to_upper(Args), "TO:") of
  466. 1 ->
  467. Address = binstr:strip(binstr:substr(Args, 4), left, $\s),
  468. case parse_encoded_address(Address) of
  469. error ->
  470. socket:send(Socket, "501 Bad recipient address syntax\r\n"),
  471. {ok, State};
  472. {<<>>, _} ->
  473. % empty rcpt to addresses aren't cool
  474. socket:send(Socket, "501 Bad recipient address syntax\r\n"),
  475. {ok, State};
  476. {ParsedAddress, <<>>} ->
  477. %io:format("To address ~s (parsed as ~s)~n", [Address, ParsedAddress]),
  478. case Module:handle_RCPT(ParsedAddress, OldCallbackState) of
  479. {ok, CallbackState} ->
  480. socket:send(Socket, "250 recipient Ok\r\n"),
  481. {ok, State#state{envelope = Envelope#envelope{to = Envelope#envelope.to ++ [ParsedAddress]}, callbackstate = CallbackState}};
  482. {error, Message, CallbackState} ->
  483. socket:send(Socket, [Message, "\r\n"]),
  484. {ok, State#state{callbackstate = CallbackState}}
  485. end;
  486. {ParsedAddress, ExtraInfo} ->
  487. % TODO - are there even any RCPT extensions?
  488. io:format("To address ~s (parsed as ~s) with extra info ~s~n", [Address, ParsedAddress, ExtraInfo]),
  489. socket:send(Socket, ["555 Unsupported option: ", ExtraInfo, "\r\n"]),
  490. {ok, State}
  491. end;
  492. _Else ->
  493. socket:send(Socket, "501 Syntax: RCPT TO:<address>\r\n"),
  494. {ok, State}
  495. end;
  496. handle_request({<<"DATA">>, <<>>}, #state{socket = Socket, envelope = undefined} = State) ->
  497. socket:send(Socket, "503 Error: send HELO/EHLO first\r\n"),
  498. {ok, State};
  499. handle_request({<<"DATA">>, <<>>}, #state{socket = Socket, envelope = Envelope} = State) ->
  500. case {Envelope#envelope.from, Envelope#envelope.to} of
  501. {undefined, _} ->
  502. socket:send(Socket, "503 Error: need MAIL command\r\n"),
  503. {ok, State};
  504. {_, []} ->
  505. socket:send(Socket, "503 Error: need RCPT command\r\n"),
  506. {ok, State};
  507. _Else ->
  508. socket:send(Socket, "354 enter mail, end with line containing only '.'\r\n"),
  509. %io:format("switching to data read mode~n", []),
  510. {ok, State#state{readmessage = true}}
  511. end;
  512. handle_request({<<"RSET">>, _Any}, #state{socket = Socket, envelope = Envelope, module = Module, callbackstate = OldCallbackState} = State) ->
  513. socket:send(Socket, "250 Ok\r\n"),
  514. % if the client sends a RSET before a HELO/EHLO don't give them a valid envelope
  515. NewEnvelope = case Envelope of
  516. undefined -> undefined;
  517. _Something -> #envelope{}
  518. end,
  519. {ok, State#state{envelope = NewEnvelope, callbackstate = Module:handle_RSET(OldCallbackState)}};
  520. handle_request({<<"NOOP">>, _Any}, #state{socket = Socket} = State) ->
  521. socket:send(Socket, "250 Ok\r\n"),
  522. {ok, State};
  523. handle_request({<<"QUIT">>, _Any}, #state{socket = Socket} = State) ->
  524. socket:send(Socket, "221 Bye\r\n"),
  525. {stop, normal, State};
  526. handle_request({<<"VRFY">>, Address}, #state{module= Module, socket = Socket, callbackstate = OldCallbackState} = State) ->
  527. case parse_encoded_address(Address) of
  528. {ParsedAddress, <<>>} ->
  529. case Module:handle_VRFY(ParsedAddress, OldCallbackState) of
  530. {ok, Reply, CallbackState} ->
  531. socket:send(Socket, ["250 ", Reply, "\r\n"]),
  532. {ok, State#state{callbackstate = CallbackState}};
  533. {error, Message, CallbackState} ->
  534. socket:send(Socket, [Message, "\r\n"]),
  535. {ok, State#state{callbackstate = CallbackState}}
  536. end;
  537. _Other ->
  538. socket:send(Socket, "501 Syntax: VRFY username/address\r\n"),
  539. {ok, State}
  540. end;
  541. handle_request({<<"STARTTLS">>, <<>>}, #state{socket = Socket, tls=false, extensions = Extensions, options = Options} = State) ->
  542. case has_extension(Extensions, "STARTTLS") of
  543. {true, _} ->
  544. socket:send(Socket, "220 OK\r\n"),
  545. crypto:start(),
  546. application:start(public_key),
  547. application:start(ssl),
  548. Options1 = case proplists:get_value(certfile, Options) of
  549. undefined ->
  550. [];
  551. CertFile ->
  552. [{certfile, CertFile}]
  553. end,
  554. Options2 = case proplists:get_value(keyfile, Options) of
  555. undefined ->
  556. Options1;
  557. KeyFile ->
  558. [{keyfile, KeyFile} | Options1]
  559. end,
  560. % TODO: certfile and keyfile should be at configurable locations
  561. case socket:to_ssl_server(Socket, Options2, 5000) of
  562. {ok, NewSocket} ->
  563. %io:format("SSL negotiation sucessful~n"),
  564. {ok, State#state{socket = NewSocket, envelope=undefined,
  565. authdata=undefined, waitingauth=false, readmessage=false,
  566. tls=true}};
  567. {error, Reason} ->
  568. io:format("SSL handshake failed : ~p~n", [Reason]),
  569. socket:send(Socket, "454 TLS negotiation failed\r\n"),
  570. {ok, State}
  571. end;
  572. false ->
  573. socket:send(Socket, "500 Command unrecognized\r\n"),
  574. {ok, State}
  575. end;
  576. handle_request({<<"STARTTLS">>, <<>>}, #state{socket = Socket} = State) ->
  577. socket:send(Socket, "500 TLS already negotiated\r\n"),
  578. {ok, State};
  579. handle_request({<<"STARTTLS">>, _Args}, #state{socket = Socket} = State) ->
  580. socket:send(Socket, "501 Syntax error (no parameters allowed)\r\n"),
  581. {ok, State};
  582. handle_request({Verb, Args}, #state{socket = Socket, module = Module, callbackstate = OldCallbackState} = State) ->
  583. {Message, CallbackState} = Module:handle_other(Verb, Args, OldCallbackState),
  584. socket:send(Socket, [Message, "\r\n"]),
  585. {ok, State#state{callbackstate = CallbackState}}.
  586. -spec(parse_encoded_address/1 :: (Address :: binary()) -> {binary(), binary()} | 'error').
  587. parse_encoded_address(<<>>) ->
  588. error; % empty
  589. parse_encoded_address(<<"<@", Address/binary>>) ->
  590. case binstr:strchr(Address, $:) of
  591. 0 ->
  592. error; % invalid address
  593. Index ->
  594. parse_encoded_address(binstr:substr(Address, Index + 1), [], {false, true})
  595. end;
  596. parse_encoded_address(<<"<", Address/binary>>) ->
  597. parse_encoded_address(Address, [], {false, true});
  598. parse_encoded_address(<<" ", Address/binary>>) ->
  599. parse_encoded_address(Address);
  600. parse_encoded_address(Address) ->
  601. parse_encoded_address(Address, [], {false, false}).
  602. -spec(parse_encoded_address/3 :: (Address :: binary(), Acc :: list(), Flags :: {boolean(), boolean()}) -> {binary(), binary()} | 'error').
  603. parse_encoded_address(<<>>, Acc, {_Quotes, false}) ->
  604. {list_to_binary(lists:reverse(Acc)), <<>>};
  605. parse_encoded_address(<<>>, _Acc, {_Quotes, true}) ->
  606. error; % began with angle brackets but didn't end with them
  607. parse_encoded_address(_, Acc, _) when length(Acc) > 129 ->
  608. error; % too long
  609. parse_encoded_address(<<"\\", Tail/binary>>, Acc, Flags) ->
  610. <<H, NewTail/binary>> = Tail,
  611. parse_encoded_address(NewTail, [H | Acc], Flags);
  612. parse_encoded_address(<<"\"", Tail/binary>>, Acc, {false, AB}) ->
  613. parse_encoded_address(Tail, Acc, {true, AB});
  614. parse_encoded_address(<<"\"", Tail/binary>>, Acc, {true, AB}) ->
  615. parse_encoded_address(Tail, Acc, {false, AB});
  616. parse_encoded_address(<<">", Tail/binary>>, Acc, {false, true}) ->
  617. {list_to_binary(lists:reverse(Acc)), binstr:strip(Tail, left, $\s)};
  618. parse_encoded_address(<<">", _Tail/binary>>, _Acc, {false, false}) ->
  619. error; % ended with angle brackets but didn't begin with them
  620. parse_encoded_address(<<" ", Tail/binary>>, Acc, {false, false}) ->
  621. {list_to_binary(lists:reverse(Acc)), binstr:strip(Tail, left, $\s)};
  622. parse_encoded_address(<<" ", _Tail/binary>>, _Acc, {false, true}) ->
  623. error; % began with angle brackets but didn't end with them
  624. parse_encoded_address(<<H, Tail/binary>>, Acc, {false, AB}) when H >= $0, H =< $9 ->
  625. parse_encoded_address(Tail, [H | Acc], {false, AB}); % digits
  626. parse_encoded_address(<<H, Tail/binary>>, Acc, {false, AB}) when H >= $@, H =< $Z ->
  627. parse_encoded_address(Tail, [H | Acc], {false, AB}); % @ symbol and uppercase letters
  628. parse_encoded_address(<<H, Tail/binary>>, Acc, {false, AB}) when H >= $a, H =< $z ->
  629. parse_encoded_address(Tail, [H | Acc], {false, AB}); % lowercase letters
  630. parse_encoded_address(<<H, Tail/binary>>, Acc, {false, AB}) when H =:= $-; H =:= $.; H =:= $_ ->
  631. parse_encoded_address(Tail, [H | Acc], {false, AB}); % dash, dot, underscore
  632. % Allowed characters in the local name: ! # $ % & ' * + - / = ? ^ _ ` . { | } ~
  633. parse_encoded_address(<<H, Tail/binary>>, Acc, {false, AB}) when H =:= $+;
  634. H =:= $!; H =:= $#; H =:= $$; H =:= $%; H =:= $&; H =:= $'; H =:= $*; H =:= $=;
  635. H =:= $/; H =:= $?; H =:= $^; H =:= $`; H =:= ${; H =:= $|; H =:= $}; H =:= $~ ->
  636. parse_encoded_address(Tail, [H | Acc], {false, AB}); % other characters
  637. parse_encoded_address(_, _Acc, {false, _AB}) ->
  638. error;
  639. parse_encoded_address(<<H, Tail/binary>>, Acc, Quotes) ->
  640. parse_encoded_address(Tail, [H | Acc], Quotes).
  641. -spec(has_extension/2 :: (Extensions :: [{string(), string()}], Extension :: string()) -> {'true', string()} | 'false').
  642. has_extension(Exts, Ext) ->
  643. Extension = string:to_upper(Ext),
  644. Extensions = [{string:to_upper(X), Y} || {X, Y} <- Exts],
  645. %io:format("extensions ~p~n", [Extensions]),
  646. case proplists:get_value(Extension, Extensions) of
  647. undefined ->
  648. false;
  649. Value ->
  650. {true, Value}
  651. end.
  652. -spec(try_auth/4 :: (AuthType :: 'login' | 'plain' | 'cram-md5', Username :: binary(), Credential :: binary() | {binary(), binary()}, State :: #state{}) -> {'ok', #state{}}).
  653. try_auth(AuthType, Username, Credential, #state{module = Module, socket = Socket, envelope = Envelope, callbackstate = OldCallbackState} = State) ->
  654. % clear out waiting auth
  655. NewState = State#state{waitingauth = false, envelope = Envelope#envelope{auth = {<<>>, <<>>}}},
  656. case erlang:function_exported(Module, handle_AUTH, 4) of
  657. true ->
  658. case Module:handle_AUTH(AuthType, Username, Credential, OldCallbackState) of
  659. {ok, CallbackState} ->
  660. socket:send(Socket, "235 Authentication successful.\r\n"),
  661. {ok, NewState#state{callbackstate = CallbackState,
  662. envelope = Envelope#envelope{auth = {Username, Credential}}}};
  663. _Other ->
  664. socket:send(Socket, "535 Authentication failed.\r\n"),
  665. {ok, NewState}
  666. end;
  667. false ->
  668. io:format("Please define handle_AUTH/4 in your server module or remove AUTH from your module extensions~n"),
  669. socket:send(Socket, "535 authentication failed (#5.7.1)\r\n"),
  670. {ok, NewState}
  671. end.
  672. %get_digest_nonce() ->
  673. %A = [io_lib:format("~2.16.0b", [X]) || <<X>> <= erlang:md5(integer_to_list(crypto:rand_uniform(0, 4294967295)))],
  674. %B = [io_lib:format("~2.16.0b", [X]) || <<X>> <= erlang:md5(integer_to_list(crypto:rand_uniform(0, 4294967295)))],
  675. %binary_to_list(base64:encode(lists:flatten(A ++ B))).
  676. %% @doc a tight loop to receive the message body
  677. receive_data(_Acc, _Socket, _, Size, MaxSize, Session, _Options) when MaxSize > 0, Size > MaxSize ->
  678. io:format("message body size ~B exceeded maximum allowed ~B~n", [Size, MaxSize]),
  679. Session ! {receive_data, {error, size_exceeded}};
  680. receive_data(Acc, Socket, RecvSize, Size, MaxSize, Session, Options) ->
  681. case socket:recv(Socket, RecvSize, 1000) of
  682. {ok, Packet} when Acc == [] ->
  683. case check_bare_crlf(Packet, <<>>, proplists:get_value(allow_bare_newlines, Options, false), 0) of
  684. error ->
  685. Session ! {receive_data, {error, bare_newline}};
  686. FixedPacket ->
  687. case binstr:strpos(FixedPacket, "\r\n.\r\n") of
  688. 0 ->
  689. %io:format("received ~B bytes; size is now ~p~n", [RecvSize, Size + size(Packet)]),
  690. %io:format("memory usage: ~p~n", [erlang:process_info(self(), memory)]),
  691. receive_data([FixedPacket | Acc], Socket, RecvSize, Size + byte_size(FixedPacket), MaxSize, Session, Options);
  692. Index ->
  693. String = binstr:substr(FixedPacket, 1, Index - 1),
  694. Rest = binstr:substr(FixedPacket, Index+5),
  695. %io:format("memory usage before flattening: ~p~n", [erlang:process_info(self(), memory)]),
  696. Result = list_to_binary(lists:reverse([String | Acc])),
  697. %io:format("memory usage after flattening: ~p~n", [erlang:process_info(self(), memory)]),
  698. Session ! {receive_data, Result, Rest}
  699. end
  700. end;
  701. {ok, Packet} ->
  702. [Last | _] = Acc,
  703. case check_bare_crlf(Packet, Last, proplists:get_value(allow_bare_newlines, Options, false), 0) of
  704. error ->
  705. Session ! {receive_data, {error, bare_newline}};
  706. FixedPacket ->
  707. case binstr:strpos(FixedPacket, "\r\n.\r\n") of
  708. 0 ->
  709. %io:format("received ~B bytes; size is now ~p~n", [RecvSize, Size + size(Packet)]),
  710. %io:format("memory usage: ~p~n", [erlang:process_info(self(), memory)]),
  711. receive_data([FixedPacket | Acc], Socket, RecvSize, Size + byte_size(FixedPacket), MaxSize, Session, Options);
  712. Index ->
  713. String = binstr:substr(FixedPacket, 1, Index - 1),
  714. Rest = binstr:substr(FixedPacket, Index+5),
  715. %io:format("memory usage before flattening: ~p~n", [erlang:process_info(self(), memory)]),
  716. Result = list_to_binary(lists:reverse([String | Acc])),
  717. %io:format("memory usage after flattening: ~p~n", [erlang:process_info(self(), memory)]),
  718. Session ! {receive_data, Result, Rest}
  719. end
  720. end;
  721. {error, timeout} when RecvSize =:= 0, length(Acc) > 1 ->
  722. % check that we didn't accidentally receive a \r\n.\r\n split across 2 receives
  723. [A, B | Acc2] = Acc,
  724. Packet = list_to_binary([B, A]),
  725. case binstr:strpos(Packet, "\r\n.\r\n") of
  726. 0 ->
  727. % uh-oh
  728. %io:format("no data on socket, and no DATA terminator, retrying ~p~n", [Session]),
  729. % eventually we'll either get data or a different error, just keep retrying
  730. receive_data(Acc, Socket, 0, Size, MaxSize, Session, Options);
  731. Index ->
  732. String = binstr:substr(Packet, 1, Index - 1),
  733. Rest = binstr:substr(Packet, Index+5),
  734. %io:format("memory usage before flattening: ~p~n", [erlang:process_info(self(), memory)]),
  735. Result = list_to_binary(lists:reverse([String | Acc2])),
  736. %io:format("memory usage after flattening: ~p~n", [erlang:process_info(self(), memory)]),
  737. Session ! {receive_data, Result, Rest}
  738. end;
  739. {error, timeout} ->
  740. receive_data(Acc, Socket, 0, Size, MaxSize, Session, Options);
  741. {error, Reason} ->
  742. io:format("receive error: ~p~n", [Reason]),
  743. exit(receive_error)
  744. end.
  745. check_for_bare_crlf(Bin, Offset) ->
  746. case {re:run(Bin, "(?<!\r)\n", [{capture, none}, {offset, Offset}]), re:run(Bin, "\r(?!\n)", [{capture, none}, {offset, Offset}])} of
  747. {match, _} -> true;
  748. {_, match} -> true;
  749. _ -> false
  750. end.
  751. fix_bare_crlf(Bin, Offset) ->
  752. Options = [{offset, Offset}, {return, binary}, global],
  753. re:replace(re:replace(Bin, "(?<!\r)\n", "\r\n", Options), "\r(?!\n)", "\r\n", Options).
  754. strip_bare_crlf(Bin, Offset) ->
  755. Options = [{offset, Offset}, {return, binary}, global],
  756. re:replace(re:replace(Bin, "(?<!\r)\n", "", Options), "\r(?!\n)", "", Options).
  757. check_bare_crlf(Binary, _, ignore, _) ->
  758. Binary;
  759. check_bare_crlf(<<$\n, _Rest/binary>> = Bin, Prev, Op, Offset) when byte_size(Prev) > 0, Offset == 0 ->
  760. % check if last character of previous was a CR
  761. Lastchar = binstr:substr(Prev, -1),
  762. case Lastchar of
  763. <<"\r">> ->
  764. % okay, check again for the rest
  765. check_bare_crlf(Bin, <<>>, Op, 1);
  766. _ when Op == false -> % not fixing or ignoring them
  767. error;
  768. _ ->
  769. % no dice
  770. check_bare_crlf(Bin, <<>>, Op, 0)
  771. end;
  772. check_bare_crlf(Binary, _Prev, Op, Offset) ->
  773. Last = binstr:substr(Binary, -1),
  774. % is the last character a CR?
  775. case Last of
  776. <<"\r">> ->
  777. % okay, the last character is a CR, we have to assume the next packet contains the corresponding LF
  778. NewBin = binstr:substr(Binary, 1, byte_size(Binary) -1),
  779. case check_for_bare_crlf(NewBin, Offset) of
  780. true when Op == fix ->
  781. list_to_binary([fix_bare_crlf(NewBin, Offset), "\r"]);
  782. true when Op == strip ->
  783. list_to_binary([strip_bare_crlf(NewBin, Offset), "\r"]);
  784. true ->
  785. error;
  786. false ->
  787. Binary
  788. end;
  789. _ ->
  790. case check_for_bare_crlf(Binary, Offset) of
  791. true when Op == fix ->
  792. fix_bare_crlf(Binary, Offset);
  793. true when Op == strip ->
  794. strip_bare_crlf(Binary, Offset);
  795. true ->
  796. error;
  797. false ->
  798. Binary
  799. end
  800. end.
  801. -ifdef(TEST).
  802. parse_encoded_address_test_() ->
  803. [
  804. {"Valid addresses should parse",
  805. fun() ->
  806. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<God@heaven.af.mil>">>)),
  807. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<\\God@heaven.af.mil>">>)),
  808. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<\"God\"@heaven.af.mil>">>)),
  809. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<@gateway.af.mil,@uucp.local:\"\\G\\o\\d\"@heaven.af.mil>">>)),
  810. ?assertEqual({<<"God2@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<God2@heaven.af.mil>">>)),
  811. ?assertEqual({<<"God+extension@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<God+extension@heaven.af.mil>">>)),
  812. ?assertEqual({<<"God~*$@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"<God~*$@heaven.af.mil>">>))
  813. end
  814. },
  815. {"Addresses that are sorta valid should parse",
  816. fun() ->
  817. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"God@heaven.af.mil">>)),
  818. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<"God@heaven.af.mil ">>)),
  819. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<" God@heaven.af.mil ">>)),
  820. ?assertEqual({<<"God@heaven.af.mil">>, <<>>}, parse_encoded_address(<<" <God@heaven.af.mil> ">>))
  821. end
  822. },
  823. {"Addresses containing unescaped <> that aren't at start/end should fail",
  824. fun() ->
  825. ?assertEqual(error, parse_encoded_address(<<"<<">>)),
  826. ?assertEqual(error, parse_encoded_address(<<"<God<@heaven.af.mil>">>))
  827. end
  828. },
  829. {"Address that begins with < but doesn't end with a > should fail",
  830. fun() ->
  831. ?assertEqual(error, parse_encoded_address(<<"<God@heaven.af.mil">>)),
  832. ?assertEqual(error, parse_encoded_address(<<"<God@heaven.af.mil ">>))
  833. end
  834. },
  835. {"Address that begins without < but ends with a > should fail",
  836. fun() ->
  837. ?assertEqual(error, parse_encoded_address(<<"God@heaven.af.mil>">>))
  838. end
  839. },
  840. {"Address longer than 129 character should fail",
  841. fun() ->
  842. MegaAddress = list_to_binary(lists:seq(97, 122) ++ lists:seq(97, 122) ++ lists:seq(97, 122) ++ "@" ++ lists:seq(97, 122) ++ lists:seq(97, 122)),
  843. ?assertEqual(error, parse_encoded_address(MegaAddress))
  844. end
  845. },
  846. {"Address with an invalid route should fail",
  847. fun() ->
  848. ?assertEqual(error, parse_encoded_address(<<"<@gateway.af.mil God@heaven.af.mil>">>))
  849. end
  850. },
  851. {"Empty addresses should parse OK",
  852. fun() ->
  853. ?assertEqual({<<>>, <<>>}, parse_encoded_address(<<"<>">>)),
  854. ?assertEqual({<<>>, <<>>}, parse_encoded_address(<<" <> ">>))
  855. end
  856. },
  857. {"Completely empty addresses are an error",
  858. fun() ->
  859. ?assertEqual(error, parse_encoded_address(<<"">>)),
  860. ?assertEqual(error, parse_encoded_address(<<" ">>))
  861. end
  862. },
  863. {"addresses with trailing parameters should return the trailing parameters",
  864. fun() ->
  865. ?assertEqual({<<"God@heaven.af.mil">>, <<"SIZE=100 BODY=8BITMIME">>}, parse_encoded_address(<<"<God@heaven.af.mil> SIZE=100 BODY=8BITMIME">>))
  866. end
  867. }
  868. ].
  869. parse_request_test_() ->
  870. [
  871. {"Parsing normal SMTP requests",
  872. fun() ->
  873. ?assertEqual({<<"HELO">>, <<>>}, parse_request(<<"HELO\r\n">>)),
  874. ?assertEqual({<<"EHLO">>, <<"hell.af.mil">>}, parse_request(<<"EHLO hell.af.mil\r\n">>)),
  875. ?assertEqual({<<"MAIL">>, <<"FROM:God@heaven.af.mil">>}, parse_request(<<"MAIL FROM:God@heaven.af.mil">>))
  876. end
  877. },
  878. {"Verbs should be uppercased",
  879. fun() ->
  880. ?assertEqual({<<"HELO">>, <<"hell.af.mil">>}, parse_request(<<"helo hell.af.mil">>))
  881. end
  882. },
  883. {"Leading and trailing spaces are removed",
  884. fun() ->
  885. ?assertEqual({<<"HELO">>, <<"hell.af.mil">>}, parse_request(<<" helo hell.af.mil ">>))
  886. end
  887. },
  888. {"Blank lines are blank",
  889. fun() ->
  890. ?assertEqual({<<>>, <<>>}, parse_request(<<"">>))
  891. end
  892. }
  893. ].
  894. smtp_session_test_() ->
  895. {foreach,
  896. local,
  897. fun() ->
  898. Self = self(),
  899. spawn(fun() ->
  900. {ok, ListenSock} = socket:listen(tcp, 9876, [binary]),
  901. {ok, X} = socket:accept(ListenSock),
  902. socket:controlling_process(X, Self),
  903. Self ! X
  904. end),
  905. {ok, CSock} = socket:connect(tcp, "localhost", 9876),
  906. receive
  907. SSock when is_port(SSock) ->
  908. ok
  909. end,
  910. {ok, Pid} = gen_smtp_server_session:start(SSock, smtp_server_example, [{hostname, "localhost"}, {sessioncount, 1}]),
  911. socket:controlling_process(SSock, Pid),
  912. {CSock, Pid}
  913. end,
  914. fun({CSock, _Pid}) ->
  915. socket:close(CSock)
  916. end,
  917. [fun({CSock, _Pid}) ->
  918. {"A new connection should get a banner",
  919. fun() ->
  920. socket:active_once(CSock),
  921. receive {tcp, CSock, Packet} -> ok end,
  922. ?assertMatch("220 localhost"++_Stuff, Packet)
  923. end
  924. }
  925. end,
  926. fun({CSock, _Pid}) ->
  927. {"A correct response to HELO",
  928. fun() ->
  929. socket:active_once(CSock),
  930. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  931. ?assertMatch("220 localhost"++_Stuff, Packet),
  932. socket:send(CSock, "HELO somehost.com\r\n"),
  933. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  934. ?assertMatch("250 localhost\r\n", Packet2)
  935. end
  936. }
  937. end,
  938. fun({CSock, _Pid}) ->
  939. {"An error in response to an invalid HELO",
  940. fun() ->
  941. socket:active_once(CSock),
  942. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  943. ?assertMatch("220 localhost"++_Stuff, Packet),
  944. socket:send(CSock, "HELO\r\n"),
  945. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  946. ?assertMatch("501 Syntax: HELO hostname\r\n", Packet2)
  947. end
  948. }
  949. end,
  950. fun({CSock, _Pid}) ->
  951. {"A rejected HELO",
  952. fun() ->
  953. socket:active_once(CSock),
  954. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  955. ?assertMatch("220 localhost"++_Stuff, Packet),
  956. socket:send(CSock, "HELO invalid\r\n"),
  957. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  958. ?assertMatch("554 invalid hostname\r\n", Packet2)
  959. end
  960. }
  961. end,
  962. fun({CSock, _Pid}) ->
  963. {"A rejected EHLO",
  964. fun() ->
  965. socket:active_once(CSock),
  966. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  967. ?assertMatch("220 localhost"++_Stuff, Packet),
  968. socket:send(CSock, "EHLO invalid\r\n"),
  969. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  970. ?assertMatch("554 invalid hostname\r\n", Packet2)
  971. end
  972. }
  973. end,
  974. fun({CSock, _Pid}) ->
  975. {"EHLO response",
  976. fun() ->
  977. socket:active_once(CSock),
  978. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  979. ?assertMatch("220 localhost"++_Stuff, Packet),
  980. socket:send(CSock, "EHLO somehost.com\r\n"),
  981. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  982. ?assertMatch("250-localhost\r\n", Packet2),
  983. Foo = fun(F) ->
  984. receive
  985. {tcp, CSock, "250-"++_Packet3} ->
  986. socket:active_once(CSock),
  987. F(F);
  988. {tcp, CSock, "250 "++_Packet3} ->
  989. socket:active_once(CSock),
  990. ok;
  991. {tcp, CSock, _R} ->
  992. socket:active_once(CSock),
  993. error
  994. end
  995. end,
  996. ?assertEqual(ok, Foo(Foo))
  997. end
  998. }
  999. end,
  1000. fun({CSock, _Pid}) ->
  1001. {"Unsupported AUTH PLAIN",
  1002. fun() ->
  1003. socket:active_once(CSock),
  1004. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1005. ?assertMatch("220 localhost"++_Stuff, Packet),
  1006. socket:send(CSock, "EHLO somehost.com\r\n"),
  1007. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1008. ?assertMatch("250-localhost\r\n", Packet2),
  1009. Foo = fun(F) ->
  1010. receive
  1011. {tcp, CSock, "250-"++_Packet3} ->
  1012. socket:active_once(CSock),
  1013. F(F);
  1014. {tcp, CSock, "250"++_Packet3} ->
  1015. socket:active_once(CSock),
  1016. ok;
  1017. {tcp, CSock, _R} ->
  1018. socket:active_once(CSock),
  1019. error
  1020. end
  1021. end,
  1022. ?assertEqual(ok, Foo(Foo)),
  1023. socket:send(CSock, "AUTH PLAIN\r\n"),
  1024. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1025. ?assertMatch("502 Error: AUTH not implemented\r\n", Packet4)
  1026. end
  1027. }
  1028. end,
  1029. fun({CSock, _Pid}) ->
  1030. {"Sending DATA",
  1031. fun() ->
  1032. socket:active_once(CSock),
  1033. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1034. ?assertMatch("220 localhost"++_Stuff, Packet),
  1035. socket:send(CSock, "HELO somehost.com\r\n"),
  1036. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1037. ?assertMatch("250 localhost\r\n", Packet2),
  1038. socket:send(CSock, "MAIL FROM: <user@somehost.com>\r\n"),
  1039. receive {tcp, CSock, Packet3} -> socket:active_once(CSock) end,
  1040. ?assertMatch("250 "++_, Packet3),
  1041. socket:send(CSock, "RCPT TO: <user@otherhost.com>\r\n"),
  1042. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1043. ?assertMatch("250 "++_, Packet4),
  1044. socket:send(CSock, "DATA\r\n"),
  1045. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1046. ?assertMatch("354 "++_, Packet5),
  1047. socket:send(CSock, "Subject: tls message\r\n"),
  1048. socket:send(CSock, "To: <user@otherhost>\r\n"),
  1049. socket:send(CSock, "From: <user@somehost.com>\r\n"),
  1050. socket:send(CSock, "\r\n"),
  1051. socket:send(CSock, "message body"),
  1052. socket:send(CSock, "\r\n.\r\n"),
  1053. receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1054. ?assertMatch("250 queued as"++_, Packet6)
  1055. end
  1056. }
  1057. end,
  1058. % fun({CSock, _Pid}) ->
  1059. % {"Sending DATA with a bare newline",
  1060. % fun() ->
  1061. % socket:active_once(CSock),
  1062. % receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1063. % ?assertMatch("220 localhost"++_Stuff, Packet),
  1064. % socket:send(CSock, "HELO somehost.com\r\n"),
  1065. % receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1066. % ?assertMatch("250 localhost\r\n", Packet2),
  1067. % socket:send(CSock, "MAIL FROM: <user@somehost.com>\r\n"),
  1068. % receive {tcp, CSock, Packet3} -> socket:active_once(CSock) end,
  1069. % ?assertMatch("250 "++_, Packet3),
  1070. % socket:send(CSock, "RCPT TO: <user@otherhost.com>\r\n"),
  1071. % receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1072. % ?assertMatch("250 "++_, Packet4),
  1073. % socket:send(CSock, "DATA\r\n"),
  1074. % receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1075. % ?assertMatch("354 "++_, Packet5),
  1076. % socket:send(CSock, "Subject: tls message\r\n"),
  1077. % socket:send(CSock, "To: <user@otherhost>\r\n"),
  1078. % socket:send(CSock, "From: <user@somehost.com>\r\n"),
  1079. % socket:send(CSock, "\r\n"),
  1080. % socket:send(CSock, "this\r\n"),
  1081. % socket:send(CSock, "body\r\n"),
  1082. % socket:send(CSock, "has\r\n"),
  1083. % socket:send(CSock, "a\r\n"),
  1084. % socket:send(CSock, "bare\n"),
  1085. % socket:send(CSock, "newline\r\n"),
  1086. % socket:send(CSock, "\r\n.\r\n"),
  1087. % receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1088. % ?assertMatch("451 "++_, Packet6),
  1089. % end
  1090. % }
  1091. % end,
  1092. %fun({CSock, _Pid}) ->
  1093. % {"Sending DATA with a bare CR",
  1094. % fun() ->
  1095. % socket:active_once(CSock),
  1096. % receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1097. % ?assertMatch("220 localhost"++_Stuff, Packet),
  1098. % socket:send(CSock, "HELO somehost.com\r\n"),
  1099. % receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1100. % ?assertMatch("250 localhost\r\n", Packet2),
  1101. % socket:send(CSock, "MAIL FROM: <user@somehost.com>\r\n"),
  1102. % receive {tcp, CSock, Packet3} -> socket:active_once(CSock) end,
  1103. % ?assertMatch("250 "++_, Packet3),
  1104. % socket:send(CSock, "RCPT TO: <user@otherhost.com>\r\n"),
  1105. % receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1106. % ?assertMatch("250 "++_, Packet4),
  1107. % socket:send(CSock, "DATA\r\n"),
  1108. % receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1109. % ?assertMatch("354 "++_, Packet5),
  1110. % socket:send(CSock, "Subject: tls message\r\n"),
  1111. % socket:send(CSock, "To: <user@otherhost>\r\n"),
  1112. % socket:send(CSock, "From: <user@somehost.com>\r\n"),
  1113. % socket:send(CSock, "\r\n"),
  1114. % socket:send(CSock, "this\r\n"),
  1115. % socket:send(CSock, "\rbody\r\n"),
  1116. % socket:send(CSock, "has\r\n"),
  1117. % socket:send(CSock, "a\r\n"),
  1118. % socket:send(CSock, "bare\r"),
  1119. % socket:send(CSock, "CR\r\n"),
  1120. % socket:send(CSock, "\r\n.\r\n"),
  1121. % receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1122. % ?assertMatch("451 "++_, Packet6),
  1123. % end
  1124. % }
  1125. % end,
  1126. % fun({CSock, _Pid}) ->
  1127. % {"Sending DATA with a bare newline in the headers",
  1128. % fun() ->
  1129. % socket:active_once(CSock),
  1130. % receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1131. % ?assertMatch("220 localhost"++_Stuff, Packet),
  1132. % socket:send(CSock, "HELO somehost.com\r\n"),
  1133. % receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1134. % ?assertMatch("250 localhost\r\n", Packet2),
  1135. % socket:send(CSock, "MAIL FROM: <user@somehost.com>\r\n"),
  1136. % receive {tcp, CSock, Packet3} -> socket:active_once(CSock) end,
  1137. % ?assertMatch("250 "++_, Packet3),
  1138. % socket:send(CSock, "RCPT TO: <user@otherhost.com>\r\n"),
  1139. % receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1140. % ?assertMatch("250 "++_, Packet4),
  1141. % socket:send(CSock, "DATA\r\n"),
  1142. % receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1143. % ?assertMatch("354 "++_, Packet5),
  1144. % socket:send(CSock, "Subject: tls message\r\n"),
  1145. % socket:send(CSock, "To: <user@otherhost>\n"),
  1146. % socket:send(CSock, "From: <user@somehost.com>\r\n"),
  1147. % socket:send(CSock, "\r\n"),
  1148. % socket:send(CSock, "this\r\n"),
  1149. % socket:send(CSock, "body\r\n"),
  1150. % socket:send(CSock, "has\r\n"),
  1151. % socket:send(CSock, "no\r\n"),
  1152. % socket:send(CSock, "bare\r\n"),
  1153. % socket:send(CSock, "newlines\r\n"),
  1154. % socket:send(CSock, "\r\n.\r\n"),
  1155. % receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1156. % ?assertMatch("451 "++_, Packet6),
  1157. % end
  1158. % }
  1159. % end,
  1160. fun({CSock, _Pid}) ->
  1161. {"Sending DATA with bare newline on first line of body",
  1162. fun() ->
  1163. socket:active_once(CSock),
  1164. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1165. ?assertMatch("220 localhost"++_Stuff, Packet),
  1166. socket:send(CSock, "HELO somehost.com\r\n"),
  1167. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1168. ?assertMatch("250 localhost\r\n", Packet2),
  1169. socket:send(CSock, "MAIL FROM: <user@somehost.com>\r\n"),
  1170. receive {tcp, CSock, Packet3} -> socket:active_once(CSock) end,
  1171. ?assertMatch("250 "++_, Packet3),
  1172. socket:send(CSock, "RCPT TO: <user@otherhost.com>\r\n"),
  1173. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1174. ?assertMatch("250 "++_, Packet4),
  1175. socket:send(CSock, "DATA\r\n"),
  1176. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1177. ?assertMatch("354 "++_, Packet5),
  1178. socket:send(CSock, "Subject: tls message\r\n"),
  1179. socket:send(CSock, "To: <user@otherhost>\n"),
  1180. socket:send(CSock, "From: <user@somehost.com>\r\n"),
  1181. socket:send(CSock, "\r\n"),
  1182. socket:send(CSock, "this\n"),
  1183. socket:send(CSock, "body\r\n"),
  1184. socket:send(CSock, "has\r\n"),
  1185. socket:send(CSock, "no\r\n"),
  1186. socket:send(CSock, "bare\r\n"),
  1187. socket:send(CSock, "newlines\r\n"),
  1188. socket:send(CSock, "\r\n.\r\n"),
  1189. receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1190. ?assertMatch("451 "++_, Packet6)
  1191. end
  1192. }
  1193. end
  1194. ]
  1195. }.
  1196. smtp_session_auth_test_() ->
  1197. {foreach,
  1198. local,
  1199. fun() ->
  1200. Self = self(),
  1201. spawn(fun() ->
  1202. {ok, ListenSock} = socket:listen(tcp, 9876, [binary]),
  1203. {ok, X} = socket:accept(ListenSock),
  1204. socket:controlling_process(X, Self),
  1205. Self ! X
  1206. end),
  1207. {ok, CSock} = socket:connect(tcp, "localhost", 9876),
  1208. receive
  1209. SSock when is_port(SSock) ->
  1210. ok
  1211. end,
  1212. {ok, Pid} = gen_smtp_server_session:start(SSock, smtp_server_example, [{hostname, "localhost"}, {sessioncount, 1}, {callbackoptions, [{auth, true}]}]),
  1213. socket:controlling_process(SSock, Pid),
  1214. {CSock, Pid}
  1215. end,
  1216. fun({CSock, _Pid}) ->
  1217. socket:close(CSock)
  1218. end,
  1219. [fun({CSock, _Pid}) ->
  1220. {"EHLO response includes AUTH",
  1221. fun() ->
  1222. socket:active_once(CSock),
  1223. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1224. ?assertMatch("220 localhost"++_Stuff, Packet),
  1225. socket:send(CSock, "EHLO somehost.com\r\n"),
  1226. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1227. ?assertMatch("250-localhost\r\n", Packet2),
  1228. Foo = fun(F, Acc) ->
  1229. receive
  1230. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1231. socket:active_once(CSock),
  1232. F(F, true);
  1233. {tcp, CSock, "250-"++_Packet3} ->
  1234. socket:active_once(CSock),
  1235. F(F, Acc);
  1236. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1237. socket:active_once(CSock),
  1238. true;
  1239. {tcp, CSock, "250 "++_Packet3} ->
  1240. socket:active_once(CSock),
  1241. Acc;
  1242. {tcp, CSock, _} ->
  1243. socket:active_once(CSock),
  1244. error
  1245. end
  1246. end,
  1247. ?assertEqual(true, Foo(Foo, false))
  1248. end
  1249. }
  1250. end,
  1251. fun({CSock, _Pid}) ->
  1252. {"AUTH before EHLO is error",
  1253. fun() ->
  1254. socket:active_once(CSock),
  1255. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1256. ?assertMatch("220 localhost"++_Stuff, Packet),
  1257. socket:send(CSock, "AUTH CRAZY\r\n"),
  1258. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1259. ?assertMatch("503 "++_, Packet4)
  1260. end
  1261. }
  1262. end,
  1263. fun({CSock, _Pid}) ->
  1264. {"Unknown authentication type",
  1265. fun() ->
  1266. socket:active_once(CSock),
  1267. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1268. ?assertMatch("220 localhost"++_Stuff, Packet),
  1269. socket:send(CSock, "EHLO somehost.com\r\n"),
  1270. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1271. ?assertMatch("250-localhost\r\n", Packet2),
  1272. Foo = fun(F, Acc) ->
  1273. receive
  1274. {tcp, CSock, "250-AUTH"++_} ->
  1275. socket:active_once(CSock),
  1276. F(F, true);
  1277. {tcp, CSock, "250-"++_} ->
  1278. socket:active_once(CSock),
  1279. F(F, Acc);
  1280. {tcp, CSock, "250 AUTH"++_} ->
  1281. socket:active_once(CSock),
  1282. true;
  1283. {tcp, CSock, "250 "++_} ->
  1284. socket:active_once(CSock),
  1285. Acc;
  1286. {tcp, CSock, _} ->
  1287. socket:active_once(CSock),
  1288. error
  1289. end
  1290. end,
  1291. ?assertEqual(true, Foo(Foo, false)),
  1292. socket:send(CSock, "AUTH CRAZY\r\n"),
  1293. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1294. ?assertMatch("504 Unrecognized authentication type\r\n", Packet4)
  1295. end
  1296. }
  1297. end,
  1298. fun({CSock, _Pid}) ->
  1299. {"A successful AUTH PLAIN",
  1300. fun() ->
  1301. socket:active_once(CSock),
  1302. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1303. ?assertMatch("220 localhost"++_Stuff, Packet),
  1304. socket:send(CSock, "EHLO somehost.com\r\n"),
  1305. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1306. ?assertMatch("250-localhost\r\n", Packet2),
  1307. Foo = fun(F, Acc) ->
  1308. receive
  1309. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1310. socket:active_once(CSock),
  1311. F(F, true);
  1312. {tcp, CSock, "250-"++_Packet3} ->
  1313. socket:active_once(CSock),
  1314. F(F, Acc);
  1315. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1316. socket:active_once(CSock),
  1317. true;
  1318. {tcp, CSock, "250 "++_Packet3} ->
  1319. socket:active_once(CSock),
  1320. Acc;
  1321. {tcp, CSock, _} ->
  1322. socket:active_once(CSock),
  1323. error
  1324. end
  1325. end,
  1326. ?assertEqual(true, Foo(Foo, false)),
  1327. socket:send(CSock, "AUTH PLAIN\r\n"),
  1328. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1329. ?assertMatch("334\r\n", Packet4),
  1330. String = binary_to_list(base64:encode("\0username\0PaSSw0rd")),
  1331. socket:send(CSock, String++"\r\n"),
  1332. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1333. ?assertMatch("235 Authentication successful.\r\n", Packet5)
  1334. end
  1335. }
  1336. end,
  1337. fun({CSock, _Pid}) ->
  1338. {"A successful AUTH PLAIN with an identity",
  1339. fun() ->
  1340. socket:active_once(CSock),
  1341. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1342. ?assertMatch("220 localhost"++_Stuff, Packet),
  1343. socket:send(CSock, "EHLO somehost.com\r\n"),
  1344. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1345. ?assertMatch("250-localhost\r\n", Packet2),
  1346. Foo = fun(F, Acc) ->
  1347. receive
  1348. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1349. socket:active_once(CSock),
  1350. F(F, true);
  1351. {tcp, CSock, "250-"++_Packet3} ->
  1352. socket:active_once(CSock),
  1353. F(F, Acc);
  1354. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1355. socket:active_once(CSock),
  1356. true;
  1357. {tcp, CSock, "250 "++_Packet3} ->
  1358. socket:active_once(CSock),
  1359. Acc;
  1360. {tcp, CSock, _} ->
  1361. socket:active_once(CSock),
  1362. error
  1363. end
  1364. end,
  1365. ?assertEqual(true, Foo(Foo, false)),
  1366. socket:send(CSock, "AUTH PLAIN\r\n"),
  1367. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1368. ?assertMatch("334\r\n", Packet4),
  1369. String = binary_to_list(base64:encode("username\0username\0PaSSw0rd")),
  1370. socket:send(CSock, String++"\r\n"),
  1371. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1372. ?assertMatch("235 Authentication successful.\r\n", Packet5)
  1373. end
  1374. }
  1375. end,
  1376. fun({CSock, _Pid}) ->
  1377. {"A successful immediate AUTH PLAIN",
  1378. fun() ->
  1379. socket:active_once(CSock),
  1380. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1381. ?assertMatch("220 localhost"++_Stuff, Packet),
  1382. socket:send(CSock, "EHLO somehost.com\r\n"),
  1383. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1384. ?assertMatch("250-localhost\r\n", Packet2),
  1385. Foo = fun(F, Acc) ->
  1386. receive
  1387. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1388. socket:active_once(CSock),
  1389. F(F, true);
  1390. {tcp, CSock, "250-"++_Packet3} ->
  1391. socket:active_once(CSock),
  1392. F(F, Acc);
  1393. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1394. socket:active_once(CSock),
  1395. true;
  1396. {tcp, CSock, "250 "++_Packet3} ->
  1397. socket:active_once(CSock),
  1398. Acc;
  1399. {tcp, CSock, _} ->
  1400. socket:active_once(CSock),
  1401. error
  1402. end
  1403. end,
  1404. ?assertEqual(true, Foo(Foo, false)),
  1405. String = binary_to_list(base64:encode("\0username\0PaSSw0rd")),
  1406. socket:send(CSock, "AUTH PLAIN "++String++"\r\n"),
  1407. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1408. ?assertMatch("235 Authentication successful.\r\n", Packet5)
  1409. end
  1410. }
  1411. end,
  1412. fun({CSock, _Pid}) ->
  1413. {"A successful immediate AUTH PLAIN with an identity",
  1414. fun() ->
  1415. socket:active_once(CSock),
  1416. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1417. ?assertMatch("220 localhost"++_Stuff, Packet),
  1418. socket:send(CSock, "EHLO somehost.com\r\n"),
  1419. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1420. ?assertMatch("250-localhost\r\n", Packet2),
  1421. ?assertMatch("250-localhost\r\n", Packet2),
  1422. Foo = fun(F, Acc) ->
  1423. receive
  1424. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1425. socket:active_once(CSock),
  1426. F(F, true);
  1427. {tcp, CSock, "250-"++_Packet3} ->
  1428. socket:active_once(CSock),
  1429. F(F, Acc);
  1430. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1431. socket:active_once(CSock),
  1432. true;
  1433. {tcp, CSock, "250 "++_Packet3} ->
  1434. socket:active_once(CSock),
  1435. Acc;
  1436. {tcp, CSock, _R} ->
  1437. socket:active_once(CSock),
  1438. error
  1439. end
  1440. end,
  1441. ?assertEqual(true, Foo(Foo, false)),
  1442. String = binary_to_list(base64:encode("username\0username\0PaSSw0rd")),
  1443. socket:send(CSock, "AUTH PLAIN "++String++"\r\n"),
  1444. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1445. ?assertMatch("235 Authentication successful.\r\n", Packet5)
  1446. end
  1447. }
  1448. end,
  1449. fun({CSock, _Pid}) ->
  1450. {"An unsuccessful immediate AUTH PLAIN",
  1451. fun() ->
  1452. socket:active_once(CSock),
  1453. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1454. ?assertMatch("220 localhost"++_Stuff, Packet),
  1455. socket:send(CSock, "EHLO somehost.com\r\n"),
  1456. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1457. ?assertMatch("250-localhost\r\n", Packet2),
  1458. ?assertMatch("250-localhost\r\n", Packet2),
  1459. Foo = fun(F, Acc) ->
  1460. receive
  1461. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1462. socket:active_once(CSock),
  1463. F(F, true);
  1464. {tcp, CSock, "250-"++_Packet3} ->
  1465. socket:active_once(CSock),
  1466. F(F, Acc);
  1467. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1468. socket:active_once(CSock),
  1469. true;
  1470. {tcp, CSock, "250 "++_Packet3} ->
  1471. socket:active_once(CSock),
  1472. Acc;
  1473. {tcp, CSock, _} ->
  1474. socket:active_once(CSock),
  1475. error
  1476. end
  1477. end,
  1478. ?assertEqual(true, Foo(Foo, false)),
  1479. String = binary_to_list(base64:encode("username\0username\0PaSSw0rd2")),
  1480. socket:send(CSock, "AUTH PLAIN "++String++"\r\n"),
  1481. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1482. ?assertMatch("535 Authentication failed.\r\n", Packet5)
  1483. end
  1484. }
  1485. end,
  1486. fun({CSock, _Pid}) ->
  1487. {"An unsuccessful AUTH PLAIN",
  1488. fun() ->
  1489. socket:active_once(CSock),
  1490. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1491. ?assertMatch("220 localhost"++_Stuff, Packet),
  1492. socket:send(CSock, "EHLO somehost.com\r\n"),
  1493. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1494. ?assertMatch("250-localhost\r\n", Packet2),
  1495. ?assertMatch("250-localhost\r\n", Packet2),
  1496. Foo = fun(F, Acc) ->
  1497. receive
  1498. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1499. socket:active_once(CSock),
  1500. F(F, true);
  1501. {tcp, CSock, "250-"++_Packet3} ->
  1502. socket:active_once(CSock),
  1503. F(F, Acc);
  1504. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1505. socket:active_once(CSock),
  1506. true;
  1507. {tcp, CSock, "250 "++_Packet3} ->
  1508. socket:active_once(CSock),
  1509. Acc;
  1510. {tcp, CSock, _} ->
  1511. socket:active_once(CSock),
  1512. error
  1513. end
  1514. end,
  1515. ?assertEqual(true, Foo(Foo, false)),
  1516. socket:send(CSock, "AUTH PLAIN\r\n"),
  1517. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1518. ?assertMatch("334\r\n", Packet4),
  1519. String = binary_to_list(base64:encode("\0username\0NotThePassword")),
  1520. socket:send(CSock, String++"\r\n"),
  1521. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1522. ?assertMatch("535 Authentication failed.\r\n", Packet5)
  1523. end
  1524. }
  1525. end,
  1526. fun({CSock, _Pid}) ->
  1527. {"A successful AUTH LOGIN",
  1528. fun() ->
  1529. socket:active_once(CSock),
  1530. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1531. ?assertMatch("220 localhost"++_Stuff, Packet),
  1532. socket:send(CSock, "EHLO somehost.com\r\n"),
  1533. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1534. ?assertMatch("250-localhost\r\n", Packet2),
  1535. Foo = fun(F, Acc) ->
  1536. receive
  1537. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1538. socket:active_once(CSock),
  1539. F(F, true);
  1540. {tcp, CSock, "250-"++_Packet3} ->
  1541. socket:active_once(CSock),
  1542. F(F, Acc);
  1543. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1544. socket:active_once(CSock),
  1545. true;
  1546. {tcp, CSock, "250 "++_Packet3} ->
  1547. socket:active_once(CSock),
  1548. Acc;
  1549. {tcp, CSock, _} ->
  1550. socket:active_once(CSock),
  1551. error
  1552. end
  1553. end,
  1554. ?assertEqual(true, Foo(Foo, false)),
  1555. socket:send(CSock, "AUTH LOGIN\r\n"),
  1556. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1557. ?assertMatch("334 VXNlcm5hbWU6\r\n", Packet4),
  1558. String = binary_to_list(base64:encode("username")),
  1559. socket:send(CSock, String++"\r\n"),
  1560. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1561. ?assertMatch("334 UGFzc3dvcmQ6\r\n", Packet5),
  1562. PString = binary_to_list(base64:encode("PaSSw0rd")),
  1563. socket:send(CSock, PString++"\r\n"),
  1564. receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1565. ?assertMatch("235 Authentication successful.\r\n", Packet6)
  1566. end
  1567. }
  1568. end,
  1569. fun({CSock, _Pid}) ->
  1570. {"An unsuccessful AUTH LOGIN",
  1571. fun() ->
  1572. socket:active_once(CSock),
  1573. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1574. ?assertMatch("220 localhost"++_Stuff, Packet),
  1575. socket:send(CSock, "EHLO somehost.com\r\n"),
  1576. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1577. ?assertMatch("250-localhost\r\n", Packet2),
  1578. Foo = fun(F, Acc) ->
  1579. receive
  1580. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1581. socket:active_once(CSock),
  1582. F(F, true);
  1583. {tcp, CSock, "250-"++_Packet3} ->
  1584. socket:active_once(CSock),
  1585. F(F, Acc);
  1586. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1587. socket:active_once(CSock),
  1588. true;
  1589. {tcp, CSock, "250 "++_Packet3} ->
  1590. socket:active_once(CSock),
  1591. Acc;
  1592. {tcp, CSock, _} ->
  1593. socket:active_once(CSock),
  1594. error
  1595. end
  1596. end,
  1597. ?assertEqual(true, Foo(Foo, false)),
  1598. socket:send(CSock, "AUTH LOGIN\r\n"),
  1599. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1600. ?assertMatch("334 VXNlcm5hbWU6\r\n", Packet4),
  1601. String = binary_to_list(base64:encode("username2")),
  1602. socket:send(CSock, String++"\r\n"),
  1603. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1604. ?assertMatch("334 UGFzc3dvcmQ6\r\n", Packet5),
  1605. PString = binary_to_list(base64:encode("PaSSw0rd")),
  1606. socket:send(CSock, PString++"\r\n"),
  1607. receive {tcp, CSock, Packet6} -> socket:active_once(CSock) end,
  1608. ?assertMatch("535 Authentication failed.\r\n", Packet6)
  1609. end
  1610. }
  1611. end,
  1612. fun({CSock, _Pid}) ->
  1613. {"A successful AUTH CRAM-MD5",
  1614. fun() ->
  1615. socket:active_once(CSock),
  1616. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1617. ?assertMatch("220 localhost"++_Stuff, Packet),
  1618. socket:send(CSock, "EHLO somehost.com\r\n"),
  1619. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1620. ?assertMatch("250-localhost\r\n", Packet2),
  1621. Foo = fun(F, Acc) ->
  1622. receive
  1623. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1624. socket:active_once(CSock),
  1625. F(F, true);
  1626. {tcp, CSock, "250-"++_Packet3} ->
  1627. socket:active_once(CSock),
  1628. F(F, Acc);
  1629. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1630. socket:active_once(CSock),
  1631. true;
  1632. {tcp, CSock, "250 "++_Packet3} ->
  1633. socket:active_once(CSock),
  1634. Acc;
  1635. {tcp, CSock, _} ->
  1636. socket:active_once(CSock),
  1637. error
  1638. end
  1639. end,
  1640. ?assertEqual(true, Foo(Foo, false)),
  1641. socket:send(CSock, "AUTH CRAM-MD5\r\n"),
  1642. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1643. ?assertMatch("334 "++_, Packet4),
  1644. ["334", Seed64] = string:tokens(smtp_util:trim_crlf(Packet4), " "),
  1645. Seed = base64:decode_to_string(Seed64),
  1646. Digest = smtp_util:compute_cram_digest("PaSSw0rd", Seed),
  1647. String = binary_to_list(base64:encode(list_to_binary(["username ", Digest]))),
  1648. socket:send(CSock, String++"\r\n"),
  1649. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1650. ?assertMatch("235 Authentication successful.\r\n", Packet5)
  1651. end
  1652. }
  1653. end,
  1654. fun({CSock, _Pid}) ->
  1655. {"An unsuccessful AUTH CRAM-MD5",
  1656. fun() ->
  1657. socket:active_once(CSock),
  1658. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1659. ?assertMatch("220 localhost"++_Stuff, Packet),
  1660. socket:send(CSock, "EHLO somehost.com\r\n"),
  1661. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1662. ?assertMatch("250-localhost\r\n", Packet2),
  1663. Foo = fun(F, Acc) ->
  1664. receive
  1665. {tcp, CSock, "250-AUTH"++_Packet3} ->
  1666. socket:active_once(CSock),
  1667. F(F, true);
  1668. {tcp, CSock, "250-"++_Packet3} ->
  1669. socket:active_once(CSock),
  1670. F(F, Acc);
  1671. {tcp, CSock, "250 AUTH"++_Packet3} ->
  1672. socket:active_once(CSock),
  1673. true;
  1674. {tcp, CSock, "250 "++_Packet3} ->
  1675. socket:active_once(CSock),
  1676. Acc;
  1677. {tcp, CSock, _} ->
  1678. socket:active_once(CSock),
  1679. error
  1680. end
  1681. end,
  1682. ?assertEqual(true, Foo(Foo, false)),
  1683. socket:send(CSock, "AUTH CRAM-MD5\r\n"),
  1684. receive {tcp, CSock, Packet4} -> socket:active_once(CSock) end,
  1685. ?assertMatch("334 "++_, Packet4),
  1686. ["334", Seed64] = string:tokens(smtp_util:trim_crlf(Packet4), " "),
  1687. Seed = base64:decode_to_string(Seed64),
  1688. Digest = smtp_util:compute_cram_digest("Passw0rd", Seed),
  1689. String = binary_to_list(base64:encode(list_to_binary(["username ", Digest]))),
  1690. socket:send(CSock, String++"\r\n"),
  1691. receive {tcp, CSock, Packet5} -> socket:active_once(CSock) end,
  1692. ?assertMatch("535 Authentication failed.\r\n", Packet5)
  1693. end
  1694. }
  1695. end
  1696. ]
  1697. }.
  1698. smtp_session_tls_test_() ->
  1699. {foreach,
  1700. local,
  1701. fun() ->
  1702. crypto:start(),
  1703. application:start(public_key),
  1704. application:start(ssl),
  1705. Self = self(),
  1706. spawn(fun() ->
  1707. {ok, ListenSock} = socket:listen(tcp, 9876, [binary]),
  1708. {ok, X} = socket:accept(ListenSock),
  1709. socket:controlling_process(X, Self),
  1710. Self ! X
  1711. end),
  1712. {ok, CSock} = socket:connect(tcp, "localhost", 9876),
  1713. receive
  1714. SSock when is_port(SSock) ->
  1715. ok
  1716. end,
  1717. {ok, Pid} = gen_smtp_server_session:start(SSock, smtp_server_example, [{keyfile, "../testdata/server.key"}, {certfile, "../testdata/server.crt"}, {hostname, "localhost"}, {sessioncount, 1}, {callbackoptions, [{auth, true}]}]),
  1718. socket:controlling_process(SSock, Pid),
  1719. {CSock, Pid}
  1720. end,
  1721. fun({CSock, _Pid}) ->
  1722. socket:close(CSock)
  1723. end,
  1724. [fun({CSock, _Pid}) ->
  1725. {"EHLO response includes STARTTLS",
  1726. fun() ->
  1727. socket:active_once(CSock),
  1728. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1729. ?assertMatch("220 localhost"++_Stuff, Packet),
  1730. socket:send(CSock, "EHLO somehost.com\r\n"),
  1731. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1732. ?assertMatch("250-localhost\r\n", Packet2),
  1733. Foo = fun(F, Acc) ->
  1734. receive
  1735. {tcp, CSock, "250-STARTTLS"++_} ->
  1736. socket:active_once(CSock),
  1737. F(F, true);
  1738. {tcp, CSock, "250-"++_Packet3} ->
  1739. socket:active_once(CSock),
  1740. F(F, Acc);
  1741. {tcp, CSock, "250 STARTTLS"++_} ->
  1742. socket:active_once(CSock),
  1743. true;
  1744. {tcp, CSock, "250 "++_Packet3} ->
  1745. socket:active_once(CSock),
  1746. Acc;
  1747. {tcp, CSock, _} ->
  1748. socket:active_once(CSock),
  1749. error
  1750. end
  1751. end,
  1752. ?assertEqual(true, Foo(Foo, false))
  1753. end
  1754. }
  1755. end,
  1756. fun({CSock, _Pid}) ->
  1757. {"STARTTLS does a SSL handshake",
  1758. fun() ->
  1759. socket:active_once(CSock),
  1760. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1761. ?assertMatch("220 localhost"++_Stuff, Packet),
  1762. socket:send(CSock, "EHLO somehost.com\r\n"),
  1763. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1764. ?assertMatch("250-localhost\r\n", Packet2),
  1765. Foo = fun(F, Acc) ->
  1766. receive
  1767. {tcp, CSock, "250-STARTTLS"++_} ->
  1768. socket:active_once(CSock),
  1769. F(F, true);
  1770. {tcp, CSock, "250-"++_Packet3} ->
  1771. socket:active_once(CSock),
  1772. F(F, Acc);
  1773. {tcp, CSock, "250 STARTTLS"++_} ->
  1774. socket:active_once(CSock),
  1775. true;
  1776. {tcp, CSock, "250 "++_Packet3} ->
  1777. socket:active_once(CSock),
  1778. Acc;
  1779. {tcp, CSock, _} ->
  1780. socket:active_once(CSock),
  1781. error
  1782. end
  1783. end,
  1784. ?assertEqual(true, Foo(Foo, false)),
  1785. socket:send(CSock, "STARTTLS\r\n"),
  1786. receive {tcp, CSock, Packet4} -> ok end,
  1787. ?assertMatch("220 "++_, Packet4),
  1788. Result = socket:to_ssl_client(CSock),
  1789. ?assertMatch({ok, _Socket}, Result),
  1790. {ok, _Socket} = Result
  1791. %socket:active_once(Socket),
  1792. %ssl:send(Socket, "EHLO somehost.com\r\n"),
  1793. %receive {ssl, Socket, Packet5} -> socket:active_once(Socket) end,
  1794. %?assertEqual("Foo", Packet5),
  1795. end
  1796. }
  1797. end,
  1798. fun({CSock, _Pid}) ->
  1799. {"After STARTTLS, EHLO doesn't report STARTTLS",
  1800. fun() ->
  1801. socket:active_once(CSock),
  1802. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1803. ?assertMatch("220 localhost"++_Stuff, Packet),
  1804. socket:send(CSock, "EHLO somehost.com\r\n"),
  1805. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1806. ?assertMatch("250-localhost\r\n", Packet2),
  1807. Foo = fun(F, Acc) ->
  1808. receive
  1809. {tcp, CSock, "250-STARTTLS"++_} ->
  1810. socket:active_once(CSock),
  1811. F(F, true);
  1812. {tcp, CSock, "250-"++_Packet3} ->
  1813. socket:active_once(CSock),
  1814. F(F, Acc);
  1815. {tcp, CSock, "250 STARTTLS"++_} ->
  1816. socket:active_once(CSock),
  1817. true;
  1818. {tcp, CSock, "250 "++_Packet3} ->
  1819. socket:active_once(CSock),
  1820. Acc;
  1821. {tcp, CSock, _} ->
  1822. socket:active_once(CSock),
  1823. error
  1824. end
  1825. end,
  1826. ?assertEqual(true, Foo(Foo, false)),
  1827. socket:send(CSock, "STARTTLS\r\n"),
  1828. receive {tcp, CSock, Packet4} -> ok end,
  1829. ?assertMatch("220 "++_, Packet4),
  1830. Result = socket:to_ssl_client(CSock),
  1831. ?assertMatch({ok, _Socket}, Result),
  1832. {ok, Socket} = Result,
  1833. socket:active_once(Socket),
  1834. socket:send(Socket, "EHLO somehost.com\r\n"),
  1835. receive {ssl, Socket, Packet5} -> socket:active_once(Socket) end,
  1836. ?assertMatch("250-localhost\r\n", Packet5),
  1837. Bar = fun(F, Acc) ->
  1838. receive
  1839. {ssl, Socket, "250-STARTTLS"++_} ->
  1840. socket:active_once(Socket),
  1841. F(F, true);
  1842. {ssl, Socket, "250-"++_} ->
  1843. socket:active_once(Socket),
  1844. F(F, Acc);
  1845. {ssl, Socket, "250 STARTTLS"++_} ->
  1846. socket:active_once(Socket),
  1847. true;
  1848. {ssl, Socket, "250 "++_} ->
  1849. socket:active_once(Socket),
  1850. Acc;
  1851. {ssl, Socket, _} ->
  1852. socket:active_once(Socket),
  1853. error
  1854. end
  1855. end,
  1856. ?assertEqual(false, Bar(Bar, false))
  1857. end
  1858. }
  1859. end,
  1860. fun({CSock, _Pid}) ->
  1861. {"After STARTTLS, re-negotiating STARTTLS is an error",
  1862. fun() ->
  1863. socket:active_once(CSock),
  1864. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1865. ?assertMatch("220 localhost"++_Stuff, Packet),
  1866. socket:send(CSock, "EHLO somehost.com\r\n"),
  1867. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1868. ?assertMatch("250-localhost\r\n", Packet2),
  1869. Foo = fun(F, Acc) ->
  1870. receive
  1871. {tcp, CSock, "250-STARTTLS"++_} ->
  1872. socket:active_once(CSock),
  1873. F(F, true);
  1874. {tcp, CSock, "250-"++_Packet3} ->
  1875. socket:active_once(CSock),
  1876. F(F, Acc);
  1877. {tcp, CSock, "250 STARTTLS"++_} ->
  1878. socket:active_once(CSock),
  1879. true;
  1880. {tcp, CSock, "250 "++_Packet3} ->
  1881. socket:active_once(CSock),
  1882. Acc;
  1883. {tcp, CSock, _} ->
  1884. socket:active_once(CSock),
  1885. error
  1886. end
  1887. end,
  1888. ?assertEqual(true, Foo(Foo, false)),
  1889. socket:send(CSock, "STARTTLS\r\n"),
  1890. receive {tcp, CSock, Packet4} -> ok end,
  1891. ?assertMatch("220 "++_, Packet4),
  1892. Result = socket:to_ssl_client(CSock),
  1893. ?assertMatch({ok, _Socket}, Result),
  1894. {ok, Socket} = Result,
  1895. socket:active_once(Socket),
  1896. socket:send(Socket, "EHLO somehost.com\r\n"),
  1897. receive {ssl, Socket, Packet5} -> socket:active_once(Socket) end,
  1898. ?assertMatch("250-localhost\r\n", Packet5),
  1899. Bar = fun(F, Acc) ->
  1900. receive
  1901. {ssl, Socket, "250-STARTTLS"++_} ->
  1902. socket:active_once(Socket),
  1903. F(F, true);
  1904. {ssl, Socket, "250-"++_} ->
  1905. socket:active_once(Socket),
  1906. F(F, Acc);
  1907. {ssl, Socket, "250 STARTTLS"++_} ->
  1908. socket:active_once(Socket),
  1909. true;
  1910. {ssl, Socket, "250 "++_} ->
  1911. socket:active_once(Socket),
  1912. Acc;
  1913. {ssl, Socket, _} ->
  1914. socket:active_once(Socket),
  1915. error
  1916. end
  1917. end,
  1918. ?assertEqual(false, Bar(Bar, false)),
  1919. socket:send(Socket, "STARTTLS\r\n"),
  1920. receive {ssl, Socket, Packet6} -> socket:active_once(Socket) end,
  1921. ?assertMatch("500 "++_, Packet6)
  1922. end
  1923. }
  1924. end,
  1925. fun({CSock, _Pid}) ->
  1926. {"STARTTLS can't take any parameters",
  1927. fun() ->
  1928. socket:active_once(CSock),
  1929. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  1930. ?assertMatch("220 localhost"++_Stuff, Packet),
  1931. socket:send(CSock, "EHLO somehost.com\r\n"),
  1932. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  1933. ?assertMatch("250-localhost\r\n", Packet2),
  1934. Foo = fun(F, Acc) ->
  1935. receive
  1936. {tcp, CSock, "250-STARTTLS"++_} ->
  1937. socket:active_once(CSock),
  1938. F(F, true);
  1939. {tcp, CSock, "250-"++_Packet3} ->
  1940. socket:active_once(CSock),
  1941. F(F, Acc);
  1942. {tcp, CSock, "250 STARTTLS"++_} ->
  1943. socket:active_once(CSock),
  1944. true;
  1945. {tcp, CSock, "250 "++_Packet3} ->
  1946. socket:active_once(CSock),
  1947. Acc;
  1948. {tcp, CSock, _} ->
  1949. socket:active_once(CSock),
  1950. error
  1951. end
  1952. end,
  1953. ?assertEqual(true, Foo(Foo, false)),
  1954. socket:send(CSock, "STARTTLS foo\r\n"),
  1955. receive {tcp, CSock, Packet4} -> ok end,
  1956. ?assertMatch("501 "++_, Packet4)
  1957. end
  1958. }
  1959. end,
  1960. fun({CSock, _Pid}) ->
  1961. {"Negotiating STARTTLS twice is an error",
  1962. fun() ->
  1963. socket:active_once(CSock),
  1964. receive {tcp, CSock, _Packet} -> socket:active_once(CSock) end,
  1965. socket:send(CSock, "EHLO somehost.com\r\n"),
  1966. receive {tcp, CSock, _Packet2} -> socket:active_once(CSock) end,
  1967. ReadExtensions = fun(F, Acc) ->
  1968. receive
  1969. {tcp, CSock, "250-STARTTLS"++_} ->
  1970. socket:active_once(CSock),
  1971. F(F, true);
  1972. {tcp, CSock, "250-"++_Packet3} ->
  1973. socket:active_once(CSock),
  1974. F(F, Acc);
  1975. {tcp, CSock, "250 STARTTLS"++_} ->
  1976. socket:active_once(CSock),
  1977. true;
  1978. {tcp, CSock, "250 "++_Packet3} ->
  1979. socket:active_once(CSock),
  1980. Acc;
  1981. {tcp, CSock, _} ->
  1982. socket:active_once(CSock),
  1983. error
  1984. end
  1985. end,
  1986. ?assertEqual(true, ReadExtensions(ReadExtensions, false)),
  1987. socket:send(CSock, "STARTTLS\r\n"),
  1988. receive {tcp, CSock, _} -> ok end,
  1989. {ok, Socket} = socket:to_ssl_client(CSock),
  1990. socket:active_once(Socket),
  1991. socket:send(Socket, "EHLO somehost.com\r\n"),
  1992. receive {ssl, Socket, PacketN} -> socket:active_once(Socket) end,
  1993. ?assertMatch("250-localhost\r\n", PacketN),
  1994. Bar = fun(F, Acc) ->
  1995. receive
  1996. {ssl, Socket, "250-STARTTLS"++_} ->
  1997. socket:active_once(Socket),
  1998. F(F, true);
  1999. {ssl, Socket, "250-"++_} ->
  2000. socket:active_once(Socket),
  2001. F(F, Acc);
  2002. {ssl, Socket, "250 STARTTLS"++_} ->
  2003. socket:active_once(Socket),
  2004. true;
  2005. {ssl, Socket, "250 "++_} ->
  2006. socket:active_once(Socket),
  2007. Acc;
  2008. {tcp, Socket, _} ->
  2009. socket:active_once(Socket),
  2010. error
  2011. end
  2012. end,
  2013. ?assertEqual(false, Bar(Bar, false)),
  2014. socket:send(Socket, "STARTTLS\r\n"),
  2015. receive {ssl, Socket, Packet6} -> socket:active_once(Socket) end,
  2016. ?assertMatch("500 "++_, Packet6)
  2017. end
  2018. }
  2019. end,
  2020. fun({CSock, _Pid}) ->
  2021. {"STARTTLS can't take any parameters",
  2022. fun() ->
  2023. socket:active_once(CSock),
  2024. receive {tcp, CSock, Packet} -> socket:active_once(CSock) end,
  2025. ?assertMatch("220 localhost"++_Stuff, Packet),
  2026. socket:send(CSock, "EHLO somehost.com\r\n"),
  2027. receive {tcp, CSock, Packet2} -> socket:active_once(CSock) end,
  2028. ?assertMatch("250-localhost\r\n", Packet2),
  2029. Foo = fun(F, Acc) ->
  2030. receive
  2031. {tcp, CSock, "250-STARTTLS"++_} ->
  2032. socket:active_once(CSock),
  2033. F(F, true);
  2034. {tcp, CSock, "250-"++_Packet3} ->
  2035. socket:active_once(CSock),
  2036. F(F, Acc);
  2037. {tcp, CSock, "250 STARTTLS"++_} ->
  2038. socket:active_once(CSock),
  2039. true;
  2040. {tcp, CSock, "250 "++_Packet3} ->
  2041. socket:active_once(CSock),
  2042. Acc;
  2043. {tcp, CSock, _} ->
  2044. socket:active_once(CSock),
  2045. error
  2046. end
  2047. end,
  2048. ?assertEqual(true, Foo(Foo, false)),
  2049. socket:send(CSock, "STARTTLS foo\r\n"),
  2050. receive {tcp, CSock, Packet4} -> ok end,
  2051. ?assertMatch("501 "++_, Packet4)
  2052. end
  2053. }
  2054. end,
  2055. fun({CSock, _Pid}) ->
  2056. {"After STARTTLS, message is received by server",
  2057. fun() ->
  2058. socket:active_once(CSock),
  2059. receive {tcp, CSock, _Packet} -> socket:active_once(CSock) end,
  2060. socket:send(CSock, "EHLO somehost.com\r\n"),
  2061. receive {tcp, CSock, _Packet2} -> socket:active_once(CSock) end,
  2062. ReadExtensions = fun(F, Acc) ->
  2063. receive
  2064. {tcp, CSock, "250-STARTTLS"++_} ->
  2065. socket:active_once(CSock),
  2066. F(F, true);
  2067. {tcp, CSock, "250-"++_Packet3} ->
  2068. socket:active_once(CSock),
  2069. F(F, Acc);
  2070. {tcp, CSock, "250 STARTTLS"++_} ->
  2071. socket:active_once(CSock),
  2072. true;
  2073. {tcp, CSock, "250 "++_Packet3} ->
  2074. socket:active_once(CSock),
  2075. Acc;
  2076. {tcp, CSock, _} ->
  2077. socket:active_once(CSock),
  2078. error
  2079. end
  2080. end,
  2081. ?assertEqual(true, ReadExtensions(ReadExtensions, false)),
  2082. socket:send(CSock, "STARTTLS\r\n"),
  2083. receive {tcp, CSock, _} -> ok end,
  2084. {ok, Socket} = socket:to_ssl_client(CSock),
  2085. socket:active_once(Socket),
  2086. socket:send(Socket, "EHLO somehost.com\r\n"),
  2087. ReadSSLExtensions = fun(F, Acc) ->
  2088. receive
  2089. {ssl, Socket, "250-"++_Rest} ->
  2090. socket:active_once(Socket),
  2091. F(F, Acc);
  2092. {ssl, Socket, "250 "++_} ->
  2093. socket:active_once(Socket),
  2094. true;
  2095. {ssl, Socket, _R} ->
  2096. socket:active_once(Socket),
  2097. error
  2098. end
  2099. end,
  2100. ?assertEqual(true, ReadSSLExtensions(ReadSSLExtensions, false)),
  2101. socket:send(Socket, "MAIL FROM: <user@somehost.com>\r\n"),
  2102. receive {ssl, Socket, Packet4} -> socket:active_once(Socket) end,
  2103. ?assertMatch("250 "++_, Packet4),
  2104. socket:send(Socket, "RCPT TO: <user@otherhost.com>\r\n"),
  2105. receive {ssl, Socket, Packet5} -> socket:active_once(Socket) end,
  2106. ?assertMatch("250 "++_, Packet5),
  2107. socket:send(Socket, "DATA\r\n"),
  2108. receive {ssl, Socket, Packet6} -> socket:active_once(Socket) end,
  2109. ?assertMatch("354 "++_, Packet6),
  2110. socket:send(Socket, "Subject: tls message\r\n"),
  2111. socket:send(Socket, "To: <user@otherhost>\r\n"),
  2112. socket:send(Socket, "From: <user@somehost.com>\r\n"),
  2113. socket:send(Socket, "\r\n"),
  2114. socket:send(Socket, "message body"),
  2115. socket:send(Socket, "\r\n.\r\n"),
  2116. receive {ssl, Socket, Packet7} -> socket:active_once(Socket) end,
  2117. ?assertMatch("250 "++_, Packet7)
  2118. end
  2119. }
  2120. end
  2121. ]
  2122. }.
  2123. stray_newline_test_() ->
  2124. [
  2125. {"Error out by default",
  2126. fun() ->
  2127. ?assertEqual(<<"foo">>, check_bare_crlf(<<"foo">>, <<>>, false, 0)),
  2128. ?assertEqual(error, check_bare_crlf(<<"foo\n">>, <<>>, false, 0)),
  2129. ?assertEqual(error, check_bare_crlf(<<"fo\ro\n">>, <<>>, false, 0)),
  2130. ?assertEqual(error, check_bare_crlf(<<"fo\ro\n\r">>, <<>>, false, 0)),
  2131. ?assertEqual(<<"foo\r\n">>, check_bare_crlf(<<"foo\r\n">>, <<>>, false, 0)),
  2132. ?assertEqual(<<"foo\r">>, check_bare_crlf(<<"foo\r">>, <<>>, false, 0))
  2133. end
  2134. },
  2135. {"Fixing them should work",
  2136. fun() ->
  2137. ?assertEqual(<<"foo">>, check_bare_crlf(<<"foo">>, <<>>, fix, 0)),
  2138. ?assertEqual(<<"foo\r\n">>, check_bare_crlf(<<"foo\n">>, <<>>, fix, 0)),
  2139. ?assertEqual(<<"fo\r\no\r\n">>, check_bare_crlf(<<"fo\ro\n">>, <<>>, fix, 0)),
  2140. ?assertEqual(<<"fo\r\no\r\n\r">>, check_bare_crlf(<<"fo\ro\n\r">>, <<>>, fix, 0)),
  2141. ?assertEqual(<<"foo\r\n">>, check_bare_crlf(<<"foo\r\n">>, <<>>, fix, 0))
  2142. end
  2143. },
  2144. {"Stripping them should work",
  2145. fun() ->
  2146. ?assertEqual(<<"foo">>, check_bare_crlf(<<"foo">>, <<>>, strip, 0)),
  2147. ?assertEqual(<<"foo">>, check_bare_crlf(<<"fo\ro\n">>, <<>>, strip, 0)),
  2148. ?assertEqual(<<"foo\r">>, check_bare_crlf(<<"fo\ro\n\r">>, <<>>, strip, 0)),
  2149. ?assertEqual(<<"foo\r\n">>, check_bare_crlf(<<"foo\r\n">>, <<>>, strip, 0))
  2150. end
  2151. },
  2152. {"Ignoring them should work",
  2153. fun() ->
  2154. ?assertEqual(<<"foo">>, check_bare_crlf(<<"foo">>, <<>>, ignore, 0)),
  2155. ?assertEqual(<<"fo\ro\n">>, check_bare_crlf(<<"fo\ro\n">>, <<>>, ignore, 0)),
  2156. ?assertEqual(<<"fo\ro\n\r">>, check_bare_crlf(<<"fo\ro\n\r">>, <<>>, ignore, 0)),
  2157. ?assertEqual(<<"foo\r\n">>, check_bare_crlf(<<"foo\r\n">>, <<>>, ignore, 0))
  2158. end
  2159. },
  2160. {"Leading bare LFs should check the previous line",
  2161. fun() ->
  2162. ?assertEqual(<<"\nfoo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r">>, false, 0)),
  2163. ?assertEqual(<<"\r\nfoo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r\n">>, fix, 0)),
  2164. ?assertEqual(<<"\nfoo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r">>, fix, 0)),
  2165. ?assertEqual(<<"foo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r\n">>, strip, 0)),
  2166. ?assertEqual(<<"\nfoo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r">>, strip, 0)),
  2167. ?assertEqual(<<"\nfoo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r\n">>, ignore, 0)),
  2168. ?assertEqual(error, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r\n">>, false, 0)),
  2169. ?assertEqual(<<"\nfoo\r\n">>, check_bare_crlf(<<"\nfoo\r\n">>, <<"bar\r">>, false, 0))
  2170. end
  2171. }
  2172. ].
  2173. -endif.