summaryrefslogtreecommitdiff
path: root/bootstrap
diff options
context:
space:
mode:
authorStuart Thackray <stuart.thackray@gmail.com>2018-12-11 08:53:29 +0200
committerStuart Thackray <stuart.thackray@gmail.com>2018-12-11 08:53:29 +0200
commitebfa797c1f5d038b99beaf658757d974412a15c7 (patch)
tree9765880a7f0119c265d85f8bac7afea8d9542080 /bootstrap
parent71187514dabdd94aa333495d92df84a2e750099f (diff)
parent8e28561d4e14ea85d42d17ab5a0f17f5f1c696d2 (diff)
Update from Upstream
Diffstat (limited to 'bootstrap')
-rwxr-xr-xbootstrap395
1 files changed, 317 insertions, 78 deletions
diff --git a/bootstrap b/bootstrap
index 90775c8..ebbf35b 100755
--- a/bootstrap
+++ b/bootstrap
@@ -16,7 +16,10 @@ main(_) ->
,{getopt, []}
,{cf, []}
,{erlware_commons, ["ec_dictionary.erl", "ec_vsn.erl"]}
- ,{certifi, []}],
+ ,{parse_trans, ["parse_trans.erl", "parse_trans_pp.erl",
+ "parse_trans_codegen.erl"]}
+ ,{certifi, []}
+ ,{hex_core, []}],
Deps = get_deps(),
[fetch_and_compile(Dep, Deps) || Dep <- BaseDeps],
@@ -24,7 +27,7 @@ main(_) ->
bootstrap_rebar3(),
%% Build rebar.app from rebar.app.src
- {ok, App} = rebar_app_info:new(rebar, "3.2.0", filename:absname("_build/default/lib/rebar/")),
+ {ok, App} = rebar_app_info:new(rebar, "3.7.5", filename:absname("_build/default/lib/rebar/")),
rebar_otp_app:compile(rebar_state:new(), App),
%% Because we are compiling files that are loaded already we want to silence
@@ -33,14 +36,6 @@ main(_) ->
setup_env(),
os:putenv("REBAR_PROFILE", "bootstrap"),
- RegistryFile = default_registry_file(),
- case filelib:is_file(RegistryFile) of
- true ->
- ok;
- false ->
- rebar3:run(["update"])
- end,
-
{ok, State} = rebar3:run(["compile"]),
reset_env(),
os:putenv("REBAR_PROFILE", ""),
@@ -49,29 +44,10 @@ main(_) ->
code:add_pathsa(DepsPaths),
rebar3:run(["clean", "-a"]),
- rebar3:run(["escriptize"]),
+ rebar3:run(["as", "prod", "escriptize"]),
%% Done with compile, can turn back on error logger
- error_logger:tty(true),
-
- %% Finally, update executable perms for our script on *nix,
- %% or write out script files on win32.
- ec_file:copy("_build/default/bin/rebar3", "./rebar3"),
- case os:type() of
- {unix,_} ->
- [] = os:cmd("chmod u+x rebar3"),
- ok;
- {win32,_} ->
- write_windows_scripts(),
- ok;
- _ ->
- ok
- end.
-
-default_registry_file() ->
- {ok, [[Home]]} = init:get_argument(home),
- CacheDir = filename:join([Home, ".cache", "rebar3"]),
- filename:join([CacheDir, "hex", "default", "registry"]).
+ error_logger:tty(true).
fetch_and_compile({Name, ErlFirstFiles}, Deps) ->
case lists:keyfind(Name, 1, Deps) of
@@ -94,13 +70,14 @@ fetch({pkg, Name, Vsn}, App) ->
false ->
CDN = "https://repo.hex.pm/tarballs",
Package = binary_to_list(<<Name/binary, "-", Vsn/binary, ".tar">>),
- Url = string:join([CDN, Package], "/"),
+ Url = join([CDN, Package], "/"),
case request(Url) of
{ok, Binary} ->
{ok, Contents} = extract(Binary),
ok = erl_tar:extract({binary, Contents}, [{cwd, Dir}, compressed]);
- _ ->
- io:format("Error: Unable to fetch package ~p ~p~n", [Name, Vsn])
+ {error, {Reason, _}} ->
+ ReasonText = re:replace(atom_to_list(Reason), "_", " ", [global,{return,list}]),
+ io:format("Error: Unable to fetch package ~s ~s: ~s~n", [Name, Vsn, ReasonText])
end;
true ->
io:format("Dependency ~s already exists~n", [Name])
@@ -112,8 +89,10 @@ extract(Binary) ->
{ok, Contents}.
request(Url) ->
+ HttpOptions = [{relaxed, true} | get_proxy_auth()],
+
case httpc:request(get, {Url, []},
- [{relaxed, true}],
+ HttpOptions,
[{body_format, binary}],
rebar) of
{ok, {{_Version, 200, _Reason}, _Headers, Body}} ->
@@ -147,8 +126,9 @@ set_httpc_options(_, []) ->
ok;
set_httpc_options(Scheme, Proxy) ->
- {ok, {_, _, Host, Port, _, _}} = http_uri:parse(Proxy),
- httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar).
+ {ok, {_, UserInfo, Host, Port, _, _}} = http_uri:parse(Proxy),
+ httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar),
+ set_proxy_auth(UserInfo).
compile(App, FirstFiles) ->
Dir = filename:join(filename:absname("_build/default/lib/"), App),
@@ -178,9 +158,10 @@ compile_file(File, Opts) ->
bootstrap_rebar3() ->
filelib:ensure_dir("_build/default/lib/rebar/ebin/dummy.beam"),
code:add_path("_build/default/lib/rebar/ebin/"),
- ok = symlink_or_copy(filename:absname("src"),
- filename:absname("_build/default/lib/rebar/src")),
- Sources = ["src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
+ Res = symlink_or_copy(filename:absname("src"),
+ filename:absname("_build/default/lib/rebar/src")),
+ true = Res == ok orelse Res == exists,
+ Sources = ["src/rebar_resource_v2.erl", "src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
[compile_file(X, [{outdir, "_build/default/lib/rebar/ebin/"}
,return | additional_defines()]) || X <- Sources],
code:add_patha(filename:absname("_build/default/lib/rebar/ebin")).
@@ -189,6 +170,8 @@ bootstrap_rebar3() ->
-define(FMT(Str, Args), lists:flatten(io_lib:format(Str, Args))).
%%/rebar.hrl
%%rebar_file_utils
+-include_lib("kernel/include/file.hrl").
+
symlink_or_copy(Source, Target) ->
Link = case os:type() of
{win32, _} ->
@@ -200,55 +183,63 @@ symlink_or_copy(Source, Target) ->
ok ->
ok;
{error, eexist} ->
- ok;
+ exists;
{error, _} ->
- cp_r([Source], Target)
+ case os:type() of
+ {win32, _} ->
+ S = unicode:characters_to_list(Source),
+ T = unicode:characters_to_list(Target),
+ case filelib:is_dir(S) of
+ true ->
+ win32_symlink_or_copy(S, T);
+ false ->
+ cp_r([S], T)
+ end;
+ _ ->
+ case filelib:is_dir(Target) of
+ true ->
+ ok;
+ false ->
+ cp_r([Source], Target)
+ end
+ end
end.
-make_relative_path(Source, Target) ->
- do_make_relative_path(filename:split(Source), filename:split(Target)).
-
-do_make_relative_path([H|T1], [H|T2]) ->
- do_make_relative_path(T1, T2);
-do_make_relative_path(Source, Target) ->
- Base = lists:duplicate(max(length(Target) - 1, 0), ".."),
- filename:join(Base ++ Source).
-
+-spec cp_r(list(string()), file:filename()) -> 'ok'.
cp_r([], _Dest) ->
ok;
cp_r(Sources, Dest) ->
case os:type() of
{unix, _} ->
- EscSources = [escape_path(Src) || Src <- Sources],
- SourceStr = string:join(EscSources, " "),
- os:cmd(?FMT("cp -R ~s \"~s\"", [SourceStr, Dest])),
+ EscSources = [escape_chars(Src) || Src <- Sources],
+ SourceStr = join(EscSources, " "),
+ {ok, []} = sh(?FMT("cp -Rp ~ts \"~ts\"",
+ [SourceStr, escape_double_quotes(Dest)]),
+ [{use_stdout, false}, abort_on_error]),
ok;
{win32, _} ->
lists:foreach(fun(Src) -> ok = cp_r_win32(Src,Dest) end, Sources),
ok
end.
-xcopy_win32(Source,Dest)->
- R = os:cmd(?FMT("xcopy \"~s\" \"~s\" /q /y /e 2> nul",
- [filename:nativename(Source), filename:nativename(Dest)])),
- case length(R) > 0 of
- %% when xcopy fails, stdout is empty and and error message is printed
- %% to stderr (which is redirected to nul)
+%% @private Compatibility function for windows
+win32_symlink_or_copy(Source, Target) ->
+ Res = sh(?FMT("cmd /c mklink /j \"~ts\" \"~ts\"",
+ [escape_double_quotes(filename:nativename(Target)),
+ escape_double_quotes(filename:nativename(Source))]),
+ [{use_stdout, false}, return_on_error]),
+ case win32_mklink_ok(Res, Target) of
true -> ok;
- false ->
- {error, lists:flatten(
- io_lib:format("Failed to xcopy from ~s to ~s~n",
- [Source, Dest]))}
+ false -> cp_r_win32(Source, drop_last_dir_from_path(Target))
end.
cp_r_win32({true, SourceDir}, {true, DestDir}) ->
%% from directory to directory
- SourceBase = filename:basename(SourceDir),
- ok = case file:make_dir(filename:join(DestDir, SourceBase)) of
+ ok = case file:make_dir(DestDir) of
{error, eexist} -> ok;
Other -> Other
end,
- ok = xcopy_win32(SourceDir, filename:join(DestDir, SourceBase));
+ ok = xcopy_win32(SourceDir, DestDir);
cp_r_win32({false, Source} = S,{true, DestDir}) ->
%% from file to directory
cp_r_win32(S, {false, filename:join(DestDir, filename:basename(Source))});
@@ -282,10 +273,231 @@ cp_r_win32(Source,Dest) ->
end, filelib:wildcard(Source)),
ok.
-escape_path(Str) ->
- re:replace(Str, "([ ()?])", "\\\\&", [global, {return, list}]).
+%% drops the last 'node' of the filename, presumably the last dir such as 'src'
+%% this is because cp_r_win32/2 automatically adds the dir name, to appease
+%% robocopy and be more uniform with POSIX
+drop_last_dir_from_path([]) ->
+ [];
+drop_last_dir_from_path(Path) ->
+ case lists:droplast(filename:split(Path)) of
+ [] -> [];
+ Dirs -> filename:join(Dirs)
+ end.
+
+%% @private specifically pattern match against the output
+%% of the windows 'mklink' shell call; different values from
+%% what win32_ok/1 handles
+win32_mklink_ok({ok, _}, _) ->
+ true;
+win32_mklink_ok({error,{1,"Local NTFS volumes are required to complete the operation.\n"}}, _) ->
+ false;
+win32_mklink_ok({error,{1,"Cannot create a file when that file already exists.\n"}}, Target) ->
+ % File or dir is already in place; find if it is already a symlink (true) or
+ % if it is a directory (copy-required; false)
+ is_symlink(Target);
+win32_mklink_ok(_, _) ->
+ false.
+
+xcopy_win32(Source,Dest)->
+ %% "xcopy \"~ts\" \"~ts\" /q /y /e 2> nul", Changed to robocopy to
+ %% handle long names. May have issues with older windows.
+ Cmd = case filelib:is_dir(Source) of
+ true ->
+ %% For robocopy, copying /a/b/c/ to /d/e/f/ recursively does not
+ %% create /d/e/f/c/*, but rather copies all files to /d/e/f/*.
+ %% The usage we make here expects the former, not the later, so we
+ %% must manually add the last fragment of a directory to the `Dest`
+ %% in order to properly replicate POSIX platforms
+ NewDest = filename:join([Dest, filename:basename(Source)]),
+ ?FMT("robocopy \"~ts\" \"~ts\" /e 1> nul",
+ [escape_double_quotes(filename:nativename(Source)),
+ escape_double_quotes(filename:nativename(NewDest))]);
+ false ->
+ ?FMT("robocopy \"~ts\" \"~ts\" \"~ts\" /e 1> nul",
+ [escape_double_quotes(filename:nativename(filename:dirname(Source))),
+ escape_double_quotes(filename:nativename(Dest)),
+ escape_double_quotes(filename:basename(Source))])
+ end,
+ Res = sh(Cmd, [{use_stdout, false}, return_on_error]),
+ case win32_ok(Res) of
+ true -> ok;
+ false ->
+ {error, lists:flatten(
+ io_lib:format("Failed to copy ~ts to ~ts~n",
+ [Source, Dest]))}
+ end.
+
+is_symlink(Filename) ->
+ {ok, Info} = file:read_link_info(Filename),
+ Info#file_info.type == symlink.
+
+win32_ok({ok, _}) -> true;
+win32_ok({error, {Rc, _}}) when Rc<9; Rc=:=16 -> true;
+win32_ok(_) -> false.
+
%%/rebar_file_utils
+%%rebar_utils
+
+%% escape\ as\ a\ shell\?
+escape_chars(Str) when is_atom(Str) ->
+ escape_chars(atom_to_list(Str));
+escape_chars(Str) ->
+ re:replace(Str, "([ ()?`!$&;\"\'])", "\\\\&",
+ [global, {return, list}, unicode]).
+
+%% "escape inside these"
+escape_double_quotes(Str) ->
+ re:replace(Str, "([\"\\\\`!$&*;])", "\\\\&",
+ [global, {return, list}, unicode]).
+
+sh(Command0, Options0) ->
+ DefaultOptions = [{use_stdout, false}],
+ Options = [expand_sh_flag(V)
+ || V <- proplists:compact(Options0 ++ DefaultOptions)],
+
+ ErrorHandler = proplists:get_value(error_handler, Options),
+ OutputHandler = proplists:get_value(output_handler, Options),
+
+ Command = lists:flatten(patch_on_windows(Command0, proplists:get_value(env, Options, []))),
+ PortSettings = proplists:get_all_values(port_settings, Options) ++
+ [exit_status, {line, 16384}, use_stdio, stderr_to_stdout, hide, eof],
+ Port = open_port({spawn, Command}, PortSettings),
+
+ try
+ case sh_loop(Port, OutputHandler, []) of
+ {ok, _Output} = Ok ->
+ Ok;
+ {error, {_Rc, _Output}=Err} ->
+ ErrorHandler(Command, Err)
+ end
+ after
+ port_close(Port)
+ end.
+
+sh_loop(Port, Fun, Acc) ->
+ receive
+ {Port, {data, {eol, Line}}} ->
+ sh_loop(Port, Fun, Fun(Line ++ "\n", Acc));
+ {Port, {data, {noeol, Line}}} ->
+ sh_loop(Port, Fun, Fun(Line, Acc));
+ {Port, eof} ->
+ Data = lists:flatten(lists:reverse(Acc)),
+ receive
+ {Port, {exit_status, 0}} ->
+ {ok, Data};
+ {Port, {exit_status, Rc}} ->
+ {error, {Rc, Data}}
+ end
+ end.
+
+expand_sh_flag(return_on_error) ->
+ {error_handler,
+ fun(_Command, Err) ->
+ {error, Err}
+ end};
+expand_sh_flag(abort_on_error) ->
+ {error_handler,
+ fun log_and_abort/2};
+expand_sh_flag({use_stdout, false}) ->
+ {output_handler,
+ fun(Line, Acc) ->
+ [Line | Acc]
+ end};
+expand_sh_flag({cd, _CdArg} = Cd) ->
+ {port_settings, Cd};
+expand_sh_flag({env, _EnvArg} = Env) ->
+ {port_settings, Env}.
+
+%% We do the shell variable substitution ourselves on Windows and hope that the
+%% command doesn't use any other shell magic.
+patch_on_windows(Cmd, Env) ->
+ case os:type() of
+ {win32,nt} ->
+ Cmd1 = "cmd /q /c "
+ ++ lists:foldl(fun({Key, Value}, Acc) ->
+ expand_env_variable(Acc, Key, Value)
+ end, Cmd, Env),
+ %% Remove left-over vars
+ re:replace(Cmd1, "\\\$\\w+|\\\${\\w+}", "",
+ [global, {return, list}, unicode]);
+ _ ->
+ Cmd
+ end.
+
+%% @doc Given env. variable `FOO' we want to expand all references to
+%% it in `InStr'. References can have two forms: `$FOO' and `${FOO}'
+%% The end of form `$FOO' is delimited with whitespace or EOL
+-spec expand_env_variable(string(), string(), term()) -> string().
+expand_env_variable(InStr, VarName, RawVarValue) ->
+ case chr(InStr, $$) of
+ 0 ->
+ %% No variables to expand
+ InStr;
+ _ ->
+ ReOpts = [global, unicode, {return, list}],
+ VarValue = re:replace(RawVarValue, "\\\\", "\\\\\\\\", ReOpts),
+ %% Use a regex to match/replace:
+ %% Given variable "FOO": match $FOO\s | $FOOeol | ${FOO}
+ RegEx = io_lib:format("\\\$(~ts(\\W|$)|{~ts})", [VarName, VarName]),
+ re:replace(InStr, RegEx, [VarValue, "\\2"], ReOpts)
+ end.
+
+-spec log_and_abort(string(), {integer(), string()}) -> no_return().
+log_and_abort(Command, {Rc, Output}) ->
+ io:format("sh(~ts)~n"
+ "failed with return code ~w and the following output:~n"
+ "~ts", [Command, Rc, Output]),
+ throw(bootstrap_abort).
+
+%%/rebar_utils
+
+%%rebar_dir
+make_relative_path(Source, Target) ->
+ AbsSource = make_normalized_path(Source),
+ AbsTarget = make_normalized_path(Target),
+ do_make_relative_path(filename:split(AbsSource), filename:split(AbsTarget)).
+
+%% @private based on fragments of paths, replace the number of common
+%% segments by `../' bits, and add the rest of the source alone after it
+-spec do_make_relative_path([string()], [string()]) -> file:filename().
+do_make_relative_path([H|T1], [H|T2]) ->
+ do_make_relative_path(T1, T2);
+do_make_relative_path(Source, Target) ->
+ Base = lists:duplicate(max(length(Target) - 1, 0), ".."),
+ filename:join(Base ++ Source).
+
+make_normalized_path(Path) ->
+ AbsPath = make_absolute_path(Path),
+ Components = filename:split(AbsPath),
+ make_normalized_path(Components, []).
+
+make_absolute_path(Path) ->
+ case filename:pathtype(Path) of
+ absolute ->
+ Path;
+ relative ->
+ {ok, Dir} = file:get_cwd(),
+ filename:join([Dir, Path]);
+ volumerelative ->
+ Volume = hd(filename:split(Path)),
+ {ok, Dir} = file:get_cwd(Volume),
+ filename:join([Dir, Path])
+ end.
+
+-spec make_normalized_path([string()], [string()]) -> file:filename().
+make_normalized_path([], NormalizedPath) ->
+ filename:join(lists:reverse(NormalizedPath));
+make_normalized_path([H|T], NormalizedPath) ->
+ case H of
+ "." when NormalizedPath == [], T == [] -> make_normalized_path(T, ["."]);
+ "." -> make_normalized_path(T, NormalizedPath);
+ ".." when NormalizedPath == [] -> make_normalized_path(T, [".."]);
+ ".." when hd(NormalizedPath) =/= ".." -> make_normalized_path(T, tl(NormalizedPath));
+ _ -> make_normalized_path(T, [H|NormalizedPath])
+ end.
+%%/rebar_dir
+
setup_env() ->
%% We don't need or want relx providers loaded yet
application:load(rebar),
@@ -301,14 +513,6 @@ reset_env() ->
application:unload(rebar),
application:load(rebar).
-write_windows_scripts() ->
- CmdScript=
- "@echo off\r\n"
- "setlocal\r\n"
- "set rebarscript=%~f0\r\n"
- "escript.exe \"%rebarscript:.cmd=%\" %*\r\n",
- ok = file:write_file("rebar3.cmd", CmdScript).
-
get_deps() ->
case file:consult("rebar.lock") of
{ok, [[]]} ->
@@ -354,7 +558,12 @@ format_error(AbsSource, Extra, {Mod, Desc}) ->
io_lib:format("~s: ~s~s~n", [AbsSource, Extra, ErrorDesc]).
additional_defines() ->
- [{d, D} || {Re, D} <- [{"^[0-9]+", namespaced_types}, {"^R1[4|5]", deprecated_crypto}, {"^((1[8|9])|2)", rand_module}], is_otp_release(Re)].
+ [{d, D} || {Re, D} <- [{"^[0-9]+", namespaced_types},
+ {"^R1[4|5]", deprecated_crypto},
+ {"^2", unicode_str},
+ {"^(R|1|20)", fun_stacktrace},
+ {"^((1[8|9])|2)", rand_module}],
+ is_otp_release(Re)].
is_otp_release(ArchRegex) ->
case re:run(otp_release(), ArchRegex, [{capture, none}]) of
@@ -402,3 +611,33 @@ otp_release1(Rel) ->
binary:bin_to_list(Vsn, {0, Size - 1})
end
end.
+
+set_proxy_auth([]) ->
+ ok;
+set_proxy_auth(UserInfo) ->
+ [Username, Password] = re:split(UserInfo, ":",
+ [{return, list}, {parts,2}, unicode]),
+ %% password may contain url encoded characters, need to decode them first
+ put(proxy_auth, [{proxy_auth, {Username, http_uri:decode(Password)}}]).
+
+get_proxy_auth() ->
+ case get(proxy_auth) of
+ undefined -> [];
+ ProxyAuth -> ProxyAuth
+ end.
+
+%% string:join/2 copy; string:join/2 is getting obsoleted
+%% and replaced by lists:join/2, but lists:join/2 is too new
+%% for version support (only appeared in 19.0) so it cannot be
+%% used. Instead we just adopt join/2 locally and hope it works
+%% for most unicode use cases anyway.
+join([], Sep) when is_list(Sep) ->
+ [];
+join([H|T], Sep) ->
+ H ++ lists:append([Sep ++ X || X <- T]).
+
+%% Same for chr; no non-deprecated equivalent in OTP20+
+chr(S, C) when is_integer(C) -> chr(S, C, 1).
+chr([C|_Cs], C, I) -> I;
+chr([_|Cs], C, I) -> chr(Cs, C, I+1);
+chr([], _C, _I) -> 0.