1%% Copyright (c) 2015-2018, Loïc Hoguin <essen@ninenines.eu>
2%%
3%% Permission to use, copy, modify, and/or distribute this software for any
4%% purpose with or without fee is hereby granted, provided that the above
5%% copyright notice and this permission notice appear in all copies.
6%%
7%% THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
8%% WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
9%% MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
10%% ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
11%% WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
12%% ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
13%% OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
14
15%% The current implementation is not suitable for use in
16%% intermediaries as the information about headers that
17%% should never be indexed is currently lost.
18
19-module(cow_hpack).
20-dialyzer(no_improper_lists).
21
22-export([init/0]).
23-export([init/1]).
24-export([set_max_size/2]).
25
26-export([decode/1]).
27-export([decode/2]).
28
29-export([encode/1]).
30-export([encode/2]).
31-export([encode/3]).
32
33-record(state, {
34	size = 0 :: non_neg_integer(),
35	max_size = 4096 :: non_neg_integer(),
36	configured_max_size = 4096 :: non_neg_integer(),
37	dyn_table = [] :: [{pos_integer(), {binary(), binary()}}]
38}).
39
40-opaque state() :: #state{}.
41-export_type([state/0]).
42
43-type opts() :: map().
44-export_type([opts/0]).
45
46-ifdef(TEST).
47-include_lib("proper/include/proper.hrl").
48-endif.
49
50%% State initialization.
51
52-spec init() -> state().
53init() ->
54	#state{}.
55
56-spec init(non_neg_integer()) -> state().
57init(MaxSize) ->
58	#state{max_size=MaxSize, configured_max_size=MaxSize}.
59
60%% Update the configured max size.
61%%
62%% When decoding, the local endpoint also needs to send a SETTINGS
63%% frame with this value and it is then up to the remote endpoint
64%% to decide what actual limit it will use. The actual limit is
65%% signaled via dynamic table size updates in the encoded data.
66%%
67%% When encoding, the local endpoint will call this function after
68%% receiving a SETTINGS frame with this value. The encoder will
69%% then use this value as the new max after signaling via a dynamic
70%% table size update. The value given as argument may be lower
71%% than the one received in the SETTINGS.
72
73-spec set_max_size(non_neg_integer(), State) -> State when State::state().
74set_max_size(MaxSize, State) ->
75	State#state{configured_max_size=MaxSize}.
76
77%% Decoding.
78
79-spec decode(binary()) -> {cow_http:headers(), state()}.
80decode(Data) ->
81	decode(Data, init()).
82
83-spec decode(binary(), State) -> {cow_http:headers(), State} when State::state().
84%% Dynamic table size update is only allowed at the beginning of a HEADERS block.
85decode(<< 0:2, 1:1, Rest/bits >>, State=#state{configured_max_size=ConfigMaxSize}) ->
86	{MaxSize, Rest2} = dec_int5(Rest),
87	if
88		MaxSize =< ConfigMaxSize ->
89			State2 = table_update_size(MaxSize, State),
90			decode(Rest2, State2)
91	end;
92decode(Data, State) ->
93	decode(Data, State, []).
94
95decode(<<>>, State, Acc) ->
96	{lists:reverse(Acc), State};
97%% Indexed header field representation.
98decode(<< 1:1, Rest/bits >>, State, Acc) ->
99	dec_indexed(Rest, State, Acc);
100%% Literal header field with incremental indexing: new name.
101decode(<< 0:1, 1:1, 0:6, Rest/bits >>, State, Acc) ->
102	dec_lit_index_new_name(Rest, State, Acc);
103%% Literal header field with incremental indexing: indexed name.
104decode(<< 0:1, 1:1, Rest/bits >>, State, Acc) ->
105	dec_lit_index_indexed_name(Rest, State, Acc);
106%% Literal header field without indexing: new name.
107decode(<< 0:8, Rest/bits >>, State, Acc) ->
108	dec_lit_no_index_new_name(Rest, State, Acc);
109%% Literal header field without indexing: indexed name.
110decode(<< 0:4, Rest/bits >>, State, Acc) ->
111	dec_lit_no_index_indexed_name(Rest, State, Acc);
112%% Literal header field never indexed: new name.
113%% @todo Keep track of "never indexed" headers.
114decode(<< 0:3, 1:1, 0:4, Rest/bits >>, State, Acc) ->
115	dec_lit_no_index_new_name(Rest, State, Acc);
116%% Literal header field never indexed: indexed name.
117%% @todo Keep track of "never indexed" headers.
118decode(<< 0:3, 1:1, Rest/bits >>, State, Acc) ->
119	dec_lit_no_index_indexed_name(Rest, State, Acc).
120
121%% Indexed header field representation.
122
123%% We do the integer decoding inline where appropriate, falling
124%% back to dec_big_int for larger values.
125dec_indexed(<<2#1111111:7, 0:1, Int:7, Rest/bits>>, State, Acc) ->
126	{Name, Value} = table_get(127 + Int, State),
127	decode(Rest, State, [{Name, Value}|Acc]);
128dec_indexed(<<2#1111111:7, Rest0/bits>>, State, Acc) ->
129	{Index, Rest} = dec_big_int(Rest0, 127, 0),
130	{Name, Value} = table_get(Index, State),
131	decode(Rest, State, [{Name, Value}|Acc]);
132dec_indexed(<<Index:7, Rest/bits>>, State, Acc) ->
133	{Name, Value} = table_get(Index, State),
134	decode(Rest, State, [{Name, Value}|Acc]).
135
136%% Literal header field with incremental indexing.
137
138dec_lit_index_new_name(Rest, State, Acc) ->
139	{Name, Rest2} = dec_str(Rest),
140	dec_lit_index(Rest2, State, Acc, Name).
141
142%% We do the integer decoding inline where appropriate, falling
143%% back to dec_big_int for larger values.
144dec_lit_index_indexed_name(<<2#111111:6, 0:1, Int:7, Rest/bits>>, State, Acc) ->
145	Name = table_get_name(63 + Int, State),
146	dec_lit_index(Rest, State, Acc, Name);
147dec_lit_index_indexed_name(<<2#111111:6, Rest0/bits>>, State, Acc) ->
148	{Index, Rest} = dec_big_int(Rest0, 63, 0),
149	Name = table_get_name(Index, State),
150	dec_lit_index(Rest, State, Acc, Name);
151dec_lit_index_indexed_name(<<Index:6, Rest/bits>>, State, Acc) ->
152	Name = table_get_name(Index, State),
153	dec_lit_index(Rest, State, Acc, Name).
154
155dec_lit_index(Rest, State, Acc, Name) ->
156	{Value, Rest2} = dec_str(Rest),
157	State2 = table_insert({Name, Value}, State),
158	decode(Rest2, State2, [{Name, Value}|Acc]).
159
160%% Literal header field without indexing.
161
162dec_lit_no_index_new_name(Rest, State, Acc) ->
163	{Name, Rest2} = dec_str(Rest),
164	dec_lit_no_index(Rest2, State, Acc, Name).
165
166%% We do the integer decoding inline where appropriate, falling
167%% back to dec_big_int for larger values.
168dec_lit_no_index_indexed_name(<<2#1111:4, 0:1, Int:7, Rest/bits>>, State, Acc) ->
169	Name = table_get_name(15 + Int, State),
170	dec_lit_no_index(Rest, State, Acc, Name);
171dec_lit_no_index_indexed_name(<<2#1111:4, Rest0/bits>>, State, Acc) ->
172	{Index, Rest} = dec_big_int(Rest0, 15, 0),
173	Name = table_get_name(Index, State),
174	dec_lit_no_index(Rest, State, Acc, Name);
175dec_lit_no_index_indexed_name(<<Index:4, Rest/bits>>, State, Acc) ->
176	Name = table_get_name(Index, State),
177	dec_lit_no_index(Rest, State, Acc, Name).
178
179dec_lit_no_index(Rest, State, Acc, Name) ->
180	{Value, Rest2} = dec_str(Rest),
181	decode(Rest2, State, [{Name, Value}|Acc]).
182
183%% @todo Literal header field never indexed.
184
185%% Decode an integer.
186
187%% The HPACK format has 4 different integer prefixes length (from 4 to 7)
188%% and each can be used to create an indefinite length integer if all bits
189%% of the prefix are set to 1.
190
191dec_int5(<< 2#11111:5, Rest/bits >>) ->
192	dec_big_int(Rest, 31, 0);
193dec_int5(<< Int:5, Rest/bits >>) ->
194	{Int, Rest}.
195
196dec_big_int(<< 0:1, Value:7, Rest/bits >>, Int, M) ->
197	{Int + (Value bsl M), Rest};
198dec_big_int(<< 1:1, Value:7, Rest/bits >>, Int, M) ->
199	dec_big_int(Rest, Int + (Value bsl M), M + 7).
200
201%% Decode a string.
202
203dec_str(<<0:1, 2#1111111:7, Rest0/bits>>) ->
204	{Length, Rest1} = dec_big_int(Rest0, 127, 0),
205	<<Str:Length/binary, Rest/bits>> = Rest1,
206	{Str, Rest};
207dec_str(<<0:1, Length:7, Rest0/bits>>) ->
208	<<Str:Length/binary, Rest/bits>> = Rest0,
209	{Str, Rest};
210dec_str(<<1:1, 2#1111111:7, Rest0/bits>>) ->
211	{Length, Rest} = dec_big_int(Rest0, 127, 0),
212	dec_huffman(Rest, Length, 0, <<>>);
213dec_str(<<1:1, Length:7, Rest/bits>>) ->
214	dec_huffman(Rest, Length, 0, <<>>).
215
216%% We use a lookup table that allows us to benefit from
217%% the binary match context optimization. A more naive
218%% implementation using bit pattern matching cannot reuse
219%% a match context because it wouldn't always match on
220%% byte boundaries.
221%%
222%% See cow_hpack_dec_huffman_lookup.hrl for more details.
223
224dec_huffman(<<A:4, B:4, R/bits>>, Len, Huff0, Acc) when Len > 1 ->
225	{_, CharA, Huff1} = dec_huffman_lookup(Huff0, A),
226	{_, CharB, Huff} = dec_huffman_lookup(Huff1, B),
227	case {CharA, CharB} of
228		{undefined, undefined} -> dec_huffman(R, Len - 1, Huff, Acc);
229		{CharA, undefined} -> dec_huffman(R, Len - 1, Huff, <<Acc/binary, CharA>>);
230		{undefined, CharB} -> dec_huffman(R, Len - 1, Huff, <<Acc/binary, CharB>>);
231		{CharA, CharB} -> dec_huffman(R, Len - 1, Huff, <<Acc/binary, CharA, CharB>>)
232	end;
233dec_huffman(<<A:4, B:4, Rest/bits>>, 1, Huff0, Acc) ->
234	{_, CharA, Huff} = dec_huffman_lookup(Huff0, A),
235	{ok, CharB, _} = dec_huffman_lookup(Huff, B),
236	case {CharA, CharB} of
237		%% {undefined, undefined} (> 7-bit final padding) is rejected with a crash.
238		{CharA, undefined} ->
239			{<<Acc/binary, CharA>>, Rest};
240		{undefined, CharB} ->
241			{<<Acc/binary, CharB>>, Rest};
242		_ ->
243			{<<Acc/binary, CharA, CharB>>, Rest}
244	end;
245%% Can only be reached when the string length to decode is 0.
246dec_huffman(Rest, 0, _, <<>>) ->
247	{<<>>, Rest}.
248
249-include("cow_hpack_dec_huffman_lookup.hrl").
250
251-ifdef(TEST).
252%% Test case extracted from h2spec.
253decode_reject_eos_test() ->
254	{'EXIT', _} = (catch decode(<<16#0085f2b24a84ff874951fffffffa7f:120>>)),
255	ok.
256
257req_decode_test() ->
258	%% First request (raw then huffman).
259	{Headers1, State1} = decode(<< 16#828684410f7777772e6578616d706c652e636f6d:160 >>),
260	{Headers1, State1} = decode(<< 16#828684418cf1e3c2e5f23a6ba0ab90f4ff:136 >>),
261	Headers1 = [
262		{<<":method">>, <<"GET">>},
263		{<<":scheme">>, <<"http">>},
264		{<<":path">>, <<"/">>},
265		{<<":authority">>, <<"www.example.com">>}
266	],
267	#state{size=57, dyn_table=[{57,{<<":authority">>, <<"www.example.com">>}}]} = State1,
268	%% Second request (raw then huffman).
269	{Headers2, State2} = decode(<< 16#828684be58086e6f2d6361636865:112 >>, State1),
270	{Headers2, State2} = decode(<< 16#828684be5886a8eb10649cbf:96 >>, State1),
271	Headers2 = [
272		{<<":method">>, <<"GET">>},
273		{<<":scheme">>, <<"http">>},
274		{<<":path">>, <<"/">>},
275		{<<":authority">>, <<"www.example.com">>},
276		{<<"cache-control">>, <<"no-cache">>}
277	],
278	#state{size=110, dyn_table=[
279		{53,{<<"cache-control">>, <<"no-cache">>}},
280		{57,{<<":authority">>, <<"www.example.com">>}}]} = State2,
281	%% Third request (raw then huffman).
282	{Headers3, State3} = decode(<< 16#828785bf400a637573746f6d2d6b65790c637573746f6d2d76616c7565:232 >>, State2),
283	{Headers3, State3} = decode(<< 16#828785bf408825a849e95ba97d7f8925a849e95bb8e8b4bf:192 >>, State2),
284	Headers3 = [
285		{<<":method">>, <<"GET">>},
286		{<<":scheme">>, <<"https">>},
287		{<<":path">>, <<"/index.html">>},
288		{<<":authority">>, <<"www.example.com">>},
289		{<<"custom-key">>, <<"custom-value">>}
290	],
291	#state{size=164, dyn_table=[
292		{54,{<<"custom-key">>, <<"custom-value">>}},
293		{53,{<<"cache-control">>, <<"no-cache">>}},
294		{57,{<<":authority">>, <<"www.example.com">>}}]} = State3,
295	ok.
296
297resp_decode_test() ->
298	%% Use a max_size of 256 to trigger header evictions.
299	State0 = init(256),
300	%% First response (raw then huffman).
301	{Headers1, State1} = decode(<< 16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560 >>, State0),
302	{Headers1, State1} = decode(<< 16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432 >>, State0),
303	Headers1 = [
304		{<<":status">>, <<"302">>},
305		{<<"cache-control">>, <<"private">>},
306		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
307		{<<"location">>, <<"https://www.example.com">>}
308	],
309	#state{size=222, dyn_table=[
310		{63,{<<"location">>, <<"https://www.example.com">>}},
311		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
312		{52,{<<"cache-control">>, <<"private">>}},
313		{42,{<<":status">>, <<"302">>}}]} = State1,
314	%% Second response (raw then huffman).
315	{Headers2, State2} = decode(<< 16#4803333037c1c0bf:64 >>, State1),
316	{Headers2, State2} = decode(<< 16#4883640effc1c0bf:64 >>, State1),
317	Headers2 = [
318		{<<":status">>, <<"307">>},
319		{<<"cache-control">>, <<"private">>},
320		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
321		{<<"location">>, <<"https://www.example.com">>}
322	],
323	#state{size=222, dyn_table=[
324		{42,{<<":status">>, <<"307">>}},
325		{63,{<<"location">>, <<"https://www.example.com">>}},
326		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
327		{52,{<<"cache-control">>, <<"private">>}}]} = State2,
328	%% Third response (raw then huffman).
329	{Headers3, State3} = decode(<< 16#88c1611d4d6f6e2c203231204f637420323031332032303a31333a323220474d54c05a04677a69707738666f6f3d4153444a4b48514b425a584f5157454f50495541585157454f49553b206d61782d6167653d333630303b2076657273696f6e3d31:784 >>, State2),
330	{Headers3, State3} = decode(<< 16#88c16196d07abe941054d444a8200595040b8166e084a62d1bffc05a839bd9ab77ad94e7821dd7f2e6c7b335dfdfcd5b3960d5af27087f3672c1ab270fb5291f9587316065c003ed4ee5b1063d5007:632 >>, State2),
331	Headers3 = [
332		{<<":status">>, <<"200">>},
333		{<<"cache-control">>, <<"private">>},
334		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:22 GMT">>},
335		{<<"location">>, <<"https://www.example.com">>},
336		{<<"content-encoding">>, <<"gzip">>},
337		{<<"set-cookie">>, <<"foo=ASDJKHQKBZXOQWEOPIUAXQWEOIU; max-age=3600; version=1">>}
338	],
339	#state{size=215, dyn_table=[
340		{98,{<<"set-cookie">>, <<"foo=ASDJKHQKBZXOQWEOPIUAXQWEOIU; max-age=3600; version=1">>}},
341		{52,{<<"content-encoding">>, <<"gzip">>}},
342		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:22 GMT">>}}]} = State3,
343	ok.
344
345table_update_decode_test() ->
346	%% Use a max_size of 256 to trigger header evictions
347	%% when the code is not updating the max size.
348	State0 = init(256),
349	%% First response (raw then huffman).
350	{Headers1, State1} = decode(<< 16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560 >>, State0),
351	{Headers1, State1} = decode(<< 16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432 >>, State0),
352	Headers1 = [
353		{<<":status">>, <<"302">>},
354		{<<"cache-control">>, <<"private">>},
355		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
356		{<<"location">>, <<"https://www.example.com">>}
357	],
358	#state{size=222, configured_max_size=256, dyn_table=[
359		{63,{<<"location">>, <<"https://www.example.com">>}},
360		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
361		{52,{<<"cache-control">>, <<"private">>}},
362		{42,{<<":status">>, <<"302">>}}]} = State1,
363	%% Set a new configured max_size to avoid header evictions.
364	State2 = set_max_size(512, State1),
365	%% Second response with the table size update (raw then huffman).
366	MaxSize = enc_big_int(512 - 31, <<>>),
367	{Headers2, State3} = decode(
368		iolist_to_binary([<< 2#00111111>>, MaxSize, <<16#4803333037c1c0bf:64>>]),
369		State2),
370	{Headers2, State3} = decode(
371		iolist_to_binary([<< 2#00111111>>, MaxSize, <<16#4883640effc1c0bf:64>>]),
372		State2),
373	Headers2 = [
374		{<<":status">>, <<"307">>},
375		{<<"cache-control">>, <<"private">>},
376		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
377		{<<"location">>, <<"https://www.example.com">>}
378	],
379	#state{size=264, configured_max_size=512, dyn_table=[
380		{42,{<<":status">>, <<"307">>}},
381		{63,{<<"location">>, <<"https://www.example.com">>}},
382		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
383		{52,{<<"cache-control">>, <<"private">>}},
384		{42,{<<":status">>, <<"302">>}}]} = State3,
385	ok.
386
387table_update_decode_smaller_test() ->
388	%% Use a max_size of 256 to trigger header evictions
389	%% when the code is not updating the max size.
390	State0 = init(256),
391	%% First response (raw then huffman).
392	{Headers1, State1} = decode(<< 16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560 >>, State0),
393	{Headers1, State1} = decode(<< 16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432 >>, State0),
394	Headers1 = [
395		{<<":status">>, <<"302">>},
396		{<<"cache-control">>, <<"private">>},
397		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
398		{<<"location">>, <<"https://www.example.com">>}
399	],
400	#state{size=222, configured_max_size=256, dyn_table=[
401		{63,{<<"location">>, <<"https://www.example.com">>}},
402		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
403		{52,{<<"cache-control">>, <<"private">>}},
404		{42,{<<":status">>, <<"302">>}}]} = State1,
405	%% Set a new configured max_size to avoid header evictions.
406	State2 = set_max_size(512, State1),
407	%% Second response with the table size update smaller than the limit (raw then huffman).
408	MaxSize = enc_big_int(400 - 31, <<>>),
409	{Headers2, State3} = decode(
410		iolist_to_binary([<< 2#00111111>>, MaxSize, <<16#4803333037c1c0bf:64>>]),
411		State2),
412	{Headers2, State3} = decode(
413		iolist_to_binary([<< 2#00111111>>, MaxSize, <<16#4883640effc1c0bf:64>>]),
414		State2),
415	Headers2 = [
416		{<<":status">>, <<"307">>},
417		{<<"cache-control">>, <<"private">>},
418		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
419		{<<"location">>, <<"https://www.example.com">>}
420	],
421	#state{size=264, configured_max_size=512, dyn_table=[
422		{42,{<<":status">>, <<"307">>}},
423		{63,{<<"location">>, <<"https://www.example.com">>}},
424		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
425		{52,{<<"cache-control">>, <<"private">>}},
426		{42,{<<":status">>, <<"302">>}}]} = State3,
427	ok.
428
429table_update_decode_too_large_test() ->
430	%% Use a max_size of 256 to trigger header evictions
431	%% when the code is not updating the max size.
432	State0 = init(256),
433	%% First response (raw then huffman).
434	{Headers1, State1} = decode(<< 16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560 >>, State0),
435	{Headers1, State1} = decode(<< 16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432 >>, State0),
436	Headers1 = [
437		{<<":status">>, <<"302">>},
438		{<<"cache-control">>, <<"private">>},
439		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
440		{<<"location">>, <<"https://www.example.com">>}
441	],
442	#state{size=222, configured_max_size=256, dyn_table=[
443		{63,{<<"location">>, <<"https://www.example.com">>}},
444		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
445		{52,{<<"cache-control">>, <<"private">>}},
446		{42,{<<":status">>, <<"302">>}}]} = State1,
447	%% Set a new configured max_size to avoid header evictions.
448	State2 = set_max_size(512, State1),
449	%% Second response with the table size update (raw then huffman).
450	MaxSize = enc_big_int(1024 - 31, <<>>),
451	{'EXIT', _} = (catch decode(
452		iolist_to_binary([<< 2#00111111>>, MaxSize, <<16#4803333037c1c0bf:64>>]),
453		State2)),
454	{'EXIT', _} = (catch decode(
455		iolist_to_binary([<< 2#00111111>>, MaxSize, <<16#4883640effc1c0bf:64>>]),
456		State2)),
457	ok.
458
459table_update_decode_zero_test() ->
460	State0 = init(256),
461	%% First response (raw then huffman).
462	{Headers1, State1} = decode(<< 16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560 >>, State0),
463	{Headers1, State1} = decode(<< 16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432 >>, State0),
464	Headers1 = [
465		{<<":status">>, <<"302">>},
466		{<<"cache-control">>, <<"private">>},
467		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
468		{<<"location">>, <<"https://www.example.com">>}
469	],
470	#state{size=222, configured_max_size=256, dyn_table=[
471		{63,{<<"location">>, <<"https://www.example.com">>}},
472		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
473		{52,{<<"cache-control">>, <<"private">>}},
474		{42,{<<":status">>, <<"302">>}}]} = State1,
475	%% Set a new configured max_size to avoid header evictions.
476	State2 = set_max_size(512, State1),
477	%% Second response with the table size update (raw then huffman).
478	%% We set the table size to 0 to evict all values before setting
479	%% it to 512 so we only get the second request indexed.
480	MaxSize = enc_big_int(512 - 31, <<>>),
481	{Headers1, State3} = decode(iolist_to_binary([
482		<<2#00100000, 2#00111111>>, MaxSize,
483		<<16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560>>]),
484		State2),
485	{Headers1, State3} = decode(iolist_to_binary([
486		<<2#00100000, 2#00111111>>, MaxSize,
487		<<16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432>>]),
488		State2),
489	#state{size=222, configured_max_size=512, dyn_table=[
490		{63,{<<"location">>, <<"https://www.example.com">>}},
491		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
492		{52,{<<"cache-control">>, <<"private">>}},
493		{42,{<<":status">>, <<"302">>}}]} = State3,
494	ok.
495
496horse_decode_raw() ->
497	horse:repeat(20000,
498		do_horse_decode_raw()
499	).
500
501do_horse_decode_raw() ->
502	{_, State1} = decode(<<16#828684410f7777772e6578616d706c652e636f6d:160>>),
503	{_, State2} = decode(<<16#828684be58086e6f2d6361636865:112>>, State1),
504	{_, _} = decode(<<16#828785bf400a637573746f6d2d6b65790c637573746f6d2d76616c7565:232>>, State2),
505	ok.
506
507horse_decode_huffman() ->
508	horse:repeat(20000,
509		do_horse_decode_huffman()
510	).
511
512do_horse_decode_huffman() ->
513	{_, State1} = decode(<<16#828684418cf1e3c2e5f23a6ba0ab90f4ff:136>>),
514	{_, State2} = decode(<<16#828684be5886a8eb10649cbf:96>>, State1),
515	{_, _} = decode(<<16#828785bf408825a849e95ba97d7f8925a849e95bb8e8b4bf:192>>, State2),
516	ok.
517-endif.
518
519%% Encoding.
520
521-spec encode(cow_http:headers()) -> {iodata(), state()}.
522encode(Headers) ->
523	encode(Headers, init(), huffman, []).
524
525-spec encode(cow_http:headers(), State) -> {iodata(), State} when State::state().
526encode(Headers, State=#state{max_size=MaxSize, configured_max_size=MaxSize}) ->
527	encode(Headers, State, huffman, []);
528encode(Headers, State0=#state{configured_max_size=MaxSize}) ->
529	{Data, State} = encode(Headers, State0#state{max_size=MaxSize}, huffman, []),
530	{[enc_int5(MaxSize, 2#001)|Data], State}.
531
532-spec encode(cow_http:headers(), State, opts()) -> {iodata(), State} when State::state().
533encode(Headers, State=#state{max_size=MaxSize, configured_max_size=MaxSize}, Opts) ->
534	encode(Headers, State, huffman_opt(Opts), []);
535encode(Headers, State0=#state{configured_max_size=MaxSize}, Opts) ->
536	{Data, State} = encode(Headers, State0#state{max_size=MaxSize}, huffman_opt(Opts), []),
537	{[enc_int5(MaxSize, 2#001)|Data], State}.
538
539huffman_opt(#{huffman := false}) -> no_huffman;
540huffman_opt(_) -> huffman.
541
542%% @todo Handle cases where no/never indexing is expected.
543encode([], State, _, Acc) ->
544	{lists:reverse(Acc), State};
545encode([{Name, Value0}|Tail], State, HuffmanOpt, Acc) ->
546	%% We conditionally call iolist_to_binary/1 because a small
547	%% but noticeable speed improvement happens when we do this.
548	Value = if
549		is_binary(Value0) -> Value0;
550		true -> iolist_to_binary(Value0)
551	end,
552	Header = {Name, Value},
553	case table_find(Header, State) of
554		%% Indexed header field representation.
555		{field, Index} ->
556			encode(Tail, State, HuffmanOpt,
557				[enc_int7(Index, 2#1)|Acc]);
558		%% Literal header field representation: indexed name.
559		{name, Index} ->
560			State2 = table_insert(Header, State),
561			encode(Tail, State2, HuffmanOpt,
562				[[enc_int6(Index, 2#01)|enc_str(Value, HuffmanOpt)]|Acc]);
563		%% Literal header field representation: new name.
564		not_found ->
565			State2 = table_insert(Header, State),
566			encode(Tail, State2, HuffmanOpt,
567				[[<< 0:1, 1:1, 0:6 >>|[enc_str(Name, HuffmanOpt)|enc_str(Value, HuffmanOpt)]]|Acc])
568	end.
569
570%% Encode an integer.
571
572enc_int5(Int, Prefix) when Int < 31 ->
573	<< Prefix:3, Int:5 >>;
574enc_int5(Int, Prefix) ->
575	enc_big_int(Int - 31, << Prefix:3, 2#11111:5 >>).
576
577enc_int6(Int, Prefix) when Int < 63 ->
578	<< Prefix:2, Int:6 >>;
579enc_int6(Int, Prefix) ->
580	enc_big_int(Int - 63, << Prefix:2, 2#111111:6 >>).
581
582enc_int7(Int, Prefix) when Int < 127 ->
583	<< Prefix:1, Int:7 >>;
584enc_int7(Int, Prefix) ->
585	enc_big_int(Int - 127, << Prefix:1, 2#1111111:7 >>).
586
587enc_big_int(Int, Acc) when Int < 128 ->
588	<<Acc/binary, Int:8>>;
589enc_big_int(Int, Acc) ->
590	enc_big_int(Int bsr 7, <<Acc/binary, 1:1, Int:7>>).
591
592%% Encode a string.
593
594enc_str(Str, huffman) ->
595	Str2 = enc_huffman(Str, <<>>),
596	[enc_int7(byte_size(Str2), 2#1)|Str2];
597enc_str(Str, no_huffman) ->
598	[enc_int7(byte_size(Str), 2#0)|Str].
599
600enc_huffman(<<>>, Acc) ->
601	case bit_size(Acc) rem 8 of
602		1 -> << Acc/bits, 2#1111111:7 >>;
603		2 -> << Acc/bits, 2#111111:6 >>;
604		3 -> << Acc/bits, 2#11111:5 >>;
605		4 -> << Acc/bits, 2#1111:4 >>;
606		5 -> << Acc/bits, 2#111:3 >>;
607		6 -> << Acc/bits, 2#11:2 >>;
608		7 -> << Acc/bits, 2#1:1 >>;
609		0 -> Acc
610	end;
611enc_huffman(<< 0, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111000:13 >>);
612enc_huffman(<< 1, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011000:23 >>);
613enc_huffman(<< 2, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111100010:28 >>);
614enc_huffman(<< 3, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111100011:28 >>);
615enc_huffman(<< 4, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111100100:28 >>);
616enc_huffman(<< 5, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111100101:28 >>);
617enc_huffman(<< 6, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111100110:28 >>);
618enc_huffman(<< 7, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111100111:28 >>);
619enc_huffman(<< 8, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101000:28 >>);
620enc_huffman(<< 9, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111101010:24 >>);
621enc_huffman(<< 10, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111111111100:30 >>);
622enc_huffman(<< 11, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101001:28 >>);
623enc_huffman(<< 12, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101010:28 >>);
624enc_huffman(<< 13, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111111111101:30 >>);
625enc_huffman(<< 14, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101011:28 >>);
626enc_huffman(<< 15, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101100:28 >>);
627enc_huffman(<< 16, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101101:28 >>);
628enc_huffman(<< 17, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101110:28 >>);
629enc_huffman(<< 18, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111101111:28 >>);
630enc_huffman(<< 19, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110000:28 >>);
631enc_huffman(<< 20, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110001:28 >>);
632enc_huffman(<< 21, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110010:28 >>);
633enc_huffman(<< 22, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111111111110:30 >>);
634enc_huffman(<< 23, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110011:28 >>);
635enc_huffman(<< 24, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110100:28 >>);
636enc_huffman(<< 25, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110101:28 >>);
637enc_huffman(<< 26, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110110:28 >>);
638enc_huffman(<< 27, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111110111:28 >>);
639enc_huffman(<< 28, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111000:28 >>);
640enc_huffman(<< 29, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111001:28 >>);
641enc_huffman(<< 30, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111010:28 >>);
642enc_huffman(<< 31, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111011:28 >>);
643enc_huffman(<< 32, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#010100:6 >>);
644enc_huffman(<< 33, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111000:10 >>);
645enc_huffman(<< 34, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111001:10 >>);
646enc_huffman(<< 35, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111010:12 >>);
647enc_huffman(<< 36, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111001:13 >>);
648enc_huffman(<< 37, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#010101:6 >>);
649enc_huffman(<< 38, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111000:8 >>);
650enc_huffman(<< 39, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111010:11 >>);
651enc_huffman(<< 40, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111010:10 >>);
652enc_huffman(<< 41, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111011:10 >>);
653enc_huffman(<< 42, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111001:8 >>);
654enc_huffman(<< 43, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111011:11 >>);
655enc_huffman(<< 44, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111010:8 >>);
656enc_huffman(<< 45, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#010110:6 >>);
657enc_huffman(<< 46, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#010111:6 >>);
658enc_huffman(<< 47, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011000:6 >>);
659enc_huffman(<< 48, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00000:5 >>);
660enc_huffman(<< 49, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00001:5 >>);
661enc_huffman(<< 50, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00010:5 >>);
662enc_huffman(<< 51, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011001:6 >>);
663enc_huffman(<< 52, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011010:6 >>);
664enc_huffman(<< 53, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011011:6 >>);
665enc_huffman(<< 54, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011100:6 >>);
666enc_huffman(<< 55, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011101:6 >>);
667enc_huffman(<< 56, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011110:6 >>);
668enc_huffman(<< 57, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#011111:6 >>);
669enc_huffman(<< 58, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1011100:7 >>);
670enc_huffman(<< 59, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111011:8 >>);
671enc_huffman(<< 60, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111100:15 >>);
672enc_huffman(<< 61, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100000:6 >>);
673enc_huffman(<< 62, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111011:12 >>);
674enc_huffman(<< 63, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111100:10 >>);
675enc_huffman(<< 64, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111010:13 >>);
676enc_huffman(<< 65, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100001:6 >>);
677enc_huffman(<< 66, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1011101:7 >>);
678enc_huffman(<< 67, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1011110:7 >>);
679enc_huffman(<< 68, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1011111:7 >>);
680enc_huffman(<< 69, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100000:7 >>);
681enc_huffman(<< 70, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100001:7 >>);
682enc_huffman(<< 71, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100010:7 >>);
683enc_huffman(<< 72, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100011:7 >>);
684enc_huffman(<< 73, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100100:7 >>);
685enc_huffman(<< 74, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100101:7 >>);
686enc_huffman(<< 75, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100110:7 >>);
687enc_huffman(<< 76, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1100111:7 >>);
688enc_huffman(<< 77, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101000:7 >>);
689enc_huffman(<< 78, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101001:7 >>);
690enc_huffman(<< 79, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101010:7 >>);
691enc_huffman(<< 80, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101011:7 >>);
692enc_huffman(<< 81, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101100:7 >>);
693enc_huffman(<< 82, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101101:7 >>);
694enc_huffman(<< 83, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101110:7 >>);
695enc_huffman(<< 84, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1101111:7 >>);
696enc_huffman(<< 85, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110000:7 >>);
697enc_huffman(<< 86, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110001:7 >>);
698enc_huffman(<< 87, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110010:7 >>);
699enc_huffman(<< 88, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111100:8 >>);
700enc_huffman(<< 89, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110011:7 >>);
701enc_huffman(<< 90, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111101:8 >>);
702enc_huffman(<< 91, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111011:13 >>);
703enc_huffman(<< 92, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111110000:19 >>);
704enc_huffman(<< 93, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111100:13 >>);
705enc_huffman(<< 94, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111100:14 >>);
706enc_huffman(<< 95, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100010:6 >>);
707enc_huffman(<< 96, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111101:15 >>);
708enc_huffman(<< 97, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00011:5 >>);
709enc_huffman(<< 98, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100011:6 >>);
710enc_huffman(<< 99, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00100:5 >>);
711enc_huffman(<< 100, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100100:6 >>);
712enc_huffman(<< 101, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00101:5 >>);
713enc_huffman(<< 102, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100101:6 >>);
714enc_huffman(<< 103, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100110:6 >>);
715enc_huffman(<< 104, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#100111:6 >>);
716enc_huffman(<< 105, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00110:5 >>);
717enc_huffman(<< 106, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110100:7 >>);
718enc_huffman(<< 107, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110101:7 >>);
719enc_huffman(<< 108, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#101000:6 >>);
720enc_huffman(<< 109, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#101001:6 >>);
721enc_huffman(<< 110, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#101010:6 >>);
722enc_huffman(<< 111, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#00111:5 >>);
723enc_huffman(<< 112, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#101011:6 >>);
724enc_huffman(<< 113, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110110:7 >>);
725enc_huffman(<< 114, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#101100:6 >>);
726enc_huffman(<< 115, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#01000:5 >>);
727enc_huffman(<< 116, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#01001:5 >>);
728enc_huffman(<< 117, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#101101:6 >>);
729enc_huffman(<< 118, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1110111:7 >>);
730enc_huffman(<< 119, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111000:7 >>);
731enc_huffman(<< 120, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111001:7 >>);
732enc_huffman(<< 121, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111010:7 >>);
733enc_huffman(<< 122, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111011:7 >>);
734enc_huffman(<< 123, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111110:15 >>);
735enc_huffman(<< 124, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111100:11 >>);
736enc_huffman(<< 125, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111101:14 >>);
737enc_huffman(<< 126, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111101:13 >>);
738enc_huffman(<< 127, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111100:28 >>);
739enc_huffman(<< 128, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111100110:20 >>);
740enc_huffman(<< 129, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111010010:22 >>);
741enc_huffman(<< 130, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111100111:20 >>);
742enc_huffman(<< 131, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111101000:20 >>);
743enc_huffman(<< 132, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111010011:22 >>);
744enc_huffman(<< 133, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111010100:22 >>);
745enc_huffman(<< 134, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111010101:22 >>);
746enc_huffman(<< 135, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011001:23 >>);
747enc_huffman(<< 136, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111010110:22 >>);
748enc_huffman(<< 137, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011010:23 >>);
749enc_huffman(<< 138, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011011:23 >>);
750enc_huffman(<< 139, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011100:23 >>);
751enc_huffman(<< 140, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011101:23 >>);
752enc_huffman(<< 141, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011110:23 >>);
753enc_huffman(<< 142, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111101011:24 >>);
754enc_huffman(<< 143, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111011111:23 >>);
755enc_huffman(<< 144, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111101100:24 >>);
756enc_huffman(<< 145, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111101101:24 >>);
757enc_huffman(<< 146, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111010111:22 >>);
758enc_huffman(<< 147, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100000:23 >>);
759enc_huffman(<< 148, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111101110:24 >>);
760enc_huffman(<< 149, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100001:23 >>);
761enc_huffman(<< 150, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100010:23 >>);
762enc_huffman(<< 151, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100011:23 >>);
763enc_huffman(<< 152, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100100:23 >>);
764enc_huffman(<< 153, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111011100:21 >>);
765enc_huffman(<< 154, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011000:22 >>);
766enc_huffman(<< 155, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100101:23 >>);
767enc_huffman(<< 156, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011001:22 >>);
768enc_huffman(<< 157, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100110:23 >>);
769enc_huffman(<< 158, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111100111:23 >>);
770enc_huffman(<< 159, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111101111:24 >>);
771enc_huffman(<< 160, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011010:22 >>);
772enc_huffman(<< 161, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111011101:21 >>);
773enc_huffman(<< 162, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111101001:20 >>);
774enc_huffman(<< 163, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011011:22 >>);
775enc_huffman(<< 164, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011100:22 >>);
776enc_huffman(<< 165, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101000:23 >>);
777enc_huffman(<< 166, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101001:23 >>);
778enc_huffman(<< 167, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111011110:21 >>);
779enc_huffman(<< 168, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101010:23 >>);
780enc_huffman(<< 169, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011101:22 >>);
781enc_huffman(<< 170, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011110:22 >>);
782enc_huffman(<< 171, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111110000:24 >>);
783enc_huffman(<< 172, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111011111:21 >>);
784enc_huffman(<< 173, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111011111:22 >>);
785enc_huffman(<< 174, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101011:23 >>);
786enc_huffman(<< 175, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101100:23 >>);
787enc_huffman(<< 176, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100000:21 >>);
788enc_huffman(<< 177, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100001:21 >>);
789enc_huffman(<< 178, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100000:22 >>);
790enc_huffman(<< 179, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100010:21 >>);
791enc_huffman(<< 180, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101101:23 >>);
792enc_huffman(<< 181, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100001:22 >>);
793enc_huffman(<< 182, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101110:23 >>);
794enc_huffman(<< 183, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111101111:23 >>);
795enc_huffman(<< 184, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111101010:20 >>);
796enc_huffman(<< 185, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100010:22 >>);
797enc_huffman(<< 186, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100011:22 >>);
798enc_huffman(<< 187, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100100:22 >>);
799enc_huffman(<< 188, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111110000:23 >>);
800enc_huffman(<< 189, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100101:22 >>);
801enc_huffman(<< 190, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100110:22 >>);
802enc_huffman(<< 191, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111110001:23 >>);
803enc_huffman(<< 192, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100000:26 >>);
804enc_huffman(<< 193, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100001:26 >>);
805enc_huffman(<< 194, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111101011:20 >>);
806enc_huffman(<< 195, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111110001:19 >>);
807enc_huffman(<< 196, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111100111:22 >>);
808enc_huffman(<< 197, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111110010:23 >>);
809enc_huffman(<< 198, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111101000:22 >>);
810enc_huffman(<< 199, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111101100:25 >>);
811enc_huffman(<< 200, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100010:26 >>);
812enc_huffman(<< 201, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100011:26 >>);
813enc_huffman(<< 202, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100100:26 >>);
814enc_huffman(<< 203, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111011110:27 >>);
815enc_huffman(<< 204, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111011111:27 >>);
816enc_huffman(<< 205, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100101:26 >>);
817enc_huffman(<< 206, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111110001:24 >>);
818enc_huffman(<< 207, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111101101:25 >>);
819enc_huffman(<< 208, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111110010:19 >>);
820enc_huffman(<< 209, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100011:21 >>);
821enc_huffman(<< 210, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100110:26 >>);
822enc_huffman(<< 211, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100000:27 >>);
823enc_huffman(<< 212, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100001:27 >>);
824enc_huffman(<< 213, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111100111:26 >>);
825enc_huffman(<< 214, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100010:27 >>);
826enc_huffman(<< 215, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111110010:24 >>);
827enc_huffman(<< 216, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100100:21 >>);
828enc_huffman(<< 217, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100101:21 >>);
829enc_huffman(<< 218, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101000:26 >>);
830enc_huffman(<< 219, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101001:26 >>);
831enc_huffman(<< 220, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111101:28 >>);
832enc_huffman(<< 221, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100011:27 >>);
833enc_huffman(<< 222, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100100:27 >>);
834enc_huffman(<< 223, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100101:27 >>);
835enc_huffman(<< 224, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111101100:20 >>);
836enc_huffman(<< 225, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111110011:24 >>);
837enc_huffman(<< 226, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111101101:20 >>);
838enc_huffman(<< 227, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100110:21 >>);
839enc_huffman(<< 228, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111101001:22 >>);
840enc_huffman(<< 229, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111100111:21 >>);
841enc_huffman(<< 230, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111101000:21 >>);
842enc_huffman(<< 231, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111110011:23 >>);
843enc_huffman(<< 232, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111101010:22 >>);
844enc_huffman(<< 233, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111101011:22 >>);
845enc_huffman(<< 234, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111101110:25 >>);
846enc_huffman(<< 235, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111101111:25 >>);
847enc_huffman(<< 236, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111110100:24 >>);
848enc_huffman(<< 237, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111110101:24 >>);
849enc_huffman(<< 238, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101010:26 >>);
850enc_huffman(<< 239, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111110100:23 >>);
851enc_huffman(<< 240, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101011:26 >>);
852enc_huffman(<< 241, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100110:27 >>);
853enc_huffman(<< 242, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101100:26 >>);
854enc_huffman(<< 243, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101101:26 >>);
855enc_huffman(<< 244, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111100111:27 >>);
856enc_huffman(<< 245, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101000:27 >>);
857enc_huffman(<< 246, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101001:27 >>);
858enc_huffman(<< 247, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101010:27 >>);
859enc_huffman(<< 248, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101011:27 >>);
860enc_huffman(<< 249, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#1111111111111111111111111110:28 >>);
861enc_huffman(<< 250, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101100:27 >>);
862enc_huffman(<< 251, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101101:27 >>);
863enc_huffman(<< 252, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101110:27 >>);
864enc_huffman(<< 253, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111101111:27 >>);
865enc_huffman(<< 254, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#111111111111111111111110000:27 >>);
866enc_huffman(<< 255, R/bits >>, A) -> enc_huffman(R, << A/bits, 2#11111111111111111111101110:26 >>).
867
868-ifdef(TEST).
869req_encode_test() ->
870	%% First request (raw then huffman).
871	Headers1 = [
872		{<<":method">>, <<"GET">>},
873		{<<":scheme">>, <<"http">>},
874		{<<":path">>, <<"/">>},
875		{<<":authority">>, <<"www.example.com">>}
876	],
877	{Raw1, State1} = encode(Headers1, init(), #{huffman => false}),
878	<< 16#828684410f7777772e6578616d706c652e636f6d:160 >> = iolist_to_binary(Raw1),
879	{Huff1, State1} = encode(Headers1),
880	<< 16#828684418cf1e3c2e5f23a6ba0ab90f4ff:136 >> = iolist_to_binary(Huff1),
881	#state{size=57, dyn_table=[{57,{<<":authority">>, <<"www.example.com">>}}]} = State1,
882	%% Second request (raw then huffman).
883	Headers2 = [
884		{<<":method">>, <<"GET">>},
885		{<<":scheme">>, <<"http">>},
886		{<<":path">>, <<"/">>},
887		{<<":authority">>, <<"www.example.com">>},
888		{<<"cache-control">>, <<"no-cache">>}
889	],
890	{Raw2, State2} = encode(Headers2, State1, #{huffman => false}),
891	<< 16#828684be58086e6f2d6361636865:112 >> = iolist_to_binary(Raw2),
892	{Huff2, State2} = encode(Headers2, State1),
893	<< 16#828684be5886a8eb10649cbf:96 >> = iolist_to_binary(Huff2),
894	#state{size=110, dyn_table=[
895		{53,{<<"cache-control">>, <<"no-cache">>}},
896		{57,{<<":authority">>, <<"www.example.com">>}}]} = State2,
897	%% Third request (raw then huffman).
898	Headers3 = [
899		{<<":method">>, <<"GET">>},
900		{<<":scheme">>, <<"https">>},
901		{<<":path">>, <<"/index.html">>},
902		{<<":authority">>, <<"www.example.com">>},
903		{<<"custom-key">>, <<"custom-value">>}
904	],
905	{Raw3, State3} = encode(Headers3, State2, #{huffman => false}),
906	<< 16#828785bf400a637573746f6d2d6b65790c637573746f6d2d76616c7565:232 >> = iolist_to_binary(Raw3),
907	{Huff3, State3} = encode(Headers3, State2),
908	<< 16#828785bf408825a849e95ba97d7f8925a849e95bb8e8b4bf:192 >> = iolist_to_binary(Huff3),
909	#state{size=164, dyn_table=[
910		{54,{<<"custom-key">>, <<"custom-value">>}},
911		{53,{<<"cache-control">>, <<"no-cache">>}},
912		{57,{<<":authority">>, <<"www.example.com">>}}]} = State3,
913	ok.
914
915resp_encode_test() ->
916	%% Use a max_size of 256 to trigger header evictions.
917	State0 = init(256),
918	%% First response (raw then huffman).
919	Headers1 = [
920		{<<":status">>, <<"302">>},
921		{<<"cache-control">>, <<"private">>},
922		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
923		{<<"location">>, <<"https://www.example.com">>}
924	],
925	{Raw1, State1} = encode(Headers1, State0, #{huffman => false}),
926	<< 16#4803333032580770726976617465611d4d6f6e2c203231204f637420323031332032303a31333a323120474d546e1768747470733a2f2f7777772e6578616d706c652e636f6d:560 >> = iolist_to_binary(Raw1),
927	{Huff1, State1} = encode(Headers1, State0),
928	<< 16#488264025885aec3771a4b6196d07abe941054d444a8200595040b8166e082a62d1bff6e919d29ad171863c78f0b97c8e9ae82ae43d3:432 >> = iolist_to_binary(Huff1),
929	#state{size=222, dyn_table=[
930		{63,{<<"location">>, <<"https://www.example.com">>}},
931		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
932		{52,{<<"cache-control">>, <<"private">>}},
933		{42,{<<":status">>, <<"302">>}}]} = State1,
934	%% Second response (raw then huffman).
935	Headers2 = [
936		{<<":status">>, <<"307">>},
937		{<<"cache-control">>, <<"private">>},
938		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
939		{<<"location">>, <<"https://www.example.com">>}
940	],
941	{Raw2, State2} = encode(Headers2, State1, #{huffman => false}),
942	<< 16#4803333037c1c0bf:64 >> = iolist_to_binary(Raw2),
943	{Huff2, State2} = encode(Headers2, State1),
944	<< 16#4883640effc1c0bf:64 >> = iolist_to_binary(Huff2),
945	#state{size=222, dyn_table=[
946		{42,{<<":status">>, <<"307">>}},
947		{63,{<<"location">>, <<"https://www.example.com">>}},
948		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
949		{52,{<<"cache-control">>, <<"private">>}}]} = State2,
950	%% Third response (raw then huffman).
951	Headers3 = [
952		{<<":status">>, <<"200">>},
953		{<<"cache-control">>, <<"private">>},
954		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:22 GMT">>},
955		{<<"location">>, <<"https://www.example.com">>},
956		{<<"content-encoding">>, <<"gzip">>},
957		{<<"set-cookie">>, <<"foo=ASDJKHQKBZXOQWEOPIUAXQWEOIU; max-age=3600; version=1">>}
958	],
959	{Raw3, State3} = encode(Headers3, State2, #{huffman => false}),
960	<< 16#88c1611d4d6f6e2c203231204f637420323031332032303a31333a323220474d54c05a04677a69707738666f6f3d4153444a4b48514b425a584f5157454f50495541585157454f49553b206d61782d6167653d333630303b2076657273696f6e3d31:784 >> = iolist_to_binary(Raw3),
961	{Huff3, State3} = encode(Headers3, State2),
962	<< 16#88c16196d07abe941054d444a8200595040b8166e084a62d1bffc05a839bd9ab77ad94e7821dd7f2e6c7b335dfdfcd5b3960d5af27087f3672c1ab270fb5291f9587316065c003ed4ee5b1063d5007:632 >> = iolist_to_binary(Huff3),
963	#state{size=215, dyn_table=[
964		{98,{<<"set-cookie">>, <<"foo=ASDJKHQKBZXOQWEOPIUAXQWEOIU; max-age=3600; version=1">>}},
965		{52,{<<"content-encoding">>, <<"gzip">>}},
966		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:22 GMT">>}}]} = State3,
967	ok.
968
969%% This test assumes that table updates work correctly when decoding.
970table_update_encode_test() ->
971	%% Use a max_size of 256 to trigger header evictions
972	%% when the code is not updating the max size.
973	DecState0 = EncState0 = init(256),
974	%% First response.
975	Headers1 = [
976		{<<":status">>, <<"302">>},
977		{<<"cache-control">>, <<"private">>},
978		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
979		{<<"location">>, <<"https://www.example.com">>}
980	],
981	{Encoded1, EncState1} = encode(Headers1, EncState0),
982	{Headers1, DecState1} = decode(iolist_to_binary(Encoded1), DecState0),
983	#state{size=222, configured_max_size=256, dyn_table=[
984		{63,{<<"location">>, <<"https://www.example.com">>}},
985		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
986		{52,{<<"cache-control">>, <<"private">>}},
987		{42,{<<":status">>, <<"302">>}}]} = DecState1,
988	#state{size=222, configured_max_size=256, dyn_table=[
989		{63,{<<"location">>, <<"https://www.example.com">>}},
990		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
991		{52,{<<"cache-control">>, <<"private">>}},
992		{42,{<<":status">>, <<"302">>}}]} = EncState1,
993	%% Set a new configured max_size to avoid header evictions.
994	DecState2 = set_max_size(512, DecState1),
995	EncState2 = set_max_size(512, EncState1),
996	%% Second response.
997	Headers2 = [
998		{<<":status">>, <<"307">>},
999		{<<"cache-control">>, <<"private">>},
1000		{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>},
1001		{<<"location">>, <<"https://www.example.com">>}
1002	],
1003	{Encoded2, EncState3} = encode(Headers2, EncState2),
1004	{Headers2, DecState3} = decode(iolist_to_binary(Encoded2), DecState2),
1005	#state{size=264, max_size=512, dyn_table=[
1006		{42,{<<":status">>, <<"307">>}},
1007		{63,{<<"location">>, <<"https://www.example.com">>}},
1008		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
1009		{52,{<<"cache-control">>, <<"private">>}},
1010		{42,{<<":status">>, <<"302">>}}]} = DecState3,
1011	#state{size=264, max_size=512, dyn_table=[
1012		{42,{<<":status">>, <<"307">>}},
1013		{63,{<<"location">>, <<"https://www.example.com">>}},
1014		{65,{<<"date">>, <<"Mon, 21 Oct 2013 20:13:21 GMT">>}},
1015		{52,{<<"cache-control">>, <<"private">>}},
1016		{42,{<<":status">>, <<"302">>}}]} = EncState3,
1017	ok.
1018
1019encode_iolist_test() ->
1020	Headers = [
1021		{<<":method">>, <<"GET">>},
1022		{<<":scheme">>, <<"http">>},
1023		{<<":path">>, <<"/">>},
1024		{<<":authority">>, <<"www.example.com">>},
1025		{<<"content-type">>, [<<"image">>,<<"/">>,<<"png">>,<<>>]}
1026	],
1027	{_, _} = encode(Headers),
1028	ok.
1029
1030horse_encode_raw() ->
1031	horse:repeat(20000,
1032		do_horse_encode_raw()
1033	).
1034
1035do_horse_encode_raw() ->
1036	Headers1 = [
1037		{<<":method">>, <<"GET">>},
1038		{<<":scheme">>, <<"http">>},
1039		{<<":path">>, <<"/">>},
1040		{<<":authority">>, <<"www.example.com">>}
1041	],
1042	{_, State1} = encode(Headers1, init(), #{huffman => false}),
1043	Headers2 = [
1044		{<<":method">>, <<"GET">>},
1045		{<<":scheme">>, <<"http">>},
1046		{<<":path">>, <<"/">>},
1047		{<<":authority">>, <<"www.example.com">>},
1048		{<<"cache-control">>, <<"no-cache">>}
1049	],
1050	{_, State2} = encode(Headers2, State1, #{huffman => false}),
1051	Headers3 = [
1052		{<<":method">>, <<"GET">>},
1053		{<<":scheme">>, <<"https">>},
1054		{<<":path">>, <<"/index.html">>},
1055		{<<":authority">>, <<"www.example.com">>},
1056		{<<"custom-key">>, <<"custom-value">>}
1057	],
1058	{_, _} = encode(Headers3, State2, #{huffman => false}),
1059	ok.
1060
1061horse_encode_huffman() ->
1062	horse:repeat(20000,
1063		do_horse_encode_huffman()
1064	).
1065
1066do_horse_encode_huffman() ->
1067	Headers1 = [
1068		{<<":method">>, <<"GET">>},
1069		{<<":scheme">>, <<"http">>},
1070		{<<":path">>, <<"/">>},
1071		{<<":authority">>, <<"www.example.com">>}
1072	],
1073	{_, State1} = encode(Headers1),
1074	Headers2 = [
1075		{<<":method">>, <<"GET">>},
1076		{<<":scheme">>, <<"http">>},
1077		{<<":path">>, <<"/">>},
1078		{<<":authority">>, <<"www.example.com">>},
1079		{<<"cache-control">>, <<"no-cache">>}
1080	],
1081	{_, State2} = encode(Headers2, State1),
1082	Headers3 = [
1083		{<<":method">>, <<"GET">>},
1084		{<<":scheme">>, <<"https">>},
1085		{<<":path">>, <<"/index.html">>},
1086		{<<":authority">>, <<"www.example.com">>},
1087		{<<"custom-key">>, <<"custom-value">>}
1088	],
1089	{_, _} = encode(Headers3, State2),
1090	ok.
1091-endif.
1092
1093%% Static and dynamic tables.
1094
1095%% @todo There must be a more efficient way.
1096table_find(Header = {Name, _}, State) ->
1097	case table_find_field(Header, State) of
1098		not_found ->
1099			case table_find_name(Name, State) of
1100				NotFound = not_found ->
1101					NotFound;
1102				Found ->
1103					{name, Found}
1104			end;
1105		Found ->
1106			{field, Found}
1107	end.
1108
1109table_find_field({<<":authority">>, <<>>}, _) -> 1;
1110table_find_field({<<":method">>, <<"GET">>}, _) -> 2;
1111table_find_field({<<":method">>, <<"POST">>}, _) -> 3;
1112table_find_field({<<":path">>, <<"/">>}, _) -> 4;
1113table_find_field({<<":path">>, <<"/index.html">>}, _) -> 5;
1114table_find_field({<<":scheme">>, <<"http">>}, _) -> 6;
1115table_find_field({<<":scheme">>, <<"https">>}, _) -> 7;
1116table_find_field({<<":status">>, <<"200">>}, _) -> 8;
1117table_find_field({<<":status">>, <<"204">>}, _) -> 9;
1118table_find_field({<<":status">>, <<"206">>}, _) -> 10;
1119table_find_field({<<":status">>, <<"304">>}, _) -> 11;
1120table_find_field({<<":status">>, <<"400">>}, _) -> 12;
1121table_find_field({<<":status">>, <<"404">>}, _) -> 13;
1122table_find_field({<<":status">>, <<"500">>}, _) -> 14;
1123table_find_field({<<"accept-charset">>, <<>>}, _) -> 15;
1124table_find_field({<<"accept-encoding">>, <<"gzip, deflate">>}, _) -> 16;
1125table_find_field({<<"accept-language">>, <<>>}, _) -> 17;
1126table_find_field({<<"accept-ranges">>, <<>>}, _) -> 18;
1127table_find_field({<<"accept">>, <<>>}, _) -> 19;
1128table_find_field({<<"access-control-allow-origin">>, <<>>}, _) -> 20;
1129table_find_field({<<"age">>, <<>>}, _) -> 21;
1130table_find_field({<<"allow">>, <<>>}, _) -> 22;
1131table_find_field({<<"authorization">>, <<>>}, _) -> 23;
1132table_find_field({<<"cache-control">>, <<>>}, _) -> 24;
1133table_find_field({<<"content-disposition">>, <<>>}, _) -> 25;
1134table_find_field({<<"content-encoding">>, <<>>}, _) -> 26;
1135table_find_field({<<"content-language">>, <<>>}, _) -> 27;
1136table_find_field({<<"content-length">>, <<>>}, _) -> 28;
1137table_find_field({<<"content-location">>, <<>>}, _) -> 29;
1138table_find_field({<<"content-range">>, <<>>}, _) -> 30;
1139table_find_field({<<"content-type">>, <<>>}, _) -> 31;
1140table_find_field({<<"cookie">>, <<>>}, _) -> 32;
1141table_find_field({<<"date">>, <<>>}, _) -> 33;
1142table_find_field({<<"etag">>, <<>>}, _) -> 34;
1143table_find_field({<<"expect">>, <<>>}, _) -> 35;
1144table_find_field({<<"expires">>, <<>>}, _) -> 36;
1145table_find_field({<<"from">>, <<>>}, _) -> 37;
1146table_find_field({<<"host">>, <<>>}, _) -> 38;
1147table_find_field({<<"if-match">>, <<>>}, _) -> 39;
1148table_find_field({<<"if-modified-since">>, <<>>}, _) -> 40;
1149table_find_field({<<"if-none-match">>, <<>>}, _) -> 41;
1150table_find_field({<<"if-range">>, <<>>}, _) -> 42;
1151table_find_field({<<"if-unmodified-since">>, <<>>}, _) -> 43;
1152table_find_field({<<"last-modified">>, <<>>}, _) -> 44;
1153table_find_field({<<"link">>, <<>>}, _) -> 45;
1154table_find_field({<<"location">>, <<>>}, _) -> 46;
1155table_find_field({<<"max-forwards">>, <<>>}, _) -> 47;
1156table_find_field({<<"proxy-authenticate">>, <<>>}, _) -> 48;
1157table_find_field({<<"proxy-authorization">>, <<>>}, _) -> 49;
1158table_find_field({<<"range">>, <<>>}, _) -> 50;
1159table_find_field({<<"referer">>, <<>>}, _) -> 51;
1160table_find_field({<<"refresh">>, <<>>}, _) -> 52;
1161table_find_field({<<"retry-after">>, <<>>}, _) -> 53;
1162table_find_field({<<"server">>, <<>>}, _) -> 54;
1163table_find_field({<<"set-cookie">>, <<>>}, _) -> 55;
1164table_find_field({<<"strict-transport-security">>, <<>>}, _) -> 56;
1165table_find_field({<<"transfer-encoding">>, <<>>}, _) -> 57;
1166table_find_field({<<"user-agent">>, <<>>}, _) -> 58;
1167table_find_field({<<"vary">>, <<>>}, _) -> 59;
1168table_find_field({<<"via">>, <<>>}, _) -> 60;
1169table_find_field({<<"www-authenticate">>, <<>>}, _) -> 61;
1170table_find_field(Header, #state{dyn_table=DynamicTable}) ->
1171	table_find_field_dyn(Header, DynamicTable, 62).
1172
1173table_find_field_dyn(_, [], _) -> not_found;
1174table_find_field_dyn(Header, [{_, Header}|_], Index) -> Index;
1175table_find_field_dyn(Header, [_|Tail], Index) -> table_find_field_dyn(Header, Tail, Index + 1).
1176
1177table_find_name(<<":authority">>, _) -> 1;
1178table_find_name(<<":method">>, _) -> 2;
1179table_find_name(<<":path">>, _) -> 4;
1180table_find_name(<<":scheme">>, _) -> 6;
1181table_find_name(<<":status">>, _) -> 8;
1182table_find_name(<<"accept-charset">>, _) -> 15;
1183table_find_name(<<"accept-encoding">>, _) -> 16;
1184table_find_name(<<"accept-language">>, _) -> 17;
1185table_find_name(<<"accept-ranges">>, _) -> 18;
1186table_find_name(<<"accept">>, _) -> 19;
1187table_find_name(<<"access-control-allow-origin">>, _) -> 20;
1188table_find_name(<<"age">>, _) -> 21;
1189table_find_name(<<"allow">>, _) -> 22;
1190table_find_name(<<"authorization">>, _) -> 23;
1191table_find_name(<<"cache-control">>, _) -> 24;
1192table_find_name(<<"content-disposition">>, _) -> 25;
1193table_find_name(<<"content-encoding">>, _) -> 26;
1194table_find_name(<<"content-language">>, _) -> 27;
1195table_find_name(<<"content-length">>, _) -> 28;
1196table_find_name(<<"content-location">>, _) -> 29;
1197table_find_name(<<"content-range">>, _) -> 30;
1198table_find_name(<<"content-type">>, _) -> 31;
1199table_find_name(<<"cookie">>, _) -> 32;
1200table_find_name(<<"date">>, _) -> 33;
1201table_find_name(<<"etag">>, _) -> 34;
1202table_find_name(<<"expect">>, _) -> 35;
1203table_find_name(<<"expires">>, _) -> 36;
1204table_find_name(<<"from">>, _) -> 37;
1205table_find_name(<<"host">>, _) -> 38;
1206table_find_name(<<"if-match">>, _) -> 39;
1207table_find_name(<<"if-modified-since">>, _) -> 40;
1208table_find_name(<<"if-none-match">>, _) -> 41;
1209table_find_name(<<"if-range">>, _) -> 42;
1210table_find_name(<<"if-unmodified-since">>, _) -> 43;
1211table_find_name(<<"last-modified">>, _) -> 44;
1212table_find_name(<<"link">>, _) -> 45;
1213table_find_name(<<"location">>, _) -> 46;
1214table_find_name(<<"max-forwards">>, _) -> 47;
1215table_find_name(<<"proxy-authenticate">>, _) -> 48;
1216table_find_name(<<"proxy-authorization">>, _) -> 49;
1217table_find_name(<<"range">>, _) -> 50;
1218table_find_name(<<"referer">>, _) -> 51;
1219table_find_name(<<"refresh">>, _) -> 52;
1220table_find_name(<<"retry-after">>, _) -> 53;
1221table_find_name(<<"server">>, _) -> 54;
1222table_find_name(<<"set-cookie">>, _) -> 55;
1223table_find_name(<<"strict-transport-security">>, _) -> 56;
1224table_find_name(<<"transfer-encoding">>, _) -> 57;
1225table_find_name(<<"user-agent">>, _) -> 58;
1226table_find_name(<<"vary">>, _) -> 59;
1227table_find_name(<<"via">>, _) -> 60;
1228table_find_name(<<"www-authenticate">>, _) -> 61;
1229table_find_name(Name, #state{dyn_table=DynamicTable}) ->
1230	table_find_name_dyn(Name, DynamicTable, 62).
1231
1232table_find_name_dyn(_, [], _) -> not_found;
1233table_find_name_dyn(Name, [{Name, _}|_], Index) -> Index;
1234table_find_name_dyn(Name, [_|Tail], Index) -> table_find_name_dyn(Name, Tail, Index + 1).
1235
1236table_get(1, _) -> {<<":authority">>, <<>>};
1237table_get(2, _) -> {<<":method">>, <<"GET">>};
1238table_get(3, _) -> {<<":method">>, <<"POST">>};
1239table_get(4, _) -> {<<":path">>, <<"/">>};
1240table_get(5, _) -> {<<":path">>, <<"/index.html">>};
1241table_get(6, _) -> {<<":scheme">>, <<"http">>};
1242table_get(7, _) -> {<<":scheme">>, <<"https">>};
1243table_get(8, _) -> {<<":status">>, <<"200">>};
1244table_get(9, _) -> {<<":status">>, <<"204">>};
1245table_get(10, _) -> {<<":status">>, <<"206">>};
1246table_get(11, _) -> {<<":status">>, <<"304">>};
1247table_get(12, _) -> {<<":status">>, <<"400">>};
1248table_get(13, _) -> {<<":status">>, <<"404">>};
1249table_get(14, _) -> {<<":status">>, <<"500">>};
1250table_get(15, _) -> {<<"accept-charset">>, <<>>};
1251table_get(16, _) -> {<<"accept-encoding">>, <<"gzip, deflate">>};
1252table_get(17, _) -> {<<"accept-language">>, <<>>};
1253table_get(18, _) -> {<<"accept-ranges">>, <<>>};
1254table_get(19, _) -> {<<"accept">>, <<>>};
1255table_get(20, _) -> {<<"access-control-allow-origin">>, <<>>};
1256table_get(21, _) -> {<<"age">>, <<>>};
1257table_get(22, _) -> {<<"allow">>, <<>>};
1258table_get(23, _) -> {<<"authorization">>, <<>>};
1259table_get(24, _) -> {<<"cache-control">>, <<>>};
1260table_get(25, _) -> {<<"content-disposition">>, <<>>};
1261table_get(26, _) -> {<<"content-encoding">>, <<>>};
1262table_get(27, _) -> {<<"content-language">>, <<>>};
1263table_get(28, _) -> {<<"content-length">>, <<>>};
1264table_get(29, _) -> {<<"content-location">>, <<>>};
1265table_get(30, _) -> {<<"content-range">>, <<>>};
1266table_get(31, _) -> {<<"content-type">>, <<>>};
1267table_get(32, _) -> {<<"cookie">>, <<>>};
1268table_get(33, _) -> {<<"date">>, <<>>};
1269table_get(34, _) -> {<<"etag">>, <<>>};
1270table_get(35, _) -> {<<"expect">>, <<>>};
1271table_get(36, _) -> {<<"expires">>, <<>>};
1272table_get(37, _) -> {<<"from">>, <<>>};
1273table_get(38, _) -> {<<"host">>, <<>>};
1274table_get(39, _) -> {<<"if-match">>, <<>>};
1275table_get(40, _) -> {<<"if-modified-since">>, <<>>};
1276table_get(41, _) -> {<<"if-none-match">>, <<>>};
1277table_get(42, _) -> {<<"if-range">>, <<>>};
1278table_get(43, _) -> {<<"if-unmodified-since">>, <<>>};
1279table_get(44, _) -> {<<"last-modified">>, <<>>};
1280table_get(45, _) -> {<<"link">>, <<>>};
1281table_get(46, _) -> {<<"location">>, <<>>};
1282table_get(47, _) -> {<<"max-forwards">>, <<>>};
1283table_get(48, _) -> {<<"proxy-authenticate">>, <<>>};
1284table_get(49, _) -> {<<"proxy-authorization">>, <<>>};
1285table_get(50, _) -> {<<"range">>, <<>>};
1286table_get(51, _) -> {<<"referer">>, <<>>};
1287table_get(52, _) -> {<<"refresh">>, <<>>};
1288table_get(53, _) -> {<<"retry-after">>, <<>>};
1289table_get(54, _) -> {<<"server">>, <<>>};
1290table_get(55, _) -> {<<"set-cookie">>, <<>>};
1291table_get(56, _) -> {<<"strict-transport-security">>, <<>>};
1292table_get(57, _) -> {<<"transfer-encoding">>, <<>>};
1293table_get(58, _) -> {<<"user-agent">>, <<>>};
1294table_get(59, _) -> {<<"vary">>, <<>>};
1295table_get(60, _) -> {<<"via">>, <<>>};
1296table_get(61, _) -> {<<"www-authenticate">>, <<>>};
1297table_get(Index, #state{dyn_table=DynamicTable}) ->
1298	{_, Header} = lists:nth(Index - 61, DynamicTable),
1299	Header.
1300
1301table_get_name(1, _) -> <<":authority">>;
1302table_get_name(2, _) -> <<":method">>;
1303table_get_name(3, _) -> <<":method">>;
1304table_get_name(4, _) -> <<":path">>;
1305table_get_name(5, _) -> <<":path">>;
1306table_get_name(6, _) -> <<":scheme">>;
1307table_get_name(7, _) -> <<":scheme">>;
1308table_get_name(8, _) -> <<":status">>;
1309table_get_name(9, _) -> <<":status">>;
1310table_get_name(10, _) -> <<":status">>;
1311table_get_name(11, _) -> <<":status">>;
1312table_get_name(12, _) -> <<":status">>;
1313table_get_name(13, _) -> <<":status">>;
1314table_get_name(14, _) -> <<":status">>;
1315table_get_name(15, _) -> <<"accept-charset">>;
1316table_get_name(16, _) -> <<"accept-encoding">>;
1317table_get_name(17, _) -> <<"accept-language">>;
1318table_get_name(18, _) -> <<"accept-ranges">>;
1319table_get_name(19, _) -> <<"accept">>;
1320table_get_name(20, _) -> <<"access-control-allow-origin">>;
1321table_get_name(21, _) -> <<"age">>;
1322table_get_name(22, _) -> <<"allow">>;
1323table_get_name(23, _) -> <<"authorization">>;
1324table_get_name(24, _) -> <<"cache-control">>;
1325table_get_name(25, _) -> <<"content-disposition">>;
1326table_get_name(26, _) -> <<"content-encoding">>;
1327table_get_name(27, _) -> <<"content-language">>;
1328table_get_name(28, _) -> <<"content-length">>;
1329table_get_name(29, _) -> <<"content-location">>;
1330table_get_name(30, _) -> <<"content-range">>;
1331table_get_name(31, _) -> <<"content-type">>;
1332table_get_name(32, _) -> <<"cookie">>;
1333table_get_name(33, _) -> <<"date">>;
1334table_get_name(34, _) -> <<"etag">>;
1335table_get_name(35, _) -> <<"expect">>;
1336table_get_name(36, _) -> <<"expires">>;
1337table_get_name(37, _) -> <<"from">>;
1338table_get_name(38, _) -> <<"host">>;
1339table_get_name(39, _) -> <<"if-match">>;
1340table_get_name(40, _) -> <<"if-modified-since">>;
1341table_get_name(41, _) -> <<"if-none-match">>;
1342table_get_name(42, _) -> <<"if-range">>;
1343table_get_name(43, _) -> <<"if-unmodified-since">>;
1344table_get_name(44, _) -> <<"last-modified">>;
1345table_get_name(45, _) -> <<"link">>;
1346table_get_name(46, _) -> <<"location">>;
1347table_get_name(47, _) -> <<"max-forwards">>;
1348table_get_name(48, _) -> <<"proxy-authenticate">>;
1349table_get_name(49, _) -> <<"proxy-authorization">>;
1350table_get_name(50, _) -> <<"range">>;
1351table_get_name(51, _) -> <<"referer">>;
1352table_get_name(52, _) -> <<"refresh">>;
1353table_get_name(53, _) -> <<"retry-after">>;
1354table_get_name(54, _) -> <<"server">>;
1355table_get_name(55, _) -> <<"set-cookie">>;
1356table_get_name(56, _) -> <<"strict-transport-security">>;
1357table_get_name(57, _) -> <<"transfer-encoding">>;
1358table_get_name(58, _) -> <<"user-agent">>;
1359table_get_name(59, _) -> <<"vary">>;
1360table_get_name(60, _) -> <<"via">>;
1361table_get_name(61, _) -> <<"www-authenticate">>;
1362table_get_name(Index, #state{dyn_table=DynamicTable}) ->
1363	{_, {Name, _}} = lists:nth(Index - 61, DynamicTable),
1364	Name.
1365
1366table_insert(Entry = {Name, Value}, State=#state{size=Size, max_size=MaxSize, dyn_table=DynamicTable}) ->
1367	EntrySize = byte_size(Name) + byte_size(Value) + 32,
1368	{DynamicTable2, Size2} = if
1369		Size + EntrySize > MaxSize ->
1370			table_resize(DynamicTable, MaxSize - EntrySize, 0, []);
1371		true ->
1372			{DynamicTable, Size}
1373	end,
1374	State#state{size=Size2 + EntrySize, dyn_table=[{EntrySize, Entry}|DynamicTable2]}.
1375
1376table_resize([], _, Size, Acc) ->
1377	{lists:reverse(Acc), Size};
1378table_resize([{EntrySize, _}|_], MaxSize, Size, Acc) when Size + EntrySize > MaxSize ->
1379	{lists:reverse(Acc), Size};
1380table_resize([Entry = {EntrySize, _}|Tail], MaxSize, Size, Acc) ->
1381	table_resize(Tail, MaxSize, Size + EntrySize, [Entry|Acc]).
1382
1383table_update_size(0, State) ->
1384	State#state{size=0, max_size=0, dyn_table=[]};
1385table_update_size(MaxSize, State=#state{max_size=CurrentMaxSize})
1386		when CurrentMaxSize =< MaxSize ->
1387	State#state{max_size=MaxSize};
1388table_update_size(MaxSize, State=#state{dyn_table=DynTable}) ->
1389	{DynTable2, Size} = table_resize(DynTable, MaxSize, 0, []),
1390	State#state{size=Size, max_size=MaxSize, dyn_table=DynTable2}.
1391
1392-ifdef(TEST).
1393prop_str_raw() ->
1394	?FORALL(Str, binary(), begin
1395		{Str, <<>>} =:= dec_str(iolist_to_binary(enc_str(Str, no_huffman)))
1396	end).
1397
1398prop_str_huffman() ->
1399	?FORALL(Str, binary(), begin
1400		{Str, <<>>} =:= dec_str(iolist_to_binary(enc_str(Str, huffman)))
1401	end).
1402-endif.
1403