cowboy_http.erl 34 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098
  1. %% Copyright (c) 2011, Loïc Hoguin <essen@dev-extend.eu>
  2. %% Copyright (c) 2011, Anthony Ramine <nox@dev-extend.eu>
  3. %%
  4. %% Permission to use, copy, modify, and/or distribute this software for any
  5. %% purpose with or without fee is hereby granted, provided that the above
  6. %% copyright notice and this permission notice appear in all copies.
  7. %%
  8. %% THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
  9. %% WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
  10. %% MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
  11. %% ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
  12. %% WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
  13. %% ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
  14. %% OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
  15. %% @doc Core HTTP parsing API.
  16. -module(cowboy_http).
  17. %% Parsing.
  18. -export([list/2, nonempty_list/2, content_type/1, media_range/2, conneg/2,
  19. language_range/2, entity_tag_match/1, expectation/2, params/2,
  20. http_date/1, rfc1123_date/1, rfc850_date/1, asctime_date/1,
  21. whitespace/2, digits/1, token/2, token_ci/2, quoted_string/2]).
  22. %% Decoding.
  23. -export([te_chunked/2, te_identity/2, ce_identity/1]).
  24. %% Interpretation.
  25. -export([connection_to_atom/1, urldecode/1, urldecode/2, urlencode/1,
  26. urlencode/2, x_www_form_urlencoded/2]).
  27. -type method() :: 'OPTIONS' | 'GET' | 'HEAD'
  28. | 'POST' | 'PUT' | 'DELETE' | 'TRACE' | binary().
  29. -type uri() :: '*' | {absoluteURI, http | https, Host::binary(),
  30. Port::integer() | undefined, Path::binary()}
  31. | {scheme, Scheme::binary(), binary()}
  32. | {abs_path, binary()} | binary().
  33. -type version() :: {Major::non_neg_integer(), Minor::non_neg_integer()}.
  34. -type header() :: 'Cache-Control' | 'Connection' | 'Date' | 'Pragma'
  35. | 'Transfer-Encoding' | 'Upgrade' | 'Via' | 'Accept' | 'Accept-Charset'
  36. | 'Accept-Encoding' | 'Accept-Language' | 'Authorization' | 'From' | 'Host'
  37. | 'If-Modified-Since' | 'If-Match' | 'If-None-Match' | 'If-Range'
  38. | 'If-Unmodified-Since' | 'Max-Forwards' | 'Proxy-Authorization' | 'Range'
  39. | 'Referer' | 'User-Agent' | 'Age' | 'Location' | 'Proxy-Authenticate'
  40. | 'Public' | 'Retry-After' | 'Server' | 'Vary' | 'Warning'
  41. | 'Www-Authenticate' | 'Allow' | 'Content-Base' | 'Content-Encoding'
  42. | 'Content-Language' | 'Content-Length' | 'Content-Location'
  43. | 'Content-Md5' | 'Content-Range' | 'Content-Type' | 'Etag'
  44. | 'Expires' | 'Last-Modified' | 'Accept-Ranges' | 'Set-Cookie'
  45. | 'Set-Cookie2' | 'X-Forwarded-For' | 'Cookie' | 'Keep-Alive'
  46. | 'Proxy-Connection' | binary().
  47. -type headers() :: [{header(), iodata()}].
  48. -type status() :: non_neg_integer() | binary().
  49. -export_type([method/0, uri/0, version/0, header/0, headers/0, status/0]).
  50. -include_lib("eunit/include/eunit.hrl").
  51. %% Parsing.
  52. %% @doc Parse a non-empty list of the given type.
  53. -spec nonempty_list(binary(), fun()) -> [any(), ...] | {error, badarg}.
  54. nonempty_list(Data, Fun) ->
  55. case list(Data, Fun, []) of
  56. {error, badarg} -> {error, badarg};
  57. [] -> {error, badarg};
  58. L -> lists:reverse(L)
  59. end.
  60. %% @doc Parse a list of the given type.
  61. -spec list(binary(), fun()) -> list() | {error, badarg}.
  62. list(Data, Fun) ->
  63. case list(Data, Fun, []) of
  64. {error, badarg} -> {error, badarg};
  65. L -> lists:reverse(L)
  66. end.
  67. -spec list(binary(), fun(), [binary()]) -> [any()] | {error, badarg}.
  68. %% From the RFC:
  69. %% <blockquote>Wherever this construct is used, null elements are allowed,
  70. %% but do not contribute to the count of elements present.
  71. %% That is, "(element), , (element) " is permitted, but counts
  72. %% as only two elements. Therefore, where at least one element is required,
  73. %% at least one non-null element MUST be present.</blockquote>
  74. list(Data, Fun, Acc) ->
  75. whitespace(Data,
  76. fun (<<>>) -> Acc;
  77. (<< $,, Rest/binary >>) -> list(Rest, Fun, Acc);
  78. (Rest) -> Fun(Rest,
  79. fun (D, I) -> whitespace(D,
  80. fun (<<>>) -> [I|Acc];
  81. (<< $,, R/binary >>) -> list(R, Fun, [I|Acc]);
  82. (_Any) -> {error, badarg}
  83. end)
  84. end)
  85. end).
  86. %% @doc Parse a content type.
  87. -spec content_type(binary()) -> any().
  88. content_type(Data) ->
  89. media_type(Data,
  90. fun (Rest, Type, SubType) ->
  91. params(Rest,
  92. fun (<<>>, Params) -> {Type, SubType, Params};
  93. (_Rest2, _) -> {error, badarg}
  94. end)
  95. end).
  96. %% @doc Parse a media range.
  97. -spec media_range(binary(), fun()) -> any().
  98. media_range(Data, Fun) ->
  99. media_type(Data,
  100. fun (Rest, Type, SubType) ->
  101. media_range_params(Rest, Fun, Type, SubType, [])
  102. end).
  103. -spec media_range_params(binary(), fun(), binary(), binary(),
  104. [{binary(), binary()}]) -> any().
  105. media_range_params(Data, Fun, Type, SubType, Acc) ->
  106. whitespace(Data,
  107. fun (<< $;, Rest/binary >>) ->
  108. whitespace(Rest,
  109. fun (Rest2) ->
  110. media_range_param_attr(Rest2, Fun, Type, SubType, Acc)
  111. end);
  112. (Rest) -> Fun(Rest, {{Type, SubType, lists:reverse(Acc)}, 1000, []})
  113. end).
  114. -spec media_range_param_attr(binary(), fun(), binary(), binary(),
  115. [{binary(), binary()}]) -> any().
  116. media_range_param_attr(Data, Fun, Type, SubType, Acc) ->
  117. token_ci(Data,
  118. fun (_Rest, <<>>) -> {error, badarg};
  119. (<< $=, Rest/binary >>, Attr) ->
  120. media_range_param_value(Rest, Fun, Type, SubType, Acc, Attr)
  121. end).
  122. -spec media_range_param_value(binary(), fun(), binary(), binary(),
  123. [{binary(), binary()}], binary()) -> any().
  124. media_range_param_value(Data, Fun, Type, SubType, Acc, <<"q">>) ->
  125. qvalue(Data,
  126. fun (Rest, Quality) ->
  127. accept_ext(Rest, Fun, Type, SubType, Acc, Quality, [])
  128. end);
  129. media_range_param_value(Data, Fun, Type, SubType, Acc, Attr) ->
  130. word(Data,
  131. fun (Rest, Value) ->
  132. media_range_params(Rest, Fun,
  133. Type, SubType, [{Attr, Value}|Acc])
  134. end).
  135. %% @doc Parse a media type.
  136. -spec media_type(binary(), fun()) -> any().
  137. media_type(Data, Fun) ->
  138. token_ci(Data,
  139. fun (_Rest, <<>>) -> {error, badarg};
  140. (<< $/, Rest/binary >>, Type) ->
  141. token_ci(Rest,
  142. fun (_Rest2, <<>>) -> {error, badarg};
  143. (Rest2, SubType) -> Fun(Rest2, Type, SubType)
  144. end);
  145. %% This is a non-strict parsing clause required by some user agents
  146. %% that use * instead of */* in the list of media types.
  147. (Rest, <<"*">> = Type) ->
  148. token_ci(<<"*", Rest/binary>>,
  149. fun (_Rest2, <<>>) -> {error, badarg};
  150. (Rest2, SubType) -> Fun(Rest2, Type, SubType)
  151. end);
  152. (_Rest, _Type) -> {error, badarg}
  153. end).
  154. -spec accept_ext(binary(), fun(), binary(), binary(),
  155. [{binary(), binary()}], 0..1000,
  156. [{binary(), binary()} | binary()]) -> any().
  157. accept_ext(Data, Fun, Type, SubType, Params, Quality, Acc) ->
  158. whitespace(Data,
  159. fun (<< $;, Rest/binary >>) ->
  160. whitespace(Rest,
  161. fun (Rest2) ->
  162. accept_ext_attr(Rest2, Fun,
  163. Type, SubType, Params, Quality, Acc)
  164. end);
  165. (Rest) ->
  166. Fun(Rest, {{Type, SubType, lists:reverse(Params)},
  167. Quality, lists:reverse(Acc)})
  168. end).
  169. -spec accept_ext_attr(binary(), fun(), binary(), binary(),
  170. [{binary(), binary()}], 0..1000,
  171. [{binary(), binary()} | binary()]) -> any().
  172. accept_ext_attr(Data, Fun, Type, SubType, Params, Quality, Acc) ->
  173. token_ci(Data,
  174. fun (_Rest, <<>>) -> {error, badarg};
  175. (<< $=, Rest/binary >>, Attr) ->
  176. accept_ext_value(Rest, Fun, Type, SubType, Params,
  177. Quality, Acc, Attr);
  178. (Rest, Attr) ->
  179. accept_ext(Rest, Fun, Type, SubType, Params,
  180. Quality, [Attr|Acc])
  181. end).
  182. -spec accept_ext_value(binary(), fun(), binary(), binary(),
  183. [{binary(), binary()}], 0..1000,
  184. [{binary(), binary()} | binary()], binary()) -> any().
  185. accept_ext_value(Data, Fun, Type, SubType, Params, Quality, Acc, Attr) ->
  186. word(Data,
  187. fun (Rest, Value) ->
  188. accept_ext(Rest, Fun,
  189. Type, SubType, Params, Quality, [{Attr, Value}|Acc])
  190. end).
  191. %% @doc Parse a conneg header (Accept-Charset, Accept-Encoding),
  192. %% followed by an optional quality value.
  193. -spec conneg(binary(), fun()) -> any().
  194. conneg(Data, Fun) ->
  195. token_ci(Data,
  196. fun (_Rest, <<>>) -> {error, badarg};
  197. (Rest, Conneg) ->
  198. maybe_qparam(Rest,
  199. fun (Rest2, Quality) ->
  200. Fun(Rest2, {Conneg, Quality})
  201. end)
  202. end).
  203. %% @doc Parse a language range, followed by an optional quality value.
  204. -spec language_range(binary(), fun()) -> any().
  205. language_range(<< $*, Rest/binary >>, Fun) ->
  206. language_range_ret(Rest, Fun, '*');
  207. language_range(Data, Fun) ->
  208. language_tag(Data,
  209. fun (Rest, LanguageTag) ->
  210. language_range_ret(Rest, Fun, LanguageTag)
  211. end).
  212. -spec language_range_ret(binary(), fun(), '*' | {binary(), [binary()]}) -> any().
  213. language_range_ret(Data, Fun, LanguageTag) ->
  214. maybe_qparam(Data,
  215. fun (Rest, Quality) ->
  216. Fun(Rest, {LanguageTag, Quality})
  217. end).
  218. -spec language_tag(binary(), fun()) -> any().
  219. language_tag(Data, Fun) ->
  220. alpha(Data,
  221. fun (_Rest, Tag) when byte_size(Tag) =:= 0; byte_size(Tag) > 8 ->
  222. {error, badarg};
  223. (<< $-, Rest/binary >>, Tag) ->
  224. language_subtag(Rest, Fun, Tag, []);
  225. (Rest, Tag) ->
  226. Fun(Rest, Tag)
  227. end).
  228. -spec language_subtag(binary(), fun(), binary(), [binary()]) -> any().
  229. language_subtag(Data, Fun, Tag, Acc) ->
  230. alpha(Data,
  231. fun (_Rest, SubTag) when byte_size(SubTag) =:= 0;
  232. byte_size(SubTag) > 8 -> {error, badarg};
  233. (<< $-, Rest/binary >>, SubTag) ->
  234. language_subtag(Rest, Fun, Tag, [SubTag|Acc]);
  235. (Rest, SubTag) ->
  236. %% Rebuild the full tag now that we know it's correct
  237. Sub = << << $-, S/binary >> || S <- lists:reverse([SubTag|Acc]) >>,
  238. Fun(Rest, << Tag/binary, Sub/binary >>)
  239. end).
  240. -spec maybe_qparam(binary(), fun()) -> any().
  241. maybe_qparam(Data, Fun) ->
  242. whitespace(Data,
  243. fun (<< $;, Rest/binary >>) ->
  244. whitespace(Rest,
  245. fun (Rest2) ->
  246. %% This is a non-strict parsing clause required by some user agents
  247. %% that use the wrong delimiter putting a charset where a qparam is
  248. %% expected.
  249. try qparam(Rest2, Fun) of
  250. Result -> Result
  251. catch
  252. error:function_clause ->
  253. Fun(<<",", Rest2/binary>>, 1000)
  254. end
  255. end);
  256. (Rest) ->
  257. Fun(Rest, 1000)
  258. end).
  259. %% @doc Parse a quality parameter string (for example q=0.500).
  260. -spec qparam(binary(), fun()) -> any().
  261. qparam(<< Q, $=, Data/binary >>, Fun) when Q =:= $q; Q =:= $Q ->
  262. qvalue(Data, Fun).
  263. %% @doc Parse either a list of entity tags or a "*".
  264. -spec entity_tag_match(binary()) -> any().
  265. entity_tag_match(<< $*, Rest/binary >>) ->
  266. whitespace(Rest,
  267. fun (<<>>) -> '*';
  268. (_Any) -> {error, badarg}
  269. end);
  270. entity_tag_match(Data) ->
  271. nonempty_list(Data, fun entity_tag/2).
  272. %% @doc Parse an entity-tag.
  273. -spec entity_tag(binary(), fun()) -> any().
  274. entity_tag(<< "W/", Rest/binary >>, Fun) ->
  275. opaque_tag(Rest, Fun, weak);
  276. entity_tag(Data, Fun) ->
  277. opaque_tag(Data, Fun, strong).
  278. -spec opaque_tag(binary(), fun(), weak | strong) -> any().
  279. opaque_tag(Data, Fun, Strength) ->
  280. quoted_string(Data,
  281. fun (_Rest, <<>>) -> {error, badarg};
  282. (Rest, OpaqueTag) -> Fun(Rest, {Strength, OpaqueTag})
  283. end).
  284. %% @doc Parse an expectation.
  285. -spec expectation(binary(), fun()) -> any().
  286. expectation(Data, Fun) ->
  287. token_ci(Data,
  288. fun (_Rest, <<>>) -> {error, badarg};
  289. (<< $=, Rest/binary >>, Expectation) ->
  290. word(Rest,
  291. fun (Rest2, ExtValue) ->
  292. params(Rest2, fun (Rest3, ExtParams) ->
  293. Fun(Rest3, {Expectation, ExtValue, ExtParams})
  294. end)
  295. end);
  296. (Rest, Expectation) ->
  297. Fun(Rest, Expectation)
  298. end).
  299. %% @doc Parse a list of parameters (a=b;c=d).
  300. -spec params(binary(), fun()) -> any().
  301. params(Data, Fun) ->
  302. params(Data, Fun, []).
  303. -spec params(binary(), fun(), [{binary(), binary()}]) -> any().
  304. params(Data, Fun, Acc) ->
  305. whitespace(Data,
  306. fun (<< $;, Rest/binary >>) -> param(Rest, Fun, Acc);
  307. (Rest) -> Fun(Rest, lists:reverse(Acc))
  308. end).
  309. -spec param(binary(), fun(), [{binary(), binary()}]) -> any().
  310. param(Data, Fun, Acc) ->
  311. whitespace(Data,
  312. fun (Rest) ->
  313. token_ci(Rest,
  314. fun (_Rest2, <<>>) -> {error, badarg};
  315. (<< $=, Rest2/binary >>, Attr) ->
  316. word(Rest2,
  317. fun (Rest3, Value) ->
  318. params(Rest3, Fun,
  319. [{Attr, Value}|Acc])
  320. end);
  321. (_Rest2, _Attr) -> {error, badarg}
  322. end)
  323. end).
  324. %% @doc Parse an HTTP date (RFC1123, RFC850 or asctime date).
  325. %% @end
  326. %%
  327. %% While this may not be the most efficient date parsing we can do,
  328. %% it should work fine for our purposes because all HTTP dates should
  329. %% be sent as RFC1123 dates in HTTP/1.1.
  330. -spec http_date(binary()) -> any().
  331. http_date(Data) ->
  332. case rfc1123_date(Data) of
  333. {error, badarg} ->
  334. case rfc850_date(Data) of
  335. {error, badarg} ->
  336. case asctime_date(Data) of
  337. {error, badarg} ->
  338. {error, badarg};
  339. HTTPDate ->
  340. HTTPDate
  341. end;
  342. HTTPDate ->
  343. HTTPDate
  344. end;
  345. HTTPDate ->
  346. HTTPDate
  347. end.
  348. %% @doc Parse an RFC1123 date.
  349. -spec rfc1123_date(binary()) -> any().
  350. rfc1123_date(Data) ->
  351. wkday(Data,
  352. fun (<< ", ", Rest/binary >>, _WkDay) ->
  353. date1(Rest,
  354. fun (<< " ", Rest2/binary >>, Date) ->
  355. time(Rest2,
  356. fun (<< " GMT", Rest3/binary >>, Time) ->
  357. http_date_ret(Rest3, {Date, Time});
  358. (_Any, _Time) ->
  359. {error, badarg}
  360. end);
  361. (_Any, _Date) ->
  362. {error, badarg}
  363. end);
  364. (_Any, _WkDay) ->
  365. {error, badarg}
  366. end).
  367. %% @doc Parse an RFC850 date.
  368. -spec rfc850_date(binary()) -> any().
  369. %% From the RFC:
  370. %% HTTP/1.1 clients and caches SHOULD assume that an RFC-850 date
  371. %% which appears to be more than 50 years in the future is in fact
  372. %% in the past (this helps solve the "year 2000" problem).
  373. rfc850_date(Data) ->
  374. weekday(Data,
  375. fun (<< ", ", Rest/binary >>, _WeekDay) ->
  376. date2(Rest,
  377. fun (<< " ", Rest2/binary >>, Date) ->
  378. time(Rest2,
  379. fun (<< " GMT", Rest3/binary >>, Time) ->
  380. http_date_ret(Rest3, {Date, Time});
  381. (_Any, _Time) ->
  382. {error, badarg}
  383. end);
  384. (_Any, _Date) ->
  385. {error, badarg}
  386. end);
  387. (_Any, _WeekDay) ->
  388. {error, badarg}
  389. end).
  390. %% @doc Parse an asctime date.
  391. -spec asctime_date(binary()) -> any().
  392. asctime_date(Data) ->
  393. wkday(Data,
  394. fun (<< " ", Rest/binary >>, _WkDay) ->
  395. date3(Rest,
  396. fun (<< " ", Rest2/binary >>, PartialDate) ->
  397. time(Rest2,
  398. fun (<< " ", Rest3/binary >>, Time) ->
  399. asctime_year(Rest3,
  400. PartialDate, Time);
  401. (_Any, _Time) ->
  402. {error, badarg}
  403. end);
  404. (_Any, _PartialDate) ->
  405. {error, badarg}
  406. end);
  407. (_Any, _WkDay) ->
  408. {error, badarg1}
  409. end).
  410. -spec asctime_year(binary(), tuple(), tuple()) -> any().
  411. asctime_year(<< Y1, Y2, Y3, Y4, Rest/binary >>, {Month, Day}, Time)
  412. when Y1 >= $0, Y1 =< $9, Y2 >= $0, Y2 =< $9,
  413. Y3 >= $0, Y3 =< $9, Y4 >= $0, Y4 =< $9 ->
  414. Year = (Y1 - $0) * 1000 + (Y2 - $0) * 100 + (Y3 - $0) * 10 + (Y4 - $0),
  415. http_date_ret(Rest, {{Year, Month, Day}, Time}).
  416. -spec http_date_ret(binary(), tuple()) -> any().
  417. http_date_ret(Data, DateTime = {Date, _Time}) ->
  418. whitespace(Data,
  419. fun (<<>>) ->
  420. case calendar:valid_date(Date) of
  421. true -> DateTime;
  422. false -> {error, badarg}
  423. end;
  424. (_Any) ->
  425. {error, badarg}
  426. end).
  427. %% We never use it, pretty much just checks the wkday is right.
  428. -spec wkday(binary(), fun()) -> any().
  429. wkday(<< WkDay:3/binary, Rest/binary >>, Fun)
  430. when WkDay =:= <<"Mon">>; WkDay =:= <<"Tue">>; WkDay =:= <<"Wed">>;
  431. WkDay =:= <<"Thu">>; WkDay =:= <<"Fri">>; WkDay =:= <<"Sat">>;
  432. WkDay =:= <<"Sun">> ->
  433. Fun(Rest, WkDay);
  434. wkday(_Any, _Fun) ->
  435. {error, badarg}.
  436. %% We never use it, pretty much just checks the weekday is right.
  437. -spec weekday(binary(), fun()) -> any().
  438. weekday(<< "Monday", Rest/binary >>, Fun) ->
  439. Fun(Rest, <<"Monday">>);
  440. weekday(<< "Tuesday", Rest/binary >>, Fun) ->
  441. Fun(Rest, <<"Tuesday">>);
  442. weekday(<< "Wednesday", Rest/binary >>, Fun) ->
  443. Fun(Rest, <<"Wednesday">>);
  444. weekday(<< "Thursday", Rest/binary >>, Fun) ->
  445. Fun(Rest, <<"Thursday">>);
  446. weekday(<< "Friday", Rest/binary >>, Fun) ->
  447. Fun(Rest, <<"Friday">>);
  448. weekday(<< "Saturday", Rest/binary >>, Fun) ->
  449. Fun(Rest, <<"Saturday">>);
  450. weekday(<< "Sunday", Rest/binary >>, Fun) ->
  451. Fun(Rest, <<"Sunday">>);
  452. weekday(_Any, _Fun) ->
  453. {error, badarg}.
  454. -spec date1(binary(), fun()) -> any().
  455. date1(<< D1, D2, " ", M:3/binary, " ", Y1, Y2, Y3, Y4, Rest/binary >>, Fun)
  456. when D1 >= $0, D1 =< $9, D2 >= $0, D2 =< $9,
  457. Y1 >= $0, Y1 =< $9, Y2 >= $0, Y2 =< $9,
  458. Y3 >= $0, Y3 =< $9, Y4 >= $0, Y4 =< $9 ->
  459. case month(M) of
  460. {error, badarg} ->
  461. {error, badarg};
  462. Month ->
  463. Fun(Rest, {
  464. (Y1 - $0) * 1000 + (Y2 - $0) * 100 + (Y3 - $0) * 10 + (Y4 - $0),
  465. Month,
  466. (D1 - $0) * 10 + (D2 - $0)
  467. })
  468. end;
  469. date1(_Data, _Fun) ->
  470. {error, badarg}.
  471. -spec date2(binary(), fun()) -> any().
  472. date2(<< D1, D2, "-", M:3/binary, "-", Y1, Y2, Rest/binary >>, Fun)
  473. when D1 >= $0, D1 =< $9, D2 >= $0, D2 =< $9,
  474. Y1 >= $0, Y1 =< $9, Y2 >= $0, Y2 =< $9 ->
  475. case month(M) of
  476. {error, badarg} ->
  477. {error, badarg};
  478. Month ->
  479. Year = (Y1 - $0) * 10 + (Y2 - $0),
  480. Year2 = case Year > 50 of
  481. true -> Year + 1900;
  482. false -> Year + 2000
  483. end,
  484. Fun(Rest, {
  485. Year2,
  486. Month,
  487. (D1 - $0) * 10 + (D2 - $0)
  488. })
  489. end;
  490. date2(_Data, _Fun) ->
  491. {error, badarg}.
  492. -spec date3(binary(), fun()) -> any().
  493. date3(<< M:3/binary, " ", D1, D2, Rest/binary >>, Fun)
  494. when (D1 >= $0 andalso D1 =< $3) orelse D1 =:= $\s,
  495. D2 >= $0, D2 =< $9 ->
  496. case month(M) of
  497. {error, badarg} ->
  498. {error, badarg};
  499. Month ->
  500. Day = case D1 of
  501. $\s -> D2 - $0;
  502. D1 -> (D1 - $0) * 10 + (D2 - $0)
  503. end,
  504. Fun(Rest, {Month, Day})
  505. end;
  506. date3(_Data, _Fun) ->
  507. {error, badarg}.
  508. -spec month(<< _:24 >>) -> 1..12 | {error, badarg}.
  509. month(<<"Jan">>) -> 1;
  510. month(<<"Feb">>) -> 2;
  511. month(<<"Mar">>) -> 3;
  512. month(<<"Apr">>) -> 4;
  513. month(<<"May">>) -> 5;
  514. month(<<"Jun">>) -> 6;
  515. month(<<"Jul">>) -> 7;
  516. month(<<"Aug">>) -> 8;
  517. month(<<"Sep">>) -> 9;
  518. month(<<"Oct">>) -> 10;
  519. month(<<"Nov">>) -> 11;
  520. month(<<"Dec">>) -> 12;
  521. month(_Any) -> {error, badarg}.
  522. -spec time(binary(), fun()) -> any().
  523. time(<< H1, H2, ":", M1, M2, ":", S1, S2, Rest/binary >>, Fun)
  524. when H1 >= $0, H1 =< $2, H2 >= $0, H2 =< $9,
  525. M1 >= $0, M1 =< $5, M2 >= $0, M2 =< $9,
  526. S1 >= $0, S1 =< $5, S2 >= $0, S2 =< $9 ->
  527. Hour = (H1 - $0) * 10 + (H2 - $0),
  528. case Hour < 24 of
  529. true ->
  530. Time = {
  531. Hour,
  532. (M1 - $0) * 10 + (M2 - $0),
  533. (S1 - $0) * 10 + (S2 - $0)
  534. },
  535. Fun(Rest, Time);
  536. false ->
  537. {error, badarg}
  538. end.
  539. %% @doc Skip whitespace.
  540. -spec whitespace(binary(), fun()) -> any().
  541. whitespace(<< C, Rest/binary >>, Fun)
  542. when C =:= $\s; C =:= $\t ->
  543. whitespace(Rest, Fun);
  544. whitespace(Data, Fun) ->
  545. Fun(Data).
  546. %% @doc Parse a list of digits as a non negative integer.
  547. -spec digits(binary()) -> non_neg_integer() | {error, badarg}.
  548. digits(Data) ->
  549. digits(Data,
  550. fun (Rest, I) ->
  551. whitespace(Rest,
  552. fun (<<>>) ->
  553. I;
  554. (_Rest2) ->
  555. {error, badarg}
  556. end)
  557. end).
  558. -spec digits(binary(), fun()) -> any().
  559. digits(<< C, Rest/binary >>, Fun)
  560. when C >= $0, C =< $9 ->
  561. digits(Rest, Fun, C - $0);
  562. digits(_Data, _Fun) ->
  563. {error, badarg}.
  564. -spec digits(binary(), fun(), non_neg_integer()) -> any().
  565. digits(<< C, Rest/binary >>, Fun, Acc)
  566. when C >= $0, C =< $9 ->
  567. digits(Rest, Fun, Acc * 10 + (C - $0));
  568. digits(Data, Fun, Acc) ->
  569. Fun(Data, Acc).
  570. %% @doc Parse a list of case-insensitive alpha characters.
  571. %%
  572. %% Changes all characters to lowercase.
  573. -spec alpha(binary(), fun()) -> any().
  574. alpha(Data, Fun) ->
  575. alpha(Data, Fun, <<>>).
  576. -spec alpha(binary(), fun(), binary()) -> any().
  577. alpha(<<>>, Fun, Acc) ->
  578. Fun(<<>>, Acc);
  579. alpha(<< C, Rest/binary >>, Fun, Acc)
  580. when C >= $a andalso C =< $z;
  581. C >= $A andalso C =< $Z ->
  582. C2 = cowboy_bstr:char_to_lower(C),
  583. alpha(Rest, Fun, << Acc/binary, C2 >>);
  584. alpha(Data, Fun, Acc) ->
  585. Fun(Data, Acc).
  586. %% @doc Parse either a token or a quoted string.
  587. -spec word(binary(), fun()) -> any().
  588. word(Data = << $", _/binary >>, Fun) ->
  589. quoted_string(Data, Fun);
  590. word(Data, Fun) ->
  591. token(Data,
  592. fun (_Rest, <<>>) -> {error, badarg};
  593. (Rest, Token) -> Fun(Rest, Token)
  594. end).
  595. %% @doc Parse a case-insensitive token.
  596. %%
  597. %% Changes all characters to lowercase.
  598. -spec token_ci(binary(), fun()) -> any().
  599. token_ci(Data, Fun) ->
  600. token(Data, Fun, ci, <<>>).
  601. %% @doc Parse a token.
  602. -spec token(binary(), fun()) -> any().
  603. token(Data, Fun) ->
  604. token(Data, Fun, cs, <<>>).
  605. -spec token(binary(), fun(), ci | cs, binary()) -> any().
  606. token(<<>>, Fun, _Case, Acc) ->
  607. Fun(<<>>, Acc);
  608. token(Data = << C, _Rest/binary >>, Fun, _Case, Acc)
  609. when C =:= $(; C =:= $); C =:= $<; C =:= $>; C =:= $@;
  610. C =:= $,; C =:= $;; C =:= $:; C =:= $\\; C =:= $";
  611. C =:= $/; C =:= $[; C =:= $]; C =:= $?; C =:= $=;
  612. C =:= ${; C =:= $}; C =:= $\s; C =:= $\t;
  613. C < 32; C =:= 127 ->
  614. Fun(Data, Acc);
  615. token(<< C, Rest/binary >>, Fun, Case = ci, Acc) ->
  616. C2 = cowboy_bstr:char_to_lower(C),
  617. token(Rest, Fun, Case, << Acc/binary, C2 >>);
  618. token(<< C, Rest/binary >>, Fun, Case, Acc) ->
  619. token(Rest, Fun, Case, << Acc/binary, C >>).
  620. %% @doc Parse a quoted string.
  621. -spec quoted_string(binary(), fun()) -> any().
  622. quoted_string(<< $", Rest/binary >>, Fun) ->
  623. quoted_string(Rest, Fun, <<>>).
  624. -spec quoted_string(binary(), fun(), binary()) -> any().
  625. quoted_string(<<>>, _Fun, _Acc) ->
  626. {error, badarg};
  627. quoted_string(<< $", Rest/binary >>, Fun, Acc) ->
  628. Fun(Rest, Acc);
  629. quoted_string(<< $\\, C, Rest/binary >>, Fun, Acc) ->
  630. quoted_string(Rest, Fun, << Acc/binary, C >>);
  631. quoted_string(<< C, Rest/binary >>, Fun, Acc) ->
  632. quoted_string(Rest, Fun, << Acc/binary, C >>).
  633. %% @doc Parse a quality value.
  634. -spec qvalue(binary(), fun()) -> any().
  635. qvalue(<< $0, $., Rest/binary >>, Fun) ->
  636. qvalue(Rest, Fun, 0, 100);
  637. %% Some user agents use q=.x instead of q=0.x
  638. qvalue(<< $., Rest/binary >>, Fun) ->
  639. qvalue(Rest, Fun, 0, 100);
  640. qvalue(<< $0, Rest/binary >>, Fun) ->
  641. Fun(Rest, 0);
  642. qvalue(<< $1, $., $0, $0, $0, Rest/binary >>, Fun) ->
  643. Fun(Rest, 1000);
  644. qvalue(<< $1, $., $0, $0, Rest/binary >>, Fun) ->
  645. Fun(Rest, 1000);
  646. qvalue(<< $1, $., $0, Rest/binary >>, Fun) ->
  647. Fun(Rest, 1000);
  648. qvalue(<< $1, Rest/binary >>, Fun) ->
  649. Fun(Rest, 1000);
  650. qvalue(_Data, _Fun) ->
  651. {error, badarg}.
  652. -spec qvalue(binary(), fun(), integer(), 1 | 10 | 100) -> any().
  653. qvalue(Data, Fun, Q, 0) ->
  654. Fun(Data, Q);
  655. qvalue(<< C, Rest/binary >>, Fun, Q, M)
  656. when C >= $0, C =< $9 ->
  657. qvalue(Rest, Fun, Q + (C - $0) * M, M div 10);
  658. qvalue(Data, Fun, Q, _M) ->
  659. Fun(Data, Q).
  660. %% Decoding.
  661. %% @doc Decode a stream of chunks.
  662. -spec te_chunked(binary(), {non_neg_integer(), non_neg_integer()})
  663. -> more | {ok, binary(), {non_neg_integer(), non_neg_integer()}}
  664. | {ok, binary(), binary(), {non_neg_integer(), non_neg_integer()}}
  665. | {done, non_neg_integer(), binary()} | {error, badarg}.
  666. te_chunked(<<>>, _) ->
  667. more;
  668. te_chunked(<< "0\r\n\r\n", Rest/binary >>, {0, Streamed}) ->
  669. {done, Streamed, Rest};
  670. te_chunked(Data, {0, Streamed}) ->
  671. %% @todo We are expecting an hex size, not a general token.
  672. token(Data,
  673. fun (Rest, _) when byte_size(Rest) < 4 ->
  674. more;
  675. (<< "\r\n", Rest/binary >>, BinLen) ->
  676. Len = list_to_integer(binary_to_list(BinLen), 16),
  677. te_chunked(Rest, {Len, Streamed});
  678. (_, _) ->
  679. {error, badarg}
  680. end);
  681. te_chunked(Data, {ChunkRem, Streamed}) when byte_size(Data) >= ChunkRem + 2 ->
  682. << Chunk:ChunkRem/binary, "\r\n", Rest/binary >> = Data,
  683. {ok, Chunk, Rest, {0, Streamed + byte_size(Chunk)}};
  684. te_chunked(Data, {ChunkRem, Streamed}) ->
  685. Size = byte_size(Data),
  686. {ok, Data, {ChunkRem - Size, Streamed + Size}}.
  687. %% @doc Decode an identity stream.
  688. -spec te_identity(binary(), {non_neg_integer(), non_neg_integer()})
  689. -> {ok, binary(), {non_neg_integer(), non_neg_integer()}}
  690. | {done, binary(), non_neg_integer(), binary()}.
  691. te_identity(Data, {Streamed, Total})
  692. when Streamed + byte_size(Data) < Total ->
  693. {ok, Data, {Streamed + byte_size(Data), Total}};
  694. te_identity(Data, {Streamed, Total}) ->
  695. Size = Total - Streamed,
  696. << Data2:Size/binary, Rest/binary >> = Data,
  697. {done, Data2, Total, Rest}.
  698. %% @doc Decode an identity content.
  699. -spec ce_identity(binary()) -> {ok, binary()}.
  700. ce_identity(Data) ->
  701. {ok, Data}.
  702. %% Interpretation.
  703. %% @doc Walk through a tokens list and return whether
  704. %% the connection is keepalive or closed.
  705. %%
  706. %% The connection token is expected to be lower-case.
  707. -spec connection_to_atom([binary()]) -> keepalive | close.
  708. connection_to_atom([]) ->
  709. keepalive;
  710. connection_to_atom([<<"keep-alive">>|_Tail]) ->
  711. keepalive;
  712. connection_to_atom([<<"close">>|_Tail]) ->
  713. close;
  714. connection_to_atom([_Any|Tail]) ->
  715. connection_to_atom(Tail).
  716. %% @doc Decode a URL encoded binary.
  717. %% @equiv urldecode(Bin, crash)
  718. -spec urldecode(binary()) -> binary().
  719. urldecode(Bin) when is_binary(Bin) ->
  720. urldecode(Bin, <<>>, crash).
  721. %% @doc Decode a URL encoded binary.
  722. %% The second argument specifies how to handle percent characters that are not
  723. %% followed by two valid hex characters. Use `skip' to ignore such errors,
  724. %% if `crash' is used the function will fail with the reason `badarg'.
  725. -spec urldecode(binary(), crash | skip) -> binary().
  726. urldecode(Bin, OnError) when is_binary(Bin) ->
  727. urldecode(Bin, <<>>, OnError).
  728. -spec urldecode(binary(), binary(), crash | skip) -> binary().
  729. urldecode(<<$%, H, L, Rest/binary>>, Acc, OnError) ->
  730. G = unhex(H),
  731. M = unhex(L),
  732. if G =:= error; M =:= error ->
  733. case OnError of skip -> ok; crash -> erlang:error(badarg) end,
  734. urldecode(<<H, L, Rest/binary>>, <<Acc/binary, $%>>, OnError);
  735. true ->
  736. urldecode(Rest, <<Acc/binary, (G bsl 4 bor M)>>, OnError)
  737. end;
  738. urldecode(<<$%, Rest/binary>>, Acc, OnError) ->
  739. case OnError of skip -> ok; crash -> erlang:error(badarg) end,
  740. urldecode(Rest, <<Acc/binary, $%>>, OnError);
  741. urldecode(<<$+, Rest/binary>>, Acc, OnError) ->
  742. urldecode(Rest, <<Acc/binary, $ >>, OnError);
  743. urldecode(<<C, Rest/binary>>, Acc, OnError) ->
  744. urldecode(Rest, <<Acc/binary, C>>, OnError);
  745. urldecode(<<>>, Acc, _OnError) ->
  746. Acc.
  747. -spec unhex(byte()) -> byte() | error.
  748. unhex(C) when C >= $0, C =< $9 -> C - $0;
  749. unhex(C) when C >= $A, C =< $F -> C - $A + 10;
  750. unhex(C) when C >= $a, C =< $f -> C - $a + 10;
  751. unhex(_) -> error.
  752. %% @doc URL encode a string binary.
  753. %% @equiv urlencode(Bin, [])
  754. -spec urlencode(binary()) -> binary().
  755. urlencode(Bin) ->
  756. urlencode(Bin, []).
  757. %% @doc URL encode a string binary.
  758. %% The `noplus' option disables the default behaviour of quoting space
  759. %% characters, `\s', as `+'. The `upper' option overrides the default behaviour
  760. %% of writing hex numbers using lowecase letters to using uppercase letters
  761. %% instead.
  762. -spec urlencode(binary(), [noplus|upper]) -> binary().
  763. urlencode(Bin, Opts) ->
  764. Plus = not proplists:get_value(noplus, Opts, false),
  765. Upper = proplists:get_value(upper, Opts, false),
  766. urlencode(Bin, <<>>, Plus, Upper).
  767. -spec urlencode(binary(), binary(), boolean(), boolean()) -> binary().
  768. urlencode(<<C, Rest/binary>>, Acc, P=Plus, U=Upper) ->
  769. if C >= $0, C =< $9 -> urlencode(Rest, <<Acc/binary, C>>, P, U);
  770. C >= $A, C =< $Z -> urlencode(Rest, <<Acc/binary, C>>, P, U);
  771. C >= $a, C =< $z -> urlencode(Rest, <<Acc/binary, C>>, P, U);
  772. C =:= $.; C =:= $-; C =:= $~; C =:= $_ ->
  773. urlencode(Rest, <<Acc/binary, C>>, P, U);
  774. C =:= $ , Plus ->
  775. urlencode(Rest, <<Acc/binary, $+>>, P, U);
  776. true ->
  777. H = C band 16#F0 bsr 4, L = C band 16#0F,
  778. H1 = if Upper -> tohexu(H); true -> tohexl(H) end,
  779. L1 = if Upper -> tohexu(L); true -> tohexl(L) end,
  780. urlencode(Rest, <<Acc/binary, $%, H1, L1>>, P, U)
  781. end;
  782. urlencode(<<>>, Acc, _Plus, _Upper) ->
  783. Acc.
  784. -spec tohexu(byte()) -> byte().
  785. tohexu(C) when C < 10 -> $0 + C;
  786. tohexu(C) when C < 17 -> $A + C - 10.
  787. -spec tohexl(byte()) -> byte().
  788. tohexl(C) when C < 10 -> $0 + C;
  789. tohexl(C) when C < 17 -> $a + C - 10.
  790. -spec x_www_form_urlencoded(binary(), fun((binary()) -> binary())) ->
  791. list({binary(), binary() | true}).
  792. x_www_form_urlencoded(<<>>, _URLDecode) ->
  793. [];
  794. x_www_form_urlencoded(Qs, URLDecode) ->
  795. Tokens = binary:split(Qs, <<"&">>, [global, trim]),
  796. [case binary:split(Token, <<"=">>) of
  797. [Token] -> {URLDecode(Token), true};
  798. [Name, Value] -> {URLDecode(Name), URLDecode(Value)}
  799. end || Token <- Tokens].
  800. %% Tests.
  801. -ifdef(TEST).
  802. nonempty_charset_list_test_() ->
  803. %% {Value, Result}
  804. Tests = [
  805. {<<>>, {error, badarg}},
  806. {<<"iso-8859-5, unicode-1-1;q=0.8">>, [
  807. {<<"iso-8859-5">>, 1000},
  808. {<<"unicode-1-1">>, 800}
  809. ]},
  810. %% Some user agents send this invalid value for the Accept-Charset header
  811. {<<"ISO-8859-1;utf-8;q=0.7,*;q=0.7">>, [
  812. {<<"iso-8859-1">>, 1000},
  813. {<<"utf-8">>, 700},
  814. {<<"*">>, 700}
  815. ]}
  816. ],
  817. [{V, fun() -> R = nonempty_list(V, fun conneg/2) end} || {V, R} <- Tests].
  818. nonempty_language_range_list_test_() ->
  819. %% {Value, Result}
  820. Tests = [
  821. {<<"da, en-gb;q=0.8, en;q=0.7">>, [
  822. {<<"da">>, 1000},
  823. {<<"en-gb">>, 800},
  824. {<<"en">>, 700}
  825. ]},
  826. {<<"en, en-US, en-cockney, i-cherokee, x-pig-latin">>, [
  827. {<<"en">>, 1000},
  828. {<<"en-us">>, 1000},
  829. {<<"en-cockney">>, 1000},
  830. {<<"i-cherokee">>, 1000},
  831. {<<"x-pig-latin">>, 1000}
  832. ]}
  833. ],
  834. [{V, fun() -> R = nonempty_list(V, fun language_range/2) end}
  835. || {V, R} <- Tests].
  836. nonempty_token_list_test_() ->
  837. %% {Value, Result}
  838. Tests = [
  839. {<<>>, {error, badarg}},
  840. {<<" ">>, {error, badarg}},
  841. {<<" , ">>, {error, badarg}},
  842. {<<",,,">>, {error, badarg}},
  843. {<<"a b">>, {error, badarg}},
  844. {<<"a , , , ">>, [<<"a">>]},
  845. {<<" , , , a">>, [<<"a">>]},
  846. {<<"a, , b">>, [<<"a">>, <<"b">>]},
  847. {<<"close">>, [<<"close">>]},
  848. {<<"keep-alive, upgrade">>, [<<"keep-alive">>, <<"upgrade">>]}
  849. ],
  850. [{V, fun() -> R = nonempty_list(V, fun token/2) end} || {V, R} <- Tests].
  851. media_range_list_test_() ->
  852. %% {Tokens, Result}
  853. Tests = [
  854. {<<"audio/*; q=0.2, audio/basic">>, [
  855. {{<<"audio">>, <<"*">>, []}, 200, []},
  856. {{<<"audio">>, <<"basic">>, []}, 1000, []}
  857. ]},
  858. {<<"text/plain; q=0.5, text/html, "
  859. "text/x-dvi; q=0.8, text/x-c">>, [
  860. {{<<"text">>, <<"plain">>, []}, 500, []},
  861. {{<<"text">>, <<"html">>, []}, 1000, []},
  862. {{<<"text">>, <<"x-dvi">>, []}, 800, []},
  863. {{<<"text">>, <<"x-c">>, []}, 1000, []}
  864. ]},
  865. {<<"text/*, text/html, text/html;level=1, */*">>, [
  866. {{<<"text">>, <<"*">>, []}, 1000, []},
  867. {{<<"text">>, <<"html">>, []}, 1000, []},
  868. {{<<"text">>, <<"html">>, [{<<"level">>, <<"1">>}]}, 1000, []},
  869. {{<<"*">>, <<"*">>, []}, 1000, []}
  870. ]},
  871. {<<"text/*;q=0.3, text/html;q=0.7, text/html;level=1, "
  872. "text/html;level=2;q=0.4, */*;q=0.5">>, [
  873. {{<<"text">>, <<"*">>, []}, 300, []},
  874. {{<<"text">>, <<"html">>, []}, 700, []},
  875. {{<<"text">>, <<"html">>, [{<<"level">>, <<"1">>}]}, 1000, []},
  876. {{<<"text">>, <<"html">>, [{<<"level">>, <<"2">>}]}, 400, []},
  877. {{<<"*">>, <<"*">>, []}, 500, []}
  878. ]},
  879. {<<"text/html;level=1;quoted=\"hi hi hi\";"
  880. "q=0.123;standalone;complex=gits, text/plain">>, [
  881. {{<<"text">>, <<"html">>,
  882. [{<<"level">>, <<"1">>}, {<<"quoted">>, <<"hi hi hi">>}]}, 123,
  883. [<<"standalone">>, {<<"complex">>, <<"gits">>}]},
  884. {{<<"text">>, <<"plain">>, []}, 1000, []}
  885. ]},
  886. {<<"text/html, image/gif, image/jpeg, *; q=.2, */*; q=.2">>, [
  887. {{<<"text">>, <<"html">>, []}, 1000, []},
  888. {{<<"image">>, <<"gif">>, []}, 1000, []},
  889. {{<<"image">>, <<"jpeg">>, []}, 1000, []},
  890. {{<<"*">>, <<"*">>, []}, 200, []},
  891. {{<<"*">>, <<"*">>, []}, 200, []}
  892. ]}
  893. ],
  894. [{V, fun() -> R = list(V, fun media_range/2) end} || {V, R} <- Tests].
  895. entity_tag_match_test_() ->
  896. %% {Tokens, Result}
  897. Tests = [
  898. {<<"\"xyzzy\"">>, [{strong, <<"xyzzy">>}]},
  899. {<<"\"xyzzy\", W/\"r2d2xxxx\", \"c3piozzzz\"">>,
  900. [{strong, <<"xyzzy">>},
  901. {weak, <<"r2d2xxxx">>},
  902. {strong, <<"c3piozzzz">>}]},
  903. {<<"*">>, '*'}
  904. ],
  905. [{V, fun() -> R = entity_tag_match(V) end} || {V, R} <- Tests].
  906. http_date_test_() ->
  907. %% {Tokens, Result}
  908. Tests = [
  909. {<<"Sun, 06 Nov 1994 08:49:37 GMT">>, {{1994, 11, 6}, {8, 49, 37}}},
  910. {<<"Sunday, 06-Nov-94 08:49:37 GMT">>, {{1994, 11, 6}, {8, 49, 37}}},
  911. {<<"Sun Nov 6 08:49:37 1994">>, {{1994, 11, 6}, {8, 49, 37}}}
  912. ],
  913. [{V, fun() -> R = http_date(V) end} || {V, R} <- Tests].
  914. rfc1123_date_test_() ->
  915. %% {Tokens, Result}
  916. Tests = [
  917. {<<"Sun, 06 Nov 1994 08:49:37 GMT">>, {{1994, 11, 6}, {8, 49, 37}}}
  918. ],
  919. [{V, fun() -> R = rfc1123_date(V) end} || {V, R} <- Tests].
  920. rfc850_date_test_() ->
  921. %% {Tokens, Result}
  922. Tests = [
  923. {<<"Sunday, 06-Nov-94 08:49:37 GMT">>, {{1994, 11, 6}, {8, 49, 37}}}
  924. ],
  925. [{V, fun() -> R = rfc850_date(V) end} || {V, R} <- Tests].
  926. asctime_date_test_() ->
  927. %% {Tokens, Result}
  928. Tests = [
  929. {<<"Sun Nov 6 08:49:37 1994">>, {{1994, 11, 6}, {8, 49, 37}}}
  930. ],
  931. [{V, fun() -> R = asctime_date(V) end} || {V, R} <- Tests].
  932. connection_to_atom_test_() ->
  933. %% {Tokens, Result}
  934. Tests = [
  935. {[<<"close">>], close},
  936. {[<<"keep-alive">>], keepalive},
  937. {[<<"keep-alive">>, <<"upgrade">>], keepalive}
  938. ],
  939. [{lists:flatten(io_lib:format("~p", [T])),
  940. fun() -> R = connection_to_atom(T) end} || {T, R} <- Tests].
  941. content_type_test_() ->
  942. %% {ContentType, Result}
  943. Tests = [
  944. {<<"text/plain; charset=iso-8859-4">>,
  945. {<<"text">>, <<"plain">>, [{<<"charset">>, <<"iso-8859-4">>}]}},
  946. {<<"multipart/form-data \t;Boundary=\"MultipartIsUgly\"">>,
  947. {<<"multipart">>, <<"form-data">>, [
  948. {<<"boundary">>, <<"MultipartIsUgly">>}
  949. ]}},
  950. {<<"foo/bar; one=FirstParam; two=SecondParam">>,
  951. {<<"foo">>, <<"bar">>, [
  952. {<<"one">>, <<"FirstParam">>},
  953. {<<"two">>, <<"SecondParam">>}
  954. ]}}
  955. ],
  956. [{V, fun () -> R = content_type(V) end} || {V, R} <- Tests].
  957. digits_test_() ->
  958. %% {Digits, Result}
  959. Tests = [
  960. {<<"42 ">>, 42},
  961. {<<"69\t">>, 69},
  962. {<<"1337">>, 1337}
  963. ],
  964. [{V, fun() -> R = digits(V) end} || {V, R} <- Tests].
  965. x_www_form_urlencoded_test_() ->
  966. %% {Qs, Result}
  967. Tests = [
  968. {<<"">>, []},
  969. {<<"a=b">>, [{<<"a">>, <<"b">>}]},
  970. {<<"aaa=bbb">>, [{<<"aaa">>, <<"bbb">>}]},
  971. {<<"a&b">>, [{<<"a">>, true}, {<<"b">>, true}]},
  972. {<<"a=b&c&d=e">>, [{<<"a">>, <<"b">>},
  973. {<<"c">>, true}, {<<"d">>, <<"e">>}]},
  974. {<<"a=b=c=d=e&f=g">>, [{<<"a">>, <<"b=c=d=e">>}, {<<"f">>, <<"g">>}]},
  975. {<<"a+b=c+d">>, [{<<"a b">>, <<"c d">>}]}
  976. ],
  977. URLDecode = fun urldecode/1,
  978. [{Qs, fun() -> R = x_www_form_urlencoded(
  979. Qs, URLDecode) end} || {Qs, R} <- Tests].
  980. urldecode_test_() ->
  981. U = fun urldecode/2,
  982. [?_assertEqual(<<" ">>, U(<<"%20">>, crash)),
  983. ?_assertEqual(<<" ">>, U(<<"+">>, crash)),
  984. ?_assertEqual(<<0>>, U(<<"%00">>, crash)),
  985. ?_assertEqual(<<255>>, U(<<"%fF">>, crash)),
  986. ?_assertEqual(<<"123">>, U(<<"123">>, crash)),
  987. ?_assertEqual(<<"%i5">>, U(<<"%i5">>, skip)),
  988. ?_assertEqual(<<"%5">>, U(<<"%5">>, skip)),
  989. ?_assertError(badarg, U(<<"%i5">>, crash)),
  990. ?_assertError(badarg, U(<<"%5">>, crash))
  991. ].
  992. urlencode_test_() ->
  993. U = fun urlencode/2,
  994. [?_assertEqual(<<"%ff%00">>, U(<<255,0>>, [])),
  995. ?_assertEqual(<<"%FF%00">>, U(<<255,0>>, [upper])),
  996. ?_assertEqual(<<"+">>, U(<<" ">>, [])),
  997. ?_assertEqual(<<"%20">>, U(<<" ">>, [noplus])),
  998. ?_assertEqual(<<"aBc">>, U(<<"aBc">>, [])),
  999. ?_assertEqual(<<".-~_">>, U(<<".-~_">>, [])),
  1000. ?_assertEqual(<<"%ff+">>, urlencode(<<255, " ">>))
  1001. ].
  1002. -endif.