Du kan inte välja fler än 25 ämnen Ämnen måste starta med en bokstav eller siffra, kan innehålla bindestreck ('-') och vara max 35 tecken långa.

653 rader
24 KiB

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