@@ -195,6 +195,13 @@ only_simulated() ->
195195 redirect_relative_uri ,
196196 port_in_host_header ,
197197 redirect_port_in_host_header ,
198+ te_header_undefined_no_connection ,
199+ te_header_empty_string_adds_connection ,
200+ te_header_whitespace_adds_connection ,
201+ te_header_trailers_adds_connection ,
202+ te_header_with_existing_connection ,
203+ te_header_with_connection_close ,
204+ te_header_already_in_connection ,
198205 relaxed ,
199206 multipart_chunks ,
200207 get_space ,
@@ -273,8 +280,18 @@ init_per_group(http_unix_socket = Group, Config0) ->
273280 lists :append ([{dummy_server_pid , Pid }, {port , Port }, {httpc_options , HttpcOpts }],
274281 Config )
275282 end ;
276- init_per_group (Group , Config0 ) when Group == http_ipv6 ;
277- Group == sim_http_ipv6 ->
283+ init_per_group (sim_http_ipv6 = Group , Config0 ) ->
284+ case is_ipv6_supported () of
285+ true ->
286+ start_apps (Group ),
287+ Config = proplists :delete (port , Config0 ),
288+ Port = server_start (Group , server_config (Group , Config )),
289+ [{port , Port }, {httpc_options , [{ipfamily , inet6 }]} | Config ];
290+ false ->
291+ {skip , " Host does not support IPv6" }
292+ end ;
293+
294+ init_per_group (http_ipv6 = Group , Config0 ) ->
278295 case is_ipv6_supported () of
279296 true ->
280297 start_apps (Group ),
@@ -283,7 +300,7 @@ init_per_group(Group, Config0) when Group == http_ipv6;
283300 [{port , Port }, {request_opts , [{socket_opts , [{ipfamily , inet6 }]}]} | Config ];
284301 false ->
285302 {skip , " Host does not support IPv6" }
286- end ;
303+ end ;
287304init_per_group (Group , Config0 ) ->
288305 start_apps (Group ),
289306 Config = proplists :delete (port , Config0 ),
@@ -1687,6 +1704,55 @@ redirect_port_in_host_header(Config) when is_list(Config) ->
16871704 RequestOpts , ? profile (Config )),
16881705 inets_test_lib :check_body (Body ).
16891706
1707+ % %-------------------------------------------------------------------------
1708+ te_header_undefined_no_connection (Config ) when is_list (Config ) ->
1709+ Request = {url (group_name (Config ), " /te_header_undefined_no_connection.html" , Config ), []},
1710+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1711+ [], ? profile (Config )),
1712+ inets_test_lib :check_body (Body ).
1713+
1714+ % %-------------------------------------------------------------------------
1715+ te_header_empty_string_adds_connection (Config ) when is_list (Config ) ->
1716+ Request = {url (group_name (Config ), " /te_header_empty_string_adds_connection.html" , Config ), [{" te" , " " }]},
1717+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1718+ [], ? profile (Config )),
1719+ inets_test_lib :check_body (Body ).
1720+
1721+ % %-------------------------------------------------------------------------
1722+ te_header_whitespace_adds_connection (Config ) when is_list (Config ) ->
1723+ Request = {url (group_name (Config ), " /te_header_whitespace_adds_connection.html" , Config ), [{" te" , " " }]},
1724+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1725+ [], ? profile (Config )),
1726+ inets_test_lib :check_body (Body ).
1727+
1728+ % %-------------------------------------------------------------------------
1729+ te_header_trailers_adds_connection (Config ) when is_list (Config ) ->
1730+ Request = {url (group_name (Config ), " /te_header_trailers_adds_connection.html" , Config ), [{" te" , " trailers" }]},
1731+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1732+ [], ? profile (Config )),
1733+ inets_test_lib :check_body (Body ).
1734+
1735+ % %-------------------------------------------------------------------------
1736+ te_header_with_existing_connection (Config ) when is_list (Config ) ->
1737+ Request = {url (group_name (Config ), " /te_header_with_existing_connection.html" , Config ), [{" te" , " trailers" }, {" connection" , " keep-alive" }]},
1738+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1739+ [], ? profile (Config )),
1740+ inets_test_lib :check_body (Body ).
1741+
1742+ % %-------------------------------------------------------------------------
1743+ te_header_with_connection_close (Config ) when is_list (Config ) ->
1744+ Request = {url (group_name (Config ), " /te_header_with_connection_close.html" , Config ), [{" te" , " trailers" }, {" connection" , " close" }]},
1745+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1746+ [], ? profile (Config )),
1747+ inets_test_lib :check_body (Body ).
1748+
1749+ % %-------------------------------------------------------------------------
1750+ te_header_already_in_connection (Config ) when is_list (Config ) ->
1751+ Request = {url (group_name (Config ), " /te_header_already_in_connection.html" , Config ), [{" te" , " trailers" }, {" connection" , " keep-alive, TE" }]},
1752+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1753+ [], ? profile (Config )),
1754+ inets_test_lib :check_body (Body ).
1755+
16901756% %-------------------------------------------------------------------------
16911757multipart_chunks (Config ) when is_list (Config ) ->
16921758 Request = {url (group_name (Config ), " /multipart_chunks.html" , Config ), []},
@@ -2580,6 +2646,22 @@ content_length([{"content-length", Value}|_]) ->
25802646content_length ([_Head | Tail ]) ->
25812647 content_length (Tail ).
25822648
2649+ header_matches (Headers , HeaderName , ExpectedValue ) ->
2650+ MatchingHeaders = [Value || {Name , Value } <- Headers , Name =:= HeaderName ],
2651+ case {MatchingHeaders , ExpectedValue } of
2652+ {[], undefined } ->
2653+ true ;
2654+ {[], _ } ->
2655+ io_lib :format (" Expected ~s : \" ~ts \" but header not found" , [HeaderName , ExpectedValue ]);
2656+ {[ActualValue ], ActualValue } ->
2657+ true ;
2658+ {[ActualValue ], _ } ->
2659+ io_lib :format (" Expected ~s : \" ~ts \" but got: \" ~ts \" " , [HeaderName , ExpectedValue , ActualValue ]);
2660+ {Multiple , _ } ->
2661+ io_lib :format (" Expected single ~s header but found ~p instances: ~p " ,
2662+ [HeaderName , length (Multiple ), Multiple ])
2663+ end .
2664+
25832665handle_uri (" GET" ," /dummy.html?foo=bar" ,_ ,_ ,_ ,_ ) ->
25842666 " HTTP/1.0 200 OK\r\n\r\n TEST" ;
25852667
@@ -2627,6 +2709,125 @@ handle_uri(_,"/redirect_ensure_host_header_with_port.html",Port,_,Socket,_) ->
26272709 " Location:" ++ NewUri ++ " \r\n " ++
26282710 " Content-Length:0\r\n\r\n " ;
26292711
2712+ handle_uri (_ ," /te_header_undefined_no_connection.html" ,_ ,Headers ,_ ,_ ) ->
2713+ case {header_matches (Headers , " te" , undefined ),
2714+ header_matches (Headers , " connection" , " keep-alive" )} of
2715+ {true , true } ->
2716+ B = " <HTML><BODY>TE header undefined - Connection not modified</BODY></HTML>" ,
2717+ Len = integer_to_list (length (B )),
2718+ " HTTP/1.1 200 OK\r\n " ++
2719+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2720+ {TEResult , ConnResult } ->
2721+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2722+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2723+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2724+ Len = integer_to_list (length (B )),
2725+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2726+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2727+ end ;
2728+
2729+ handle_uri (_ ," /te_header_empty_string_adds_connection.html" ,_ ,Headers ,_ ,_ ) ->
2730+ case {header_matches (Headers , " te" , " " ),
2731+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2732+ {true , true } ->
2733+ B = " <HTML><BODY>TE empty string - Connection header contains TE</BODY></HTML>" ,
2734+ Len = integer_to_list (length (B )),
2735+ " HTTP/1.1 200 OK\r\n " ++
2736+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2737+ {TEResult , ConnResult } ->
2738+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2739+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2740+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2741+ Len = integer_to_list (length (B )),
2742+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2743+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2744+ end ;
2745+
2746+ handle_uri (_ ," /te_header_whitespace_adds_connection.html" ,_ ,Headers ,_ ,_ ) ->
2747+ case {header_matches (Headers , " te" , " " ),
2748+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2749+ {true , true } ->
2750+ B = " <HTML><BODY>TE whitespace - Connection header contains TE</BODY></HTML>" ,
2751+ Len = integer_to_list (length (B )),
2752+ " HTTP/1.1 200 OK\r\n " ++
2753+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2754+ {TEResult , ConnResult } ->
2755+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2756+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2757+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2758+ Len = integer_to_list (length (B )),
2759+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2760+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2761+ end ;
2762+
2763+ handle_uri (_ ," /te_header_trailers_adds_connection.html" ,_ ,Headers ,_ ,_ ) ->
2764+ case {header_matches (Headers , " te" , " trailers" ),
2765+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2766+ {true , true } ->
2767+ B = " <HTML><BODY>TE trailers - Connection header contains TE</BODY></HTML>" ,
2768+ Len = integer_to_list (length (B )),
2769+ " HTTP/1.1 200 OK\r\n " ++
2770+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2771+ {TEResult , ConnResult } ->
2772+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2773+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2774+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2775+ Len = integer_to_list (length (B )),
2776+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2777+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2778+ end ;
2779+
2780+ handle_uri (_ ," /te_header_with_existing_connection.html" ,_ ,Headers ,_ ,_ ) ->
2781+ case {header_matches (Headers , " te" , " trailers" ),
2782+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2783+ {true , true } ->
2784+ B = " <HTML><BODY>TE with existing Connection - both keep-alive and TE present</BODY></HTML>" ,
2785+ Len = integer_to_list (length (B )),
2786+ " HTTP/1.1 200 OK\r\n " ++
2787+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2788+ {TEResult , ConnResult } ->
2789+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2790+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2791+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2792+ Len = integer_to_list (length (B )),
2793+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2794+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2795+ end ;
2796+
2797+ handle_uri (_ ," /te_header_with_connection_close.html" ,_ ,Headers ,_ ,_ ) ->
2798+ case {header_matches (Headers , " te" , " trailers" ),
2799+ header_matches (Headers , " connection" , " close, TE" )} of
2800+ {true , true } ->
2801+ B = " <HTML><BODY>TE with Connection close - both close and TE present</BODY></HTML>" ,
2802+ Len = integer_to_list (length (B )),
2803+ " HTTP/1.1 200 OK\r\n " ++
2804+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2805+ {TEResult , ConnResult } ->
2806+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2807+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2808+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2809+ Len = integer_to_list (length (B )),
2810+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2811+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2812+ end ;
2813+
2814+ handle_uri (_ ," /te_header_already_in_connection.html" ,_ ,Headers ,_ ,_ ) ->
2815+ case {header_matches (Headers , " te" , " trailers" ),
2816+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2817+ {true , true } ->
2818+ B = " <HTML><BODY>TE already in Connection - TE not duplicated</BODY></HTML>" ,
2819+ Len = integer_to_list (length (B )),
2820+ " HTTP/1.1 200 OK\r\n " ++
2821+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2822+ {TEResult , ConnResult } ->
2823+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2824+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2825+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2826+ Len = integer_to_list (length (B )),
2827+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2828+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2829+ end ;
2830+
26302831handle_uri (_ ," /300.html" ,Port ,_ ,Socket ,_ ) ->
26312832 NewUri = url_start (Socket ) ++
26322833 integer_to_list (Port ) ++ " /dummy.html" ,
0 commit comments