mirror of
https://github.com/erlang/rebar3.git
synced 2025-04-19 02:04:00 +03:00
Fix typos
This commit is contained in:
parent
7721444165
commit
47d7c9202a
@ -6,7 +6,7 @@ FROM erlang:20.3.8.1-alpine as builder
|
||||
# "The LABEL instruction adds metadata to an image."
|
||||
LABEL stage=builder
|
||||
|
||||
# Install git for fetching non-hex depenencies. Also allows rebar3
|
||||
# Install git for fetching non-hex dependencies. Also allows rebar3
|
||||
# to find it's own git version.
|
||||
# Add any other Alpine libraries needed to compile the project here.
|
||||
# See https://wiki.alpinelinux.org/wiki/Local_APK_cache for details
|
||||
|
@ -61,7 +61,7 @@ end
|
||||
##
|
||||
## plugins <task>:
|
||||
## list List local and global plugins for this project
|
||||
## upgrade Uprade plugins
|
||||
## upgrade Upgrade plugins
|
||||
##
|
||||
## Run 'rebar3 help <TASK>' for details.
|
||||
# general options
|
||||
@ -190,7 +190,7 @@ complete -f -c 'rebar3' -n '__fish_rebar3_using_command tar' -l system_libs
|
||||
complete -f -c 'rebar3' -n '__fish_rebar3_using_command tar' -l version -d "Print relx version"
|
||||
complete -f -c 'rebar3' -n '__fish_rebar3_using_command tar' -s r -l root -d "The project root directory"
|
||||
|
||||
complete -f -c 'rebar3' -n '__fish_rebar3_needs_command' -a tree -d "Print depdency tree."
|
||||
complete -f -c 'rebar3' -n '__fish_rebar3_needs_command' -a tree -d "Print dependency tree."
|
||||
|
||||
complete -f -c 'rebar3' -n '__fish_rebar3_needs_command tree' -s v -l verbose -d "Print repo and branch/tag/ref for git and hg deps."
|
||||
|
||||
|
@ -58,7 +58,7 @@ error(Str, Args) -> ?ERROR(Str, Args).
|
||||
expand_env_variable(InStr, VarName, RawVarValue) ->
|
||||
rebar_utils:expand_env_variable(InStr, VarName, RawVarValue).
|
||||
|
||||
%% @doc returns the sytem architecture, in strings like
|
||||
%% @doc returns the system architecture, in strings like
|
||||
%% `"19.0.4-x86_64-unknown-linux-gnu-64"'.
|
||||
-spec get_arch() -> string().
|
||||
get_arch() ->
|
||||
|
@ -54,7 +54,7 @@ do(State, LibDirs) ->
|
||||
end, State, lists:reverse(CurrentProfiles)),
|
||||
|
||||
%% Handle sub project apps deps
|
||||
%% Sort apps so we get the same merged deps config everytime
|
||||
%% Sort apps so we get the same merged deps config every time
|
||||
SortedApps = rebar_utils:sort_deps(Apps),
|
||||
lists:foldl(fun(AppInfo, StateAcc) ->
|
||||
Name = rebar_app_info:name(AppInfo),
|
||||
@ -438,7 +438,7 @@ create_app_info(AppInfo, AppDir, AppFile) ->
|
||||
end.
|
||||
|
||||
|
||||
%% @doc Read in and parse the .app file if it is availabe. Do the same for
|
||||
%% @doc Read in and parse the .app file if it is available. Do the same for
|
||||
%% the .app.src file if it exists.
|
||||
-spec try_handle_resource_files(AppInfo, AppDir, ResourceFiles, valid | invalid | all) ->
|
||||
{true, AppInfo} | false when
|
||||
@ -463,7 +463,7 @@ try_handle_resource_files(_AppInfo, _AppDir, [], _Validate) ->
|
||||
false.
|
||||
|
||||
|
||||
%% @doc Read in and parse the .app file if it is availabe. Do the same for
|
||||
%% @doc Read in and parse the .app file if it is available. Do the same for
|
||||
%% the .app.src file if it exists.
|
||||
-spec try_handle_app_file(AppInfo, AppDir, File, AppSrcFile, valid | invalid | all) ->
|
||||
{true, AppInfo} | false when
|
||||
|
@ -119,7 +119,7 @@
|
||||
%% API
|
||||
%% ============================================================================
|
||||
%% @doc Build a new, empty, app info value. This is not of a lot of use and you
|
||||
%% probably wont be doing this much.
|
||||
%% probably won't be doing this much.
|
||||
-spec new() -> t().
|
||||
new() ->
|
||||
#app_info_t{}.
|
||||
|
@ -336,7 +336,7 @@ atoms_in_erl_first_files_warning(Atoms) ->
|
||||
W = "You have provided atoms as file entries in erl_first_files; "
|
||||
"erl_first_files only expects lists of filenames as strings. "
|
||||
"The following modules (~p) may not work as expected and it is advised "
|
||||
"that you change these entires to string format "
|
||||
"that you change these entries to string format "
|
||||
"(e.g., \"src/module.erl\") ",
|
||||
?WARN(W, [Atoms]).
|
||||
|
||||
|
@ -56,7 +56,7 @@ atoms_in_mib_first_files_warning(Atoms) ->
|
||||
W = "You have provided atoms as file entries in mib_first_files; "
|
||||
"mib_first_files only expects lists of filenames as strings. "
|
||||
"The following MIBs (~p) may not work as expected and it is advised "
|
||||
"that you change these entires to string format "
|
||||
"that you change these entries to string format "
|
||||
"(e.g., \"mibs/SOME-MIB.mib\") ",
|
||||
?WARN(W, [Atoms]).
|
||||
|
||||
|
@ -8,7 +8,7 @@
|
||||
%%% out the cody bits
|
||||
%%% * red: things that went bad, i.e. the wrong argument in a
|
||||
%%% call. It allows to quickly catching where in the code
|
||||
%%% ane error is.
|
||||
%%% and error is.
|
||||
%%% * green: the 'good' stuff, i.e. what was expected as an argument
|
||||
%%% the 'red vs green' resambles the diff view 'remove vs add'
|
||||
%%% * blue: argument positions.
|
||||
@ -412,14 +412,14 @@ highlight([N | Nr], N, r, [Arg | Rest]) ->
|
||||
highlight(Ns, N, C, [Arg | Rest]) ->
|
||||
[Arg | highlight(Ns, N + 1, C, Rest)].
|
||||
|
||||
%% Arugments to functions and constraints are passed as
|
||||
%% Arguments to functions and constraints are passed as
|
||||
%% strings not as data, this function pulls them apart
|
||||
%% to allow interacting with them separately and not
|
||||
%% as one bug chunk of data.
|
||||
separate_args([$( | S]) ->
|
||||
separate_args([], S, "", []).
|
||||
|
||||
%% We strip this space since dialyzer is inconsistant in adding or not adding
|
||||
%% We strip this space since dialyzer is inconsistent in adding or not adding
|
||||
%% it ....
|
||||
separate_args([], [$,, $\s | R], Arg, Args) ->
|
||||
separate_args([], R, [], [lists:reverse(Arg) | Args]);
|
||||
|
@ -292,8 +292,8 @@ all_src_dirs(Opts, SrcDefault, ExtraDefault) ->
|
||||
%%% @doc
|
||||
%%% Return the list of options for the given src directory
|
||||
%%% If the same option is given multiple times for a directory in the
|
||||
%%% config, the priority order is: first occurence of `src_dirs'
|
||||
%%% followed by first occurence of `extra_src_dirs'.
|
||||
%%% config, the priority order is: first occurrence of `src_dirs'
|
||||
%%% followed by first occurrence of `extra_src_dirs'.
|
||||
-spec src_dir_opts(rebar_dict(), file:filename_all()) -> [{atom(),term()}].
|
||||
src_dir_opts(Opts, Dir) ->
|
||||
RawSrcDirs = raw_src_dirs(src_dirs, Opts, []),
|
||||
|
@ -831,7 +831,7 @@ atoms_in_erl_first_files_warning(Atoms) ->
|
||||
W = "You have provided atoms as file entries in erl_first_files; "
|
||||
"erl_first_files only expects lists of filenames as strings. "
|
||||
"The following modules (~p) may not work as expected and it is advised "
|
||||
"that you change these entires to string format "
|
||||
"that you change these entries to string format "
|
||||
"(e.g., \"src/module.erl\") ",
|
||||
?WARN(W, [Atoms]).
|
||||
|
||||
|
@ -17,7 +17,7 @@
|
||||
make_vsn_/1,
|
||||
git_vsn/0]).
|
||||
|
||||
%% For backward compatibilty
|
||||
%% For backward compatibility
|
||||
-export ([download/3]).
|
||||
|
||||
-include("rebar.hrl").
|
||||
@ -141,7 +141,7 @@ download(TmpDir, AppInfo, State, _) ->
|
||||
{error, Error}
|
||||
end.
|
||||
|
||||
%% For backward compatibilty
|
||||
%% For backward compatibility
|
||||
download(Dir, AppInfo, State) ->
|
||||
download_(Dir, AppInfo, State).
|
||||
|
||||
|
@ -11,7 +11,7 @@
|
||||
make_vsn/2]).
|
||||
|
||||
|
||||
%% For backward compatibilty
|
||||
%% For backward compatibility
|
||||
-export([ download/3
|
||||
]).
|
||||
|
||||
@ -77,7 +77,7 @@ download(TmpDir, AppInfo, State, _) ->
|
||||
{error, Error}
|
||||
end.
|
||||
|
||||
%% For backward compatibilty
|
||||
%% For backward compatibility
|
||||
download(Dir, AppInfo, State) ->
|
||||
download_(Dir, AppInfo, State).
|
||||
|
||||
|
@ -428,7 +428,7 @@ cmp_(BestMatch, MinVsn, [Vsn | R], CmpFun) ->
|
||||
end.
|
||||
|
||||
%% We need to treat this differently since we want a version that is LOWER but
|
||||
%% the higest possible one.
|
||||
%% the highest possible one.
|
||||
cmpl(Dep, Vsn, Repo, HexRegistry, State, CmpFun) ->
|
||||
case get_package_versions(Dep, Vsn, Repo, HexRegistry, State) of
|
||||
[] ->
|
||||
|
@ -135,7 +135,7 @@ format_error({bad_registry_checksum, Name, Vsn, Expected, Found}) ->
|
||||
%% Download the pkg belonging to the given address. If the etag of the pkg
|
||||
%% is the same what we stored in the etag file previously return {ok, cached},
|
||||
%% if the file has changed (so the etag is not the same anymore) return
|
||||
%% {ok, Contents, NewEtag}, otherwise if some error occured return error.
|
||||
%% {ok, Contents, NewEtag}, otherwise if some error occurred return error.
|
||||
%% @end
|
||||
%%------------------------------------------------------------------------------
|
||||
-spec request(rebar_hex_repos:repo(), binary(), binary(), false | binary())
|
||||
|
@ -340,7 +340,7 @@ build_custom_builder_app(AppInfo, State) ->
|
||||
ProjectBuilders = rebar_state:project_builders(State),
|
||||
case lists:keyfind(Type, 1, ProjectBuilders) of
|
||||
{_, Module} ->
|
||||
%% load plugins since thats where project builders would be,
|
||||
%% load plugins since that's where project builders would be,
|
||||
%% prevents parallelism at this level.
|
||||
rebar_paths:set_paths([deps, plugins], State),
|
||||
Res = Module:build(AppInfo),
|
||||
|
@ -90,7 +90,7 @@ get_template_vars(TemplateTerms, State) ->
|
||||
|
||||
%% Provide a way to merge a set of variables with another one. The left-hand
|
||||
%% set of variables takes precedence over the right-hand set.
|
||||
%% In the case where left-hand variable description contains overriden defaults, but
|
||||
%% In the case where left-hand variable description contains overridden defaults, but
|
||||
%% the right-hand one contains additional data such as documentation, the resulting
|
||||
%% variable description will contain the widest set of information possible.
|
||||
override_vars([], General) -> General;
|
||||
|
@ -97,7 +97,7 @@ sort_deps(Deps) ->
|
||||
%% We need a sort stable, based on the name. So that for multiple deps on
|
||||
%% the same level with the same name, we keep the order the parents had.
|
||||
%% `lists:keysort/2' is documented as stable in the stdlib.
|
||||
%% The list of deps is revered when we get it. For the proper stable
|
||||
%% The list of deps is reversed when we get it. For the proper stable
|
||||
%% result, re-reverse it.
|
||||
lists:keysort(?APP_NAME_INDEX, lists:reverse(Deps)).
|
||||
|
||||
@ -129,7 +129,7 @@ is_arch(ArchRegex) ->
|
||||
false
|
||||
end.
|
||||
|
||||
%% @doc returns the sytem architecture, in strings like
|
||||
%% @doc returns the system architecture, in strings like
|
||||
%% `"19.0.4-x86_64-unknown-linux-gnu-64"'.
|
||||
-spec get_arch() -> string().
|
||||
get_arch() ->
|
||||
|
@ -36,7 +36,7 @@
|
||||
%% Options used when reading a tar archive.
|
||||
-record(read_opts, {
|
||||
cwd :: string(), %% Current working directory.
|
||||
keep_old_files = false :: boolean(), %% Owerwrite or not.
|
||||
keep_old_files = false :: boolean(), %% Overwrite or not.
|
||||
files = all, %% Set of files to extract (or all)
|
||||
output = file :: 'file' | 'memory',
|
||||
open_mode = [], %% Open mode options.
|
||||
@ -202,7 +202,7 @@
|
||||
%% These constants (except S_IFMT) are
|
||||
%% used to determine what type of device
|
||||
%% a file is. Namely, `S_IFMT band file_info.mode`
|
||||
%% will equal one of these contants, and tells us
|
||||
%% will equal one of these constants, and tells us
|
||||
%% which type it is. The stdlib file_info record
|
||||
%% does not differentiate between device types, and
|
||||
%% will not allow us to differentiate between sockets
|
||||
|
@ -1,4 +1,4 @@
|
||||
{alias, [{help, [version]}, % should be skipped, but be overriden by plugin
|
||||
{alias, [{help, [version]}, % should be skipped, but be overridden by plugin
|
||||
{test, [compile, {eunit, "-c"}, cover]}]}.
|
||||
|
||||
{plugins, [rebar_alias]}. % should be overridden
|
||||
|
@ -53,7 +53,7 @@ groups() ->
|
||||
mv_file_dir_same, mv_file_dir_diff, mv_no_clobber]}].
|
||||
|
||||
init_per_group(reset_dir, Config) ->
|
||||
TmpDir = rebar_file_utils:system_tmpdir(["rebar_file_utils_SUITE", "resetable"]),
|
||||
TmpDir = rebar_file_utils:system_tmpdir(["rebar_file_utils_SUITE", "resettable"]),
|
||||
[{tmpdir, TmpDir} | Config];
|
||||
init_per_group(tmpdir, Config) ->
|
||||
PreviousTmpDir = os:getenv("TMPDIR"),
|
||||
|
@ -192,7 +192,7 @@ upgrade(Config) ->
|
||||
{{iolist_to_binary(PkgName), <<"0.1.1">>}, []}]}
|
||||
]),
|
||||
|
||||
%% beam file to verify plugin is acutally compiled
|
||||
%% beam file to verify plugin is actually compiled
|
||||
PluginBeam = filename:join([AppDir, "_build", "default", "plugins",
|
||||
PkgName, "ebin", [PkgName, ".beam"]]),
|
||||
|
||||
|
@ -49,7 +49,7 @@ release(Config) ->
|
||||
config_file(Config) ->
|
||||
AppDir = ?config(apps, Config),
|
||||
Name = list_to_atom(?config(name, Config)),
|
||||
%% Relase build fails if no relx config exists
|
||||
%% Release build fails if no relx config exists
|
||||
?assertError({error, {relx, no_releases_in_system}},
|
||||
rebar_test_utils:run_and_check(Config, [], ["release"], result)),
|
||||
%% Write relx.config
|
||||
|
Loading…
x
Reference in New Issue
Block a user