3737-define (URL_START , " http://" ).
3838-define (TLS_URL_START , " https://" ).
3939-define (NOT_IN_USE_PORT , 8997 ).
40+ -define (profile (Config ), proplists :get_value (profile , Config , httpc :default_profile ())).
4041
4142-define (SSL_NO_VERIFY , {ssl , [{verify , verify_none }]}).
4243
@@ -195,6 +196,13 @@ only_simulated() ->
195196 redirect_relative_uri ,
196197 port_in_host_header ,
197198 redirect_port_in_host_header ,
199+ te_header_undefined_no_connection ,
200+ te_header_empty_string_adds_connection ,
201+ te_header_whitespace_adds_connection ,
202+ te_header_trailers_adds_connection ,
203+ te_header_with_existing_connection ,
204+ te_header_with_connection_close ,
205+ te_header_already_in_connection ,
198206 relaxed ,
199207 multipart_chunks ,
200208 get_space ,
@@ -274,8 +282,18 @@ init_per_group(http_unix_socket = Group, Config0) ->
274282 {Pid , Port } = server_start (Group , server_config (Group , Config )),
275283 lists :append ([{dummy_server_pid , Pid }, {port , Port }], Config )
276284 end ;
277- init_per_group (Group , Config0 ) when Group == http_ipv6 ;
278- Group == sim_http_ipv6 ->
285+ init_per_group (sim_http_ipv6 = Group , Config0 ) ->
286+ case is_ipv6_supported () of
287+ true ->
288+ start_apps (Group ),
289+ Config = proplists :delete (port , Config0 ),
290+ Port = server_start (Group , server_config (Group , Config )),
291+ [{port , Port }, {httpc_options , [{ipfamily , inet6 }]} | Config ];
292+ false ->
293+ {skip , " Host does not support IPv6" }
294+ end ;
295+
296+ init_per_group (http_ipv6 = Group , Config0 ) ->
279297 case is_ipv6_supported () of
280298 true ->
281299 start_apps (Group ),
@@ -284,7 +302,7 @@ init_per_group(Group, Config0) when Group == http_ipv6;
284302 [{port , Port }, {request_opts , [{socket_opts , [{ipfamily , inet6 }]}]} | Config ];
285303 false ->
286304 {skip , " Host does not support IPv6" }
287- end ;
305+ end ;
288306init_per_group (Group , Config0 ) ->
289307 start_apps (Group ),
290308 Config = proplists :delete (port , Config0 ),
@@ -1642,6 +1660,55 @@ redirect_port_in_host_header(Config) when is_list(Config) ->
16421660 {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [], RequestOpts ),
16431661 inets_test_lib :check_body (Body ).
16441662
1663+ % %-------------------------------------------------------------------------
1664+ te_header_undefined_no_connection (Config ) when is_list (Config ) ->
1665+ Request = {url (group_name (Config ), " /te_header_undefined_no_connection.html" , Config ), []},
1666+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1667+ [], ? profile (Config )),
1668+ inets_test_lib :check_body (Body ).
1669+
1670+ % %-------------------------------------------------------------------------
1671+ te_header_empty_string_adds_connection (Config ) when is_list (Config ) ->
1672+ Request = {url (group_name (Config ), " /te_header_empty_string_adds_connection.html" , Config ), [{" te" , " " }]},
1673+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1674+ [], ? profile (Config )),
1675+ inets_test_lib :check_body (Body ).
1676+
1677+ % %-------------------------------------------------------------------------
1678+ te_header_whitespace_adds_connection (Config ) when is_list (Config ) ->
1679+ Request = {url (group_name (Config ), " /te_header_whitespace_adds_connection.html" , Config ), [{" te" , " " }]},
1680+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1681+ [], ? profile (Config )),
1682+ inets_test_lib :check_body (Body ).
1683+
1684+ % %-------------------------------------------------------------------------
1685+ te_header_trailers_adds_connection (Config ) when is_list (Config ) ->
1686+ Request = {url (group_name (Config ), " /te_header_trailers_adds_connection.html" , Config ), [{" te" , " trailers" }]},
1687+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1688+ [], ? profile (Config )),
1689+ inets_test_lib :check_body (Body ).
1690+
1691+ % %-------------------------------------------------------------------------
1692+ te_header_with_existing_connection (Config ) when is_list (Config ) ->
1693+ Request = {url (group_name (Config ), " /te_header_with_existing_connection.html" , Config ), [{" te" , " trailers" }, {" connection" , " keep-alive" }]},
1694+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1695+ [], ? profile (Config )),
1696+ inets_test_lib :check_body (Body ).
1697+
1698+ % %-------------------------------------------------------------------------
1699+ te_header_with_connection_close (Config ) when is_list (Config ) ->
1700+ Request = {url (group_name (Config ), " /te_header_with_connection_close.html" , Config ), [{" te" , " trailers" }, {" connection" , " close" }]},
1701+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1702+ [], ? profile (Config )),
1703+ inets_test_lib :check_body (Body ).
1704+
1705+ % %-------------------------------------------------------------------------
1706+ te_header_already_in_connection (Config ) when is_list (Config ) ->
1707+ Request = {url (group_name (Config ), " /te_header_already_in_connection.html" , Config ), [{" te" , " trailers" }, {" connection" , " keep-alive, TE" }]},
1708+ {ok , {{_ , 200 , _ }, _ , Body }} = httpc :request (get , Request , [? SSL_NO_VERIFY ],
1709+ [], ? profile (Config )),
1710+ inets_test_lib :check_body (Body ).
1711+
16451712% %-------------------------------------------------------------------------
16461713multipart_chunks (Config ) when is_list (Config ) ->
16471714 Request = {url (group_name (Config ), " /multipart_chunks.html" , Config ), []},
@@ -2492,6 +2559,22 @@ content_length([{"content-length", Value}|_]) ->
24922559content_length ([_Head | Tail ]) ->
24932560 content_length (Tail ).
24942561
2562+ header_matches (Headers , HeaderName , ExpectedValue ) ->
2563+ MatchingHeaders = [Value || {Name , Value } <- Headers , Name =:= HeaderName ],
2564+ case {MatchingHeaders , ExpectedValue } of
2565+ {[], undefined } ->
2566+ true ;
2567+ {[], _ } ->
2568+ io_lib :format (" Expected ~s : \" ~ts \" but header not found" , [HeaderName , ExpectedValue ]);
2569+ {[ActualValue ], ActualValue } ->
2570+ true ;
2571+ {[ActualValue ], _ } ->
2572+ io_lib :format (" Expected ~s : \" ~ts \" but got: \" ~ts \" " , [HeaderName , ExpectedValue , ActualValue ]);
2573+ {Multiple , _ } ->
2574+ io_lib :format (" Expected single ~s header but found ~p instances: ~p " ,
2575+ [HeaderName , length (Multiple ), Multiple ])
2576+ end .
2577+
24952578handle_uri (" GET" ," /dummy.html?foo=bar" ,_ ,_ ,_ ,_ ) ->
24962579 " HTTP/1.0 200 OK\r\n\r\n TEST" ;
24972580
@@ -2539,6 +2622,125 @@ handle_uri(_,"/redirect_ensure_host_header_with_port.html",Port,_,Socket,_) ->
25392622 " Location:" ++ NewUri ++ " \r\n " ++
25402623 " Content-Length:0\r\n\r\n " ;
25412624
2625+ handle_uri (_ ," /te_header_undefined_no_connection.html" ,_ ,Headers ,_ ,_ ) ->
2626+ case {header_matches (Headers , " te" , undefined ),
2627+ header_matches (Headers , " connection" , " keep-alive" )} of
2628+ {true , true } ->
2629+ B = " <HTML><BODY>TE header undefined - Connection not modified</BODY></HTML>" ,
2630+ Len = integer_to_list (length (B )),
2631+ " HTTP/1.1 200 OK\r\n " ++
2632+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2633+ {TEResult , ConnResult } ->
2634+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2635+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2636+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2637+ Len = integer_to_list (length (B )),
2638+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2639+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2640+ end ;
2641+
2642+ handle_uri (_ ," /te_header_empty_string_adds_connection.html" ,_ ,Headers ,_ ,_ ) ->
2643+ case {header_matches (Headers , " te" , " " ),
2644+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2645+ {true , true } ->
2646+ B = " <HTML><BODY>TE empty string - Connection header contains TE</BODY></HTML>" ,
2647+ Len = integer_to_list (length (B )),
2648+ " HTTP/1.1 200 OK\r\n " ++
2649+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2650+ {TEResult , ConnResult } ->
2651+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2652+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2653+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2654+ Len = integer_to_list (length (B )),
2655+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2656+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2657+ end ;
2658+
2659+ handle_uri (_ ," /te_header_whitespace_adds_connection.html" ,_ ,Headers ,_ ,_ ) ->
2660+ case {header_matches (Headers , " te" , " " ),
2661+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2662+ {true , true } ->
2663+ B = " <HTML><BODY>TE whitespace - Connection header contains TE</BODY></HTML>" ,
2664+ Len = integer_to_list (length (B )),
2665+ " HTTP/1.1 200 OK\r\n " ++
2666+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2667+ {TEResult , ConnResult } ->
2668+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2669+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2670+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2671+ Len = integer_to_list (length (B )),
2672+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2673+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2674+ end ;
2675+
2676+ handle_uri (_ ," /te_header_trailers_adds_connection.html" ,_ ,Headers ,_ ,_ ) ->
2677+ case {header_matches (Headers , " te" , " trailers" ),
2678+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2679+ {true , true } ->
2680+ B = " <HTML><BODY>TE trailers - Connection header contains TE</BODY></HTML>" ,
2681+ Len = integer_to_list (length (B )),
2682+ " HTTP/1.1 200 OK\r\n " ++
2683+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2684+ {TEResult , ConnResult } ->
2685+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2686+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2687+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2688+ Len = integer_to_list (length (B )),
2689+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2690+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2691+ end ;
2692+
2693+ handle_uri (_ ," /te_header_with_existing_connection.html" ,_ ,Headers ,_ ,_ ) ->
2694+ case {header_matches (Headers , " te" , " trailers" ),
2695+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2696+ {true , true } ->
2697+ B = " <HTML><BODY>TE with existing Connection - both keep-alive and TE present</BODY></HTML>" ,
2698+ Len = integer_to_list (length (B )),
2699+ " HTTP/1.1 200 OK\r\n " ++
2700+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2701+ {TEResult , ConnResult } ->
2702+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2703+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2704+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2705+ Len = integer_to_list (length (B )),
2706+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2707+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2708+ end ;
2709+
2710+ handle_uri (_ ," /te_header_with_connection_close.html" ,_ ,Headers ,_ ,_ ) ->
2711+ case {header_matches (Headers , " te" , " trailers" ),
2712+ header_matches (Headers , " connection" , " close, TE" )} of
2713+ {true , true } ->
2714+ B = " <HTML><BODY>TE with Connection close - both close and TE present</BODY></HTML>" ,
2715+ Len = integer_to_list (length (B )),
2716+ " HTTP/1.1 200 OK\r\n " ++
2717+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2718+ {TEResult , ConnResult } ->
2719+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2720+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2721+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2722+ Len = integer_to_list (length (B )),
2723+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2724+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2725+ end ;
2726+
2727+ handle_uri (_ ," /te_header_already_in_connection.html" ,_ ,Headers ,_ ,_ ) ->
2728+ case {header_matches (Headers , " te" , " trailers" ),
2729+ header_matches (Headers , " connection" , " keep-alive, TE" )} of
2730+ {true , true } ->
2731+ B = " <HTML><BODY>TE already in Connection - TE not duplicated</BODY></HTML>" ,
2732+ Len = integer_to_list (length (B )),
2733+ " HTTP/1.1 200 OK\r\n " ++
2734+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B ;
2735+ {TEResult , ConnResult } ->
2736+ Errors = [Error || Error <- [TEResult , ConnResult ], Error =/= true ],
2737+ ErrorMsg = string :join ([lists :flatten (E ) || E <- Errors ], " ; " ),
2738+ B = " <HTML><BODY>ERROR: " ++ ErrorMsg ++ " </BODY></HTML>" ,
2739+ Len = integer_to_list (length (B )),
2740+ " HTTP/1.1 500 Internal Server Error\r\n " ++
2741+ " Content-Length:" ++ Len ++ " \r\n\r\n " ++ B
2742+ end ;
2743+
25422744handle_uri (_ ," /300.html" ,Port ,_ ,Socket ,_ ) ->
25432745 NewUri = url_start (Socket ) ++
25442746 integer_to_list (Port ) ++ " /dummy.html" ,
0 commit comments