You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

655 lines
24 KiB

7 years ago
10 years ago
10 years ago
10 years ago
10 years ago
10 years ago
10 years ago
10 years ago
  1. #!/usr/bin/env escript
  2. %% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
  3. %% ex: ft=erlang ts=4 sw=4 et
  4. main(_) ->
  5. application:start(crypto),
  6. application:start(asn1),
  7. application:start(public_key),
  8. application:start(ssl),
  9. inets:start(),
  10. inets:start(httpc, [{profile, rebar}]),
  11. set_httpc_options(),
  12. %% Fetch and build deps required to build rebar3
  13. BaseDeps = [{providers, []}
  14. ,{getopt, []}
  15. ,{cf, []}
  16. ,{erlware_commons, ["ec_dictionary.erl", "ec_vsn.erl"]}
  17. ,{parse_trans, ["parse_trans.erl", "parse_trans_pp.erl",
  18. "parse_trans_codegen.erl"]}
  19. ,{certifi, []}],
  20. Deps = get_deps(),
  21. [fetch_and_compile(Dep, Deps) || Dep <- BaseDeps],
  22. %% Build rebar3 modules with compile:file
  23. bootstrap_rebar3(),
  24. %% Build rebar.app from rebar.app.src
  25. {ok, App} = rebar_app_info:new(rebar, "3.6.1", filename:absname("_build/default/lib/rebar/")),
  26. rebar_otp_app:compile(rebar_state:new(), App),
  27. %% Because we are compiling files that are loaded already we want to silence
  28. %% not_purged errors in rebar_erlc_compiler:opts_changed/1
  29. error_logger:tty(false),
  30. setup_env(),
  31. os:putenv("REBAR_PROFILE", "bootstrap"),
  32. RegistryFile = default_registry_file(),
  33. case filelib:is_file(RegistryFile) of
  34. true ->
  35. ok;
  36. false ->
  37. rebar3:run(["update"])
  38. end,
  39. {ok, State} = rebar3:run(["compile"]),
  40. reset_env(),
  41. os:putenv("REBAR_PROFILE", ""),
  42. DepsPaths = rebar_state:code_paths(State, all_deps),
  43. code:add_pathsa(DepsPaths),
  44. rebar3:run(["clean", "-a"]),
  45. rebar3:run(["as", "prod", "escriptize"]),
  46. %% Done with compile, can turn back on error logger
  47. error_logger:tty(true).
  48. default_registry_file() ->
  49. {ok, [[Home]]} = init:get_argument(home),
  50. CacheDir = filename:join([Home, ".cache", "rebar3"]),
  51. filename:join([CacheDir, "hex", "default", "registry"]).
  52. fetch_and_compile({Name, ErlFirstFiles}, Deps) ->
  53. case lists:keyfind(Name, 1, Deps) of
  54. {Name, Vsn} ->
  55. ok = fetch({pkg, atom_to_binary(Name, utf8), list_to_binary(Vsn)}, Name);
  56. {Name, _, Source} ->
  57. ok = fetch(Source, Name)
  58. end,
  59. %% Hack: erlware_commons depends on a .script file to check if it is being built with
  60. %% rebar2 or rebar3. But since rebar3 isn't built yet it can't get the vsn with get_key.
  61. %% So we simply make sure that file is deleted before compiling
  62. file:delete("_build/default/lib/erlware_commons/rebar.config.script"),
  63. compile(Name, ErlFirstFiles).
  64. fetch({pkg, Name, Vsn}, App) ->
  65. Dir = filename:join([filename:absname("_build/default/lib/"), App]),
  66. case filelib:is_dir(Dir) of
  67. false ->
  68. CDN = "https://repo.hex.pm/tarballs",
  69. Package = binary_to_list(<<Name/binary, "-", Vsn/binary, ".tar">>),
  70. Url = join([CDN, Package], "/"),
  71. case request(Url) of
  72. {ok, Binary} ->
  73. {ok, Contents} = extract(Binary),
  74. ok = erl_tar:extract({binary, Contents}, [{cwd, Dir}, compressed]);
  75. {error, {Reason, _}} ->
  76. ReasonText = re:replace(atom_to_list(Reason), "_", " ", [global,{return,list}]),
  77. io:format("Error: Unable to fetch package ~s ~s: ~s~n", [Name, Vsn, ReasonText])
  78. end;
  79. true ->
  80. io:format("Dependency ~s already exists~n", [Name])
  81. end.
  82. extract(Binary) ->
  83. {ok, Files} = erl_tar:extract({binary, Binary}, [memory]),
  84. {"contents.tar.gz", Contents} = lists:keyfind("contents.tar.gz", 1, Files),
  85. {ok, Contents}.
  86. request(Url) ->
  87. HttpOptions = [{relaxed, true} | get_proxy_auth()],
  88. case httpc:request(get, {Url, []},
  89. HttpOptions,
  90. [{body_format, binary}],
  91. rebar) of
  92. {ok, {{_Version, 200, _Reason}, _Headers, Body}} ->
  93. {ok, Body};
  94. Error ->
  95. Error
  96. end.
  97. get_rebar_config() ->
  98. {ok, [[Home]]} = init:get_argument(home),
  99. ConfDir = filename:join(Home, ".config/rebar3"),
  100. case file:consult(filename:join(ConfDir, "rebar.config")) of
  101. {ok, Config} ->
  102. Config;
  103. _ ->
  104. []
  105. end.
  106. get_http_vars(Scheme) ->
  107. OS = case os:getenv(atom_to_list(Scheme)) of
  108. Str when is_list(Str) -> Str;
  109. _ -> []
  110. end,
  111. proplists:get_value(Scheme, get_rebar_config(), OS).
  112. set_httpc_options() ->
  113. set_httpc_options(https_proxy, get_http_vars(https_proxy)),
  114. set_httpc_options(proxy, get_http_vars(http_proxy)).
  115. set_httpc_options(_, []) ->
  116. ok;
  117. set_httpc_options(Scheme, Proxy) ->
  118. {ok, {_, UserInfo, Host, Port, _, _}} = http_uri:parse(Proxy),
  119. httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar),
  120. set_proxy_auth(UserInfo).
  121. compile(App, FirstFiles) ->
  122. Dir = filename:join(filename:absname("_build/default/lib/"), App),
  123. filelib:ensure_dir(filename:join([Dir, "ebin", "dummy.beam"])),
  124. code:add_path(filename:join(Dir, "ebin")),
  125. FirstFilesPaths = [filename:join([Dir, "src", Module]) || Module <- FirstFiles],
  126. Sources = FirstFilesPaths ++ filelib:wildcard(filename:join([Dir, "src", "*.erl"])),
  127. [compile_file(X, [{i, filename:join(Dir, "include")}
  128. ,debug_info
  129. ,{outdir, filename:join(Dir, "ebin")}
  130. ,return | additional_defines()]) || X <- Sources].
  131. compile_file(File, Opts) ->
  132. case compile:file(File, Opts) of
  133. {ok, _Mod} ->
  134. ok;
  135. {ok, _Mod, []} ->
  136. ok;
  137. {ok, _Mod, Ws} ->
  138. io:format("~s~n", [format_warnings(File, Ws)]),
  139. halt(1);
  140. {error, Es, Ws} ->
  141. io:format("~s ~s~n", [format_errors(File, Es), format_warnings(File, Ws)]),
  142. halt(1)
  143. end.
  144. bootstrap_rebar3() ->
  145. filelib:ensure_dir("_build/default/lib/rebar/ebin/dummy.beam"),
  146. code:add_path("_build/default/lib/rebar/ebin/"),
  147. Res = symlink_or_copy(filename:absname("src"),
  148. filename:absname("_build/default/lib/rebar/src")),
  149. true = Res == ok orelse Res == exists,
  150. Sources = ["src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
  151. [compile_file(X, [{outdir, "_build/default/lib/rebar/ebin/"}
  152. ,return | additional_defines()]) || X <- Sources],
  153. code:add_patha(filename:absname("_build/default/lib/rebar/ebin")).
  154. %%rebar.hrl
  155. -define(FMT(Str, Args), lists:flatten(io_lib:format(Str, Args))).
  156. %%/rebar.hrl
  157. %%rebar_file_utils
  158. -include_lib("kernel/include/file.hrl").
  159. symlink_or_copy(Source, Target) ->
  160. Link = case os:type() of
  161. {win32, _} ->
  162. Source;
  163. _ ->
  164. make_relative_path(Source, Target)
  165. end,
  166. case file:make_symlink(Link, Target) of
  167. ok ->
  168. ok;
  169. {error, eexist} ->
  170. exists;
  171. {error, _} ->
  172. case os:type() of
  173. {win32, _} ->
  174. S = unicode:characters_to_list(Source),
  175. T = unicode:characters_to_list(Target),
  176. case filelib:is_dir(S) of
  177. true ->
  178. win32_symlink_or_copy(S, T);
  179. false ->
  180. cp_r([S], T)
  181. end;
  182. _ ->
  183. case filelib:is_dir(Target) of
  184. true ->
  185. ok;
  186. false ->
  187. cp_r([Source], Target)
  188. end
  189. end
  190. end.
  191. -spec cp_r(list(string()), file:filename()) -> 'ok'.
  192. cp_r([], _Dest) ->
  193. ok;
  194. cp_r(Sources, Dest) ->
  195. case os:type() of
  196. {unix, _} ->
  197. EscSources = [escape_chars(Src) || Src <- Sources],
  198. SourceStr = join(EscSources, " "),
  199. {ok, []} = sh(?FMT("cp -Rp ~ts \"~ts\"",
  200. [SourceStr, escape_double_quotes(Dest)]),
  201. [{use_stdout, false}, abort_on_error]),
  202. ok;
  203. {win32, _} ->
  204. lists:foreach(fun(Src) -> ok = cp_r_win32(Src,Dest) end, Sources),
  205. ok
  206. end.
  207. %% @private Compatibility function for windows
  208. win32_symlink_or_copy(Source, Target) ->
  209. Res = sh(?FMT("cmd /c mklink /j \"~ts\" \"~ts\"",
  210. [escape_double_quotes(filename:nativename(Target)),
  211. escape_double_quotes(filename:nativename(Source))]),
  212. [{use_stdout, false}, return_on_error]),
  213. case win32_mklink_ok(Res, Target) of
  214. true -> ok;
  215. false -> cp_r_win32(Source, drop_last_dir_from_path(Target))
  216. end.
  217. cp_r_win32({true, SourceDir}, {true, DestDir}) ->
  218. %% from directory to directory
  219. ok = case file:make_dir(DestDir) of
  220. {error, eexist} -> ok;
  221. Other -> Other
  222. end,
  223. ok = xcopy_win32(SourceDir, DestDir);
  224. cp_r_win32({false, Source} = S,{true, DestDir}) ->
  225. %% from file to directory
  226. cp_r_win32(S, {false, filename:join(DestDir, filename:basename(Source))});
  227. cp_r_win32({false, Source},{false, Dest}) ->
  228. %% from file to file
  229. {ok,_} = file:copy(Source, Dest),
  230. ok;
  231. cp_r_win32({true, SourceDir}, {false, DestDir}) ->
  232. case filelib:is_regular(DestDir) of
  233. true ->
  234. %% From directory to file? This shouldn't happen
  235. {error, lists:flatten(
  236. io_lib:format("Cannot copy dir (~p) to file (~p)\n",
  237. [SourceDir, DestDir]))};
  238. false ->
  239. %% Specifying a target directory that doesn't currently exist.
  240. %% So let's attempt to create this directory
  241. case filelib:ensure_dir(filename:join(DestDir, "dummy")) of
  242. ok ->
  243. ok = xcopy_win32(SourceDir, DestDir);
  244. {error, Reason} ->
  245. {error, lists:flatten(
  246. io_lib:format("Unable to create dir ~p: ~p\n",
  247. [DestDir, Reason]))}
  248. end
  249. end;
  250. cp_r_win32(Source,Dest) ->
  251. Dst = {filelib:is_dir(Dest), Dest},
  252. lists:foreach(fun(Src) ->
  253. ok = cp_r_win32({filelib:is_dir(Src), Src}, Dst)
  254. end, filelib:wildcard(Source)),
  255. ok.
  256. %% drops the last 'node' of the filename, presumably the last dir such as 'src'
  257. %% this is because cp_r_win32/2 automatically adds the dir name, to appease
  258. %% robocopy and be more uniform with POSIX
  259. drop_last_dir_from_path([]) ->
  260. [];
  261. drop_last_dir_from_path(Path) ->
  262. case lists:droplast(filename:split(Path)) of
  263. [] -> [];
  264. Dirs -> filename:join(Dirs)
  265. end.
  266. %% @private specifically pattern match against the output
  267. %% of the windows 'mklink' shell call; different values from
  268. %% what win32_ok/1 handles
  269. win32_mklink_ok({ok, _}, _) ->
  270. true;
  271. win32_mklink_ok({error,{1,"Local NTFS volumes are required to complete the operation.\n"}}, _) ->
  272. false;
  273. win32_mklink_ok({error,{1,"Cannot create a file when that file already exists.\n"}}, Target) ->
  274. % File or dir is already in place; find if it is already a symlink (true) or
  275. % if it is a directory (copy-required; false)
  276. is_symlink(Target);
  277. win32_mklink_ok(_, _) ->
  278. false.
  279. xcopy_win32(Source,Dest)->
  280. %% "xcopy \"~ts\" \"~ts\" /q /y /e 2> nul", Changed to robocopy to
  281. %% handle long names. May have issues with older windows.
  282. Cmd = case filelib:is_dir(Source) of
  283. true ->
  284. %% For robocopy, copying /a/b/c/ to /d/e/f/ recursively does not
  285. %% create /d/e/f/c/*, but rather copies all files to /d/e/f/*.
  286. %% The usage we make here expects the former, not the later, so we
  287. %% must manually add the last fragment of a directory to the `Dest`
  288. %% in order to properly replicate POSIX platforms
  289. NewDest = filename:join([Dest, filename:basename(Source)]),
  290. ?FMT("robocopy \"~ts\" \"~ts\" /e 1> nul",
  291. [escape_double_quotes(filename:nativename(Source)),
  292. escape_double_quotes(filename:nativename(NewDest))]);
  293. false ->
  294. ?FMT("robocopy \"~ts\" \"~ts\" \"~ts\" /e 1> nul",
  295. [escape_double_quotes(filename:nativename(filename:dirname(Source))),
  296. escape_double_quotes(filename:nativename(Dest)),
  297. escape_double_quotes(filename:basename(Source))])
  298. end,
  299. Res = sh(Cmd, [{use_stdout, false}, return_on_error]),
  300. case win32_ok(Res) of
  301. true -> ok;
  302. false ->
  303. {error, lists:flatten(
  304. io_lib:format("Failed to copy ~ts to ~ts~n",
  305. [Source, Dest]))}
  306. end.
  307. is_symlink(Filename) ->
  308. {ok, Info} = file:read_link_info(Filename),
  309. Info#file_info.type == symlink.
  310. win32_ok({ok, _}) -> true;
  311. win32_ok({error, {Rc, _}}) when Rc<9; Rc=:=16 -> true;
  312. win32_ok(_) -> false.
  313. %%/rebar_file_utils
  314. %%rebar_utils
  315. %% escape\ as\ a\ shell\?
  316. escape_chars(Str) when is_atom(Str) ->
  317. escape_chars(atom_to_list(Str));
  318. escape_chars(Str) ->
  319. re:replace(Str, "([ ()?`!$&;\"\'])", "\\\\&",
  320. [global, {return, list}, unicode]).
  321. %% "escape inside these"
  322. escape_double_quotes(Str) ->
  323. re:replace(Str, "([\"\\\\`!$&*;])", "\\\\&",
  324. [global, {return, list}, unicode]).
  325. sh(Command0, Options0) ->
  326. DefaultOptions = [{use_stdout, false}],
  327. Options = [expand_sh_flag(V)
  328. || V <- proplists:compact(Options0 ++ DefaultOptions)],
  329. ErrorHandler = proplists:get_value(error_handler, Options),
  330. OutputHandler = proplists:get_value(output_handler, Options),
  331. Command = lists:flatten(patch_on_windows(Command0, proplists:get_value(env, Options, []))),
  332. PortSettings = proplists:get_all_values(port_settings, Options) ++
  333. [exit_status, {line, 16384}, use_stdio, stderr_to_stdout, hide, eof],
  334. Port = open_port({spawn, Command}, PortSettings),
  335. try
  336. case sh_loop(Port, OutputHandler, []) of
  337. {ok, _Output} = Ok ->
  338. Ok;
  339. {error, {_Rc, _Output}=Err} ->
  340. ErrorHandler(Command, Err)
  341. end
  342. after
  343. port_close(Port)
  344. end.
  345. sh_loop(Port, Fun, Acc) ->
  346. receive
  347. {Port, {data, {eol, Line}}} ->
  348. sh_loop(Port, Fun, Fun(Line ++ "\n", Acc));
  349. {Port, {data, {noeol, Line}}} ->
  350. sh_loop(Port, Fun, Fun(Line, Acc));
  351. {Port, eof} ->
  352. Data = lists:flatten(lists:reverse(Acc)),
  353. receive
  354. {Port, {exit_status, 0}} ->
  355. {ok, Data};
  356. {Port, {exit_status, Rc}} ->
  357. {error, {Rc, Data}}
  358. end
  359. end.
  360. expand_sh_flag(return_on_error) ->
  361. {error_handler,
  362. fun(_Command, Err) ->
  363. {error, Err}
  364. end};
  365. expand_sh_flag(abort_on_error) ->
  366. {error_handler,
  367. fun log_and_abort/2};
  368. expand_sh_flag({use_stdout, false}) ->
  369. {output_handler,
  370. fun(Line, Acc) ->
  371. [Line | Acc]
  372. end};
  373. expand_sh_flag({cd, _CdArg} = Cd) ->
  374. {port_settings, Cd};
  375. expand_sh_flag({env, _EnvArg} = Env) ->
  376. {port_settings, Env}.
  377. %% We do the shell variable substitution ourselves on Windows and hope that the
  378. %% command doesn't use any other shell magic.
  379. patch_on_windows(Cmd, Env) ->
  380. case os:type() of
  381. {win32,nt} ->
  382. Cmd1 = "cmd /q /c "
  383. ++ lists:foldl(fun({Key, Value}, Acc) ->
  384. expand_env_variable(Acc, Key, Value)
  385. end, Cmd, Env),
  386. %% Remove left-over vars
  387. re:replace(Cmd1, "\\\$\\w+|\\\${\\w+}", "",
  388. [global, {return, list}, unicode]);
  389. _ ->
  390. Cmd
  391. end.
  392. %% @doc Given env. variable `FOO' we want to expand all references to
  393. %% it in `InStr'. References can have two forms: `$FOO' and `${FOO}'
  394. %% The end of form `$FOO' is delimited with whitespace or EOL
  395. -spec expand_env_variable(string(), string(), term()) -> string().
  396. expand_env_variable(InStr, VarName, RawVarValue) ->
  397. case chr(InStr, $$) of
  398. 0 ->
  399. %% No variables to expand
  400. InStr;
  401. _ ->
  402. ReOpts = [global, unicode, {return, list}],
  403. VarValue = re:replace(RawVarValue, "\\\\", "\\\\\\\\", ReOpts),
  404. %% Use a regex to match/replace:
  405. %% Given variable "FOO": match $FOO\s | $FOOeol | ${FOO}
  406. RegEx = io_lib:format("\\\$(~ts(\\W|$)|{~ts})", [VarName, VarName]),
  407. re:replace(InStr, RegEx, [VarValue, "\\2"], ReOpts)
  408. end.
  409. -spec log_and_abort(string(), {integer(), string()}) -> no_return().
  410. log_and_abort(Command, {Rc, Output}) ->
  411. io:format("sh(~ts)~n"
  412. "failed with return code ~w and the following output:~n"
  413. "~ts", [Command, Rc, Output]),
  414. throw(bootstrap_abort).
  415. %%/rebar_utils
  416. %%rebar_dir
  417. make_relative_path(Source, Target) ->
  418. AbsSource = make_normalized_path(Source),
  419. AbsTarget = make_normalized_path(Target),
  420. do_make_relative_path(filename:split(AbsSource), filename:split(AbsTarget)).
  421. %% @private based on fragments of paths, replace the number of common
  422. %% segments by `../' bits, and add the rest of the source alone after it
  423. -spec do_make_relative_path([string()], [string()]) -> file:filename().
  424. do_make_relative_path([H|T1], [H|T2]) ->
  425. do_make_relative_path(T1, T2);
  426. do_make_relative_path(Source, Target) ->
  427. Base = lists:duplicate(max(length(Target) - 1, 0), ".."),
  428. filename:join(Base ++ Source).
  429. make_normalized_path(Path) ->
  430. AbsPath = make_absolute_path(Path),
  431. Components = filename:split(AbsPath),
  432. make_normalized_path(Components, []).
  433. make_absolute_path(Path) ->
  434. case filename:pathtype(Path) of
  435. absolute ->
  436. Path;
  437. relative ->
  438. {ok, Dir} = file:get_cwd(),
  439. filename:join([Dir, Path]);
  440. volumerelative ->
  441. Volume = hd(filename:split(Path)),
  442. {ok, Dir} = file:get_cwd(Volume),
  443. filename:join([Dir, Path])
  444. end.
  445. -spec make_normalized_path([string()], [string()]) -> file:filename().
  446. make_normalized_path([], NormalizedPath) ->
  447. filename:join(lists:reverse(NormalizedPath));
  448. make_normalized_path([H|T], NormalizedPath) ->
  449. case H of
  450. "." when NormalizedPath == [], T == [] -> make_normalized_path(T, ["."]);
  451. "." -> make_normalized_path(T, NormalizedPath);
  452. ".." when NormalizedPath == [] -> make_normalized_path(T, [".."]);
  453. ".." when hd(NormalizedPath) =/= ".." -> make_normalized_path(T, tl(NormalizedPath));
  454. _ -> make_normalized_path(T, [H|NormalizedPath])
  455. end.
  456. %%/rebar_dir
  457. setup_env() ->
  458. %% We don't need or want relx providers loaded yet
  459. application:load(rebar),
  460. {ok, Providers} = application:get_env(rebar, providers),
  461. Providers1 = Providers -- [rebar_prv_release,
  462. rebar_prv_relup,
  463. rebar_prv_tar],
  464. application:set_env(rebar, providers, Providers1).
  465. reset_env() ->
  466. %% Reset the env so we get all providers
  467. application:unset_env(rebar, providers),
  468. application:unload(rebar),
  469. application:load(rebar).
  470. get_deps() ->
  471. case file:consult("rebar.lock") of
  472. {ok, [[]]} ->
  473. %% Something went wrong in a previous build, lock file shouldn't be empty
  474. io:format("Empty list in lock file, deleting rebar.lock~n"),
  475. ok = file:delete("rebar.lock"),
  476. {ok, Config} = file:consult("rebar.config"),
  477. proplists:get_value(deps, Config);
  478. {ok, [Deps]} ->
  479. [{binary_to_atom(Name, utf8), "", Source} || {Name, Source, _Level} <- Deps];
  480. _ ->
  481. {ok, Config} = file:consult("rebar.config"),
  482. proplists:get_value(deps, Config)
  483. end.
  484. format_errors(Source, Errors) ->
  485. format_errors(Source, "", Errors).
  486. format_warnings(Source, Warnings) ->
  487. format_warnings(Source, Warnings, []).
  488. format_warnings(Source, Warnings, Opts) ->
  489. Prefix = case lists:member(warnings_as_errors, Opts) of
  490. true -> "";
  491. false -> "Warning: "
  492. end,
  493. format_errors(Source, Prefix, Warnings).
  494. format_errors(_MainSource, Extra, Errors) ->
  495. [begin
  496. [format_error(Source, Extra, Desc) || Desc <- Descs]
  497. end
  498. || {Source, Descs} <- Errors].
  499. format_error(AbsSource, Extra, {{Line, Column}, Mod, Desc}) ->
  500. ErrorDesc = Mod:format_error(Desc),
  501. io_lib:format("~s:~w:~w: ~s~s~n", [AbsSource, Line, Column, Extra, ErrorDesc]);
  502. format_error(AbsSource, Extra, {Line, Mod, Desc}) ->
  503. ErrorDesc = Mod:format_error(Desc),
  504. io_lib:format("~s:~w: ~s~s~n", [AbsSource, Line, Extra, ErrorDesc]);
  505. format_error(AbsSource, Extra, {Mod, Desc}) ->
  506. ErrorDesc = Mod:format_error(Desc),
  507. io_lib:format("~s: ~s~s~n", [AbsSource, Extra, ErrorDesc]).
  508. additional_defines() ->
  509. [{d, D} || {Re, D} <- [{"^[0-9]+", namespaced_types},
  510. {"^R1[4|5]", deprecated_crypto},
  511. {"^2", unicode_str},
  512. {"^(R|1|20)", fun_stacktrace},
  513. {"^((1[8|9])|2)", rand_module}],
  514. is_otp_release(Re)].
  515. is_otp_release(ArchRegex) ->
  516. case re:run(otp_release(), ArchRegex, [{capture, none}]) of
  517. match ->
  518. true;
  519. nomatch ->
  520. false
  521. end.
  522. otp_release() ->
  523. otp_release1(erlang:system_info(otp_release)).
  524. %% If OTP <= R16, otp_release is already what we want.
  525. otp_release1([$R,N|_]=Rel) when is_integer(N) ->
  526. Rel;
  527. %% If OTP >= 17.x, erlang:system_info(otp_release) returns just the
  528. %% major version number, we have to read the full version from
  529. %% a file. See http://www.erlang.org/doc/system_principles/versions.html
  530. %% Read vsn string from the 'OTP_VERSION' file and return as list without
  531. %% the "\n".
  532. otp_release1(Rel) ->
  533. File = filename:join([code:root_dir(), "releases", Rel, "OTP_VERSION"]),
  534. case file:read_file(File) of
  535. {error, _} ->
  536. Rel;
  537. {ok, Vsn} ->
  538. %% It's fine to rely on the binary module here because we can
  539. %% be sure that it's available when the otp_release string does
  540. %% not begin with $R.
  541. Size = byte_size(Vsn),
  542. %% The shortest vsn string consists of at least two digits
  543. %% followed by "\n". Therefore, it's safe to assume Size >= 3.
  544. case binary:part(Vsn, {Size, -3}) of
  545. <<"**\n">> ->
  546. %% The OTP documentation mentions that a system patched
  547. %% using the otp_patch_apply tool available to licensed
  548. %% customers will leave a '**' suffix in the version as a
  549. %% flag saying the system consists of application versions
  550. %% from multiple OTP versions. We ignore this flag and
  551. %% drop the suffix, given for all intents and purposes, we
  552. %% cannot obtain relevant information from it as far as
  553. %% tooling is concerned.
  554. binary:bin_to_list(Vsn, {0, Size - 3});
  555. _ ->
  556. binary:bin_to_list(Vsn, {0, Size - 1})
  557. end
  558. end.
  559. set_proxy_auth([]) ->
  560. ok;
  561. set_proxy_auth(UserInfo) ->
  562. [Username, Password] = re:split(UserInfo, ":",
  563. [{return, list}, {parts,2}, unicode]),
  564. %% password may contain url encoded characters, need to decode them first
  565. put(proxy_auth, [{proxy_auth, {Username, http_uri:decode(Password)}}]).
  566. get_proxy_auth() ->
  567. case get(proxy_auth) of
  568. undefined -> [];
  569. ProxyAuth -> ProxyAuth
  570. end.
  571. %% string:join/2 copy; string:join/2 is getting obsoleted
  572. %% and replaced by lists:join/2, but lists:join/2 is too new
  573. %% for version support (only appeared in 19.0) so it cannot be
  574. %% used. Instead we just adopt join/2 locally and hope it works
  575. %% for most unicode use cases anyway.
  576. join([], Sep) when is_list(Sep) ->
  577. [];
  578. join([H|T], Sep) ->
  579. H ++ lists:append([Sep ++ X || X <- T]).
  580. %% Same for chr; no non-deprecated equivalent in OTP20+
  581. chr(S, C) when is_integer(C) -> chr(S, C, 1).
  582. chr([C|_Cs], C, I) -> I;
  583. chr([_|Cs], C, I) -> chr(Cs, C, I+1);
  584. chr([], _C, _I) -> 0.