Skip to content

Commit

Permalink
Merge pull request #2738 from dmitrivereshchagin/empty-if-none-match
Browse files Browse the repository at this point in the history
Do not send empty If-None-Match in tarball request
  • Loading branch information
ferd committed Aug 22, 2022
2 parents 0d95d08 + 2828bdb commit c0c5a0e
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 6 deletions.
12 changes: 6 additions & 6 deletions apps/rebar/src/rebar_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ format_error({bad_registry_checksum, Name, Vsn, Expected, Found}) ->
%% {ok, Contents, NewEtag}, otherwise if some error occurred return error.
%% @end
%%------------------------------------------------------------------------------
-spec request(rebar_hex_repos:repo(), binary(), binary(), false | binary())
-spec request(rebar_hex_repos:repo(), binary(), binary(), binary() | undefined)
-> {ok, cached} | {ok, binary(), binary()} | error.
request(Config, Name, Version, ETag) ->
Config1 = Config#{http_etag => ETag},
Expand Down Expand Up @@ -169,7 +169,7 @@ request(Config, Name, Version, ETag) ->
-spec etag(PackagePath, ETagPath) -> Res when
PackagePath :: file:name(),
ETagPath :: file:name(),
Res :: binary().
Res :: binary() | undefined.
etag(PackagePath, ETagPath) ->
case file:read_file(ETagPath) of
{ok, Bin} ->
Expand All @@ -179,10 +179,10 @@ etag(PackagePath, ETagPath) ->
true ->
Bin;
false ->
<<>>
undefined
end;
{error, _} ->
<<>>
undefined
end.

%%------------------------------------------------------------------------------
Expand All @@ -205,7 +205,7 @@ store_etag_in_cache(Path, ETag) ->
CachePath :: file:name(),
Pkg :: package(),
State :: rebar_state:t(),
ETag :: binary(),
ETag :: binary() | undefined,
ETagPath :: file:name(),
UpdateETag :: boolean(),
Res :: ok | {unexpected_hash, integer(), integer()} | {fetch_fail, binary(), binary()}
Expand All @@ -222,7 +222,7 @@ cached_download(TmpDir, CachePath, Pkg={pkg, Name, Vsn, _OldHash, _Hash, RepoCon
?DEBUG("Downloaded package ~ts, caching at ~ts", [Name, CachePath]),
maybe_store_etag_in_cache(UpdateETag, ETagPath, NewETag),
serve_from_download(TmpDir, CachePath, Pkg, Body);
error when ETag =/= <<>> ->
error when ETag =/= undefined ->
store_etag_in_cache(ETagPath, ETag),
?INFO("Download error, using cached file at ~ts", [CachePath]),
serve_from_cache(TmpDir, CachePath, Pkg);
Expand Down
6 changes: 6 additions & 0 deletions apps/rebar/test/rebar_pkg_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,8 @@ good_uncached(Config) ->
State = ?config(state, Config),
?assertEqual(ok,
rebar_pkg_resource:download(Tmp, {pkg, Pkg, Vsn, ?good_checksum, ?good_checksum, #{}}, State, #{}, true)),
?assert(meck:called(r3_hex_repo, get_tarball,
[meck:is(fun(#{http_etag := T}) -> T =:= undefined end), '_', '_'])),
Cache = ?config(cache_dir, Config),
?assert(filelib:is_regular(filename:join(Cache, <<Pkg/binary, "-", Vsn/binary, ".tar">>))).

Expand All @@ -127,9 +129,13 @@ good_cached(Config) ->
Cache = ?config(cache_dir, Config),
CachedFile = filename:join(Cache, <<Pkg/binary, "-", Vsn/binary, ".tar">>),
?assert(filelib:is_regular(CachedFile)),
ETagPath = filename:join(Cache, <<Pkg/binary, "-", Vsn/binary, ".etag">>),
rebar_pkg_resource:store_etag_in_cache(ETagPath, ?good_etag),
{ok, Content} = file:read_file(CachedFile),
?assertEqual(ok,
rebar_pkg_resource:download(Tmp, {pkg, Pkg, Vsn, ?good_checksum, ?good_checksum, #{}}, State, #{}, true)),
?assert(meck:called(r3_hex_repo, get_tarball,
[meck:is(fun(#{http_etag := T}) -> T =:= ?good_etag end), '_', '_'])),
{ok, Content} = file:read_file(CachedFile).


Expand Down

0 comments on commit c0c5a0e

Please sign in to comment.