zx/zx
2017-11-29 16:04:11 +09:00

2565 lines
90 KiB
Erlang
Executable File

#! /usr/bin/env escript
%%% zx
%%%
%%% A general dependency and packaging tool that works together with the zomp
%%% package manager. Given a project directory with a standard layout, zx can:
%%% - Initialize your project for packaging and semver tracking under zomp.
%%% - Add dependencies (recursively) defined in any zomp repository realm.
%%% - Update dependencies (recursively) defined in any zomp repository realm.
%%% - Remove dependencies.
%%% - Update, upgrade or run any application from source that zomp tracks.
%%% - Locally install packages from files and locally stored public keys.
%%% - Build and run a local project from source using zomp dependencies.
-module(zx).
-mode(compile).
-export([main/1]).
-record(s,
{realm = "otpr" :: realm(),
name = none :: none | name(),
version = {z, z, z} :: version(),
type = app :: app | lib,
deps = [] :: [package_id()],
serial = 0 :: serial(),
dir = none :: none | file:filename(),
socket = none :: none | gen_tcp:socket(),
pid = none :: none | pid(),
mon = none :: none | reference()}).
-type state() :: #s{}.
-type serial() :: integer().
-type package_id() :: {realm(), name(), version()}.
-type package() :: {realm(), name()}.
-type realm() :: lower0_9().
-type name() :: lower0_9().
-type version() :: {Major :: non_neg_integer() | z,
Minor :: non_neg_integer() | z,
Patch :: non_neg_integer() | z}.
-type option() :: {string(), term()}.
-type host() :: {string() | inet:ip_address(), inet:port_number()}.
%-type keybin() :: {ID :: key_id(),
% Type :: public | private,
% DER :: binary()}.
-type key_id() :: {realm(), key_name()}.
-type key_name() :: label().
-type lower0_9() :: [$a..$z | $0..$9 | $_].
-type label() :: [$a..$z | $0..$9 | $_ | $- | $.].
-type package_meta() :: map().
-spec main(Args) -> no_return()
when Args :: [string()].
%% @private
%% The automatically exposed function initially called by escript to kick things off.
%% Args is a list of command-line provided arguments, all presented as a list of strings
%% delimited by whitespace in the shell.
main(Args) ->
ok = ensure_zomp_home(),
start(Args).
-spec start(Args) -> no_return()
when Args :: [string()].
%% Dispatch work functions based on the nature of the input arguments.
start(["help"]) ->
usage_exit(0);
start(["run", PackageString | Args]) ->
run(PackageString, Args);
start(["init", "app", PackageString]) ->
PackageID = package_id(PackageString),
initialize(app, PackageID);
start(["init", "lib", PackageString]) ->
PackageID = package_id(PackageString),
initialize(lib, PackageID);
start(["install", PackageFile]) ->
assimilate(PackageFile);
start(["set", "dep", PackageString]) ->
PackageID = package_id(PackageString),
set_dep(PackageID);
start(["set", "version", VersionString]) ->
set_version(VersionString);
start(["drop", "dep", PackageString]) ->
PackageID = package_id(PackageString),
drop_dep(PackageID);
start(["drop", "key", KeyID]) ->
drop_key(KeyID);
start(["verup", Level]) ->
verup(Level);
start(["runlocal" | Args]) ->
run_local(Args);
start(["package"]) ->
{ok, TargetDir} = file:get_cwd(),
package(TargetDir);
start(["package", TargetDir]) ->
case filelib:is_dir(TargetDir) of
true ->
package(TargetDir);
false ->
ok = log(error, "Target directory ~tp does not exist!", [TargetDir]),
halt(22)
end;
start(["submit", PackageFile]) ->
submit(PackageFile);
start(["dialyze"]) ->
dialyze();
start(["create", "keypair"]) ->
create_keypair();
start(["create", "plt"]) ->
create_plt();
start(["create", "realm"]) ->
create_realm();
start(["create", "sysop"]) ->
create_sysop();
start(_) ->
usage_exit(22).
%%% Execution of application
-spec run(Identifier, Args) -> no_return()
when Identifier :: string(),
Args :: [string()].
%% @private
%% Given a program Identifier and a list of Args, attempt to locate the program and its
%% dependencies and run the program. This implies determining whether the program and
%% its dependencies are installed, available, need to be downloaded, or are inaccessible
%% given the current system condition (they could also be bogus, of course). The
%% Identifier should be a valid PackageString of the form `realm-appname-version'
%% where the realm and appname should follow standard realm and app package naming
%% conventions and the version should be represented as a semver in string form (where
%% ommitted elements of the version always default to whatever is most current).
%%
%% Once the target program is running, this process, (which will run with the registered
%% name `zx') will sit in an `exec_wait' state, waiting for either a direct message from
%% a child program or for calls made via zx_lib to assist in environment discovery.
%%
%% If there is a problem anywhere in the locating, discovery, building, and loading
%% procedure the runtime will halt with an error message.
run(Identifier, Args) ->
MaybeID = package_id(Identifier),
{ok, PackageID = {Realm, Name, Version}} = ensure_installed(MaybeID),
ok = file:set_cwd(zomp_dir()),
Dir = filename:join("lib", package_string(PackageID)),
Meta = read_meta(Dir),
Deps = maps:get(deps, Meta),
ok = ensure_deps(Deps),
State = #s{realm = Realm,
name = Name,
version = Version,
dir = Dir,
deps = Deps},
execute(State, Args).
%%% Project initialization
-spec initialize(Type, PackageID) -> no_return()
when Type :: app | lib,
PackageID :: package_id().
%% @private
%% Initialize an application in the local directory based on the PackageID provided.
%% This function does not care about the name of the current directory and leaves
%% providing a complete, proper and accurate PackageID.
%% This function will check the current `lib/' directory for zomp-style dependencies.
%% If this is not the intended function or if there are non-compliant directory names
%% in `lib/' then the project will need to be rearranged to become zomp compliant or
%% the `deps' section of the resulting meta file will need to be manually updated.
initialize(Type, PackageID) ->
PackageString = package_string(PackageID),
ok = log(info, "Initializing ~s...", [PackageString]),
MetaList = [{package_id, PackageID},
{deps, []},
{type, Type}],
Meta = maps:from_list(MetaList),
ok = write_meta(Meta),
ok = log(info, "Project ~tp initialized.", [PackageString]),
Message =
"NOTICE:~n"
" This project is currently listed as having no dependencies.~n"
" If this is not true then run `zx set dep DepID` for each current dependency.~n"
" (run `zx help` for more information on usage)~n",
ok = io:format(Message),
halt(0).
%%% Add a package from a local file
-spec assimilate(PackageFile) -> PackageID
when PackageFile :: file:filename(),
PackageID :: package_id().
%% @private
%% Receives a path to a file containing package data, examines it, and copies it to a
%% canonical location under a canonical name, returning the PackageID of the package
%% contents.
assimilate(PackageFile) ->
Files = extract_zrp(PackageFile),
{ok, CWD} = file:get_cwd(),
ok = file:set_cwd(zomp_dir()),
{"zomp.meta", MetaBin} = lists:keyfind("zomp.meta", 1, Files),
Meta = binary_to_term(MetaBin),
PackageID = maps:get(package_id, Meta),
TgzFile = namify_tgz(PackageID),
{TgzFile, TgzData} = lists:keyfind(TgzFile, 1, Files),
{KeyID, Signature} = maps:get(sig, Meta),
{ok, PubKey} = loadkey(public, KeyID),
ok =
case public_key:verify(TgzData, sha512, Signature, PubKey) of
true ->
ZrpPath = filename:join("zrp", namify_zrp(PackageID)),
erl_tar:create(ZrpPath, Files);
false ->
error_exit("Bad package signature: ~ts", [PackageFile], ?FILE, ?LINE)
end,
ok = file:set_cwd(CWD),
Message = "~ts is now locally available.",
ok = log(info, Message, [package_string(PackageID)]),
halt(0).
%%% Set dependency
-spec set_dep(package_id()) -> no_return().
%% @private
%% Set a specific dependency in the current project. If the project currently has a
%% dependency on the same package then the version of that dependency is updated to
%% reflect that in the PackageString argument. The AppString is permitted to be
%% incomplete. Incomplete elements of the VersionString (if included) will default to
%% the latest version available at the indicated level.
set_dep(PackageID = {_, _, {X, Y, Z}})
when is_integer(X), is_integer(Y), is_integer(Z) ->
Meta = read_meta(),
Deps = maps:get(deps, Meta),
case lists:member(PackageID, Deps) of
true ->
ok = log(info, "~ts is already a dependency", [package_string(PackageID)]),
halt(0);
false ->
set_dep(PackageID, Deps, Meta)
end;
set_dep({Realm, Name, {z, z, z}}) ->
Socket = connect_user(Realm),
{ok, Version} = query_latest(Socket, {Realm, Name}),
ok = disconnect(Socket),
set_dep({Realm, Name, Version});
set_dep({Realm, Name, Version}) ->
Socket = connect_user(Realm),
{ok, Latest} = query_latest(Socket, {Realm, Name, Version}),
ok = disconnect(Socket),
set_dep({Realm, Name, Latest}).
-spec set_dep(PackageID, Deps, Meta) -> no_return()
when PackageID :: package_id(),
Deps :: [package_id()],
Meta :: [term()].
%% @private
%% Given the PackageID, list of Deps and the current contents of the project Meta, add
%% or update Deps to include (or update) Deps to reflect a dependency on PackageID, if
%% such a dependency is not already present. Then write the project meta back to its
%% file and exit.
set_dep(PackageID = {Realm, Name, NewVersion}, Deps, Meta) ->
ExistingPackageIDs = fun ({R, N, _}) -> {R, N} == {Realm, Name} end,
NewDeps =
case lists:partition(ExistingPackageIDs, Deps) of
{[{Realm, Name, OldVersion}], Rest} ->
Message = "Updating dep ~ts to ~ts",
OldPackageString = package_string({Realm, Name, OldVersion}),
NewPackageString = package_string({Realm, Name, NewVersion}),
ok = log(info, Message, [OldPackageString, NewPackageString]),
[PackageID | Rest];
{[], Deps} ->
ok = log(info, "Adding dep ~ts", [package_string(PackageID)]),
[PackageID | Deps]
end,
NewMeta = maps:put(deps, NewDeps, Meta),
ok = write_meta(NewMeta),
halt(0).
-spec ensure_installed(PackageID) -> Result | no_return()
when PackageID :: package_id(),
Result :: {ok, ActualID :: package_id()}.
%% @private
%% Given a PackageID, check whether it is installed on the system, and if not, ensure
%% that the package is either in the cache or can be downloaded. If all attempts at
%% locating or acquiring the package fail, then exit with an error.
ensure_installed(PackageID = {Realm, Name, Version}) ->
case resolve_installed_version(PackageID) of
exact -> {ok, PackageID};
{ok, Installed} -> {ok, {Realm, Name, Installed}};
not_found -> ensure_installed(Realm, Name, Version)
end.
-spec ensure_installed(Realm, Name, Version) -> Result
when Realm :: realm(),
Name :: name(),
Version :: version(),
Result :: exact
| {ok, package_id()}
| not_found.
%% @private
%% Fetch and install the latest compatible version of the given package ID, whether
%% the version indicator is complete, partial or blank.
ensure_installed(Realm, Name, Version) ->
Socket = connect_user(Realm),
case query_latest(Socket, {Realm, Name, Version}) of
{ok, LatestVersion} ->
LatestID = {Realm, Name, LatestVersion},
ok = ensure_dep(Socket, LatestID),
ok = disconnect(Socket),
{ok, LatestID};
{error, bad_realm} ->
PackageString = package_string({Realm, Name, Version}),
ok = log(warning, "Bad realm: ~ts.", [PackageString]),
halt(1);
{error, bad_package} ->
PackageString = package_string({Realm, Name, Version}),
ok = log(warning, "Bad package: ~ts.", [PackageString]),
halt(1);
{error, bad_version} ->
PackageString = package_string({Realm, Name, Version}),
ok = log(warning, "Bad version: ~s.", [PackageString]),
halt(1)
end.
-spec query_latest(Socket, Object) -> Result
when Socket :: gen_tcp:socket(),
Object :: package() | package_id(),
Result :: {ok, version()}
| {error, Reason},
Reason :: bad_realm
| bad_package
| bad_version.
%% @private
%% Queries the connected zomp node for the latest version of a package or package
%% version (complete or incomplete version number).
query_latest(Socket, {Realm, Name}) ->
ok = send(Socket, {latest, Realm, Name}),
receive
{tcp, Socket, Bin} -> binary_to_term(Bin)
after 5000 -> {error, timeout}
end;
query_latest(Socket, {Realm, Name, Version}) ->
ok = send(Socket, {latest, Realm, Name, Version}),
receive
{tcp, Socket, Bin} -> binary_to_term(Bin)
after 5000 -> {error, timeout}
end.
-spec resolve_installed_version(PackageID) -> Result
when PackageID :: package_id(),
Result :: not_found
| exact
| {ok, Installed :: version()}.
%% @private
%% Resolve the provided PackageID to the latest matching installed package directory
%% version if one exists, returning a value that indicates whether an exact match was
%% found (in the case of a full version input), a version matching a partial version
%% input was found, or no match was found at all.
resolve_installed_version(PackageID) ->
PackageString = package_string(PackageID),
Pattern = PackageString ++ "*",
case filelib:wildcard(Pattern, "lib") of
[] ->
not_found;
[PackageString] ->
exact;
[Dir] ->
{_, _, Version} = package_id(Dir),
{ok, Version};
Dirs ->
Dir = lists:last(lists:sort(Dirs)),
{_, _, Version} = package_id(Dir),
{ok, Version}
end.
ensure_deps(Deps) ->
case scrub(Deps) of
[] ->
ok;
Needed ->
Partitioned = partition_by_realm(Needed),
EnsureDeps =
fun({Realm, Packages}) ->
Socket = connect_user(Realm),
ok = ensure_deps(Socket, Realm, Packages),
ok = disconnect(Socket),
log(info, "Disconnecting from realm: ~ts", [Realm])
end,
lists:foreach(EnsureDeps, Partitioned)
end.
partition_by_realm(PackageIDs) ->
PartitionMap = lists:foldl(fun partition_by_realm/2, #{}, PackageIDs),
maps:to_list(PartitionMap).
partition_by_realm({R, P, V}, M) ->
maps:update_with(R, fun(Ps) -> [{P, V} | Ps] end, [{P, V}], M).
ensure_deps(_, _, []) ->
ok;
ensure_deps(Socket, Realm, [{Name, Version} | Rest]) ->
ok = ensure_dep(Socket, {Realm, Name, Version}),
ensure_deps(Socket, Realm, Rest).
-spec ensure_dep(gen_tcp:socket(), package_id()) -> ok | no_return().
%% @private
%% Given an PackageID as an argument, check whether its package file exists in the
%% system cache, and if not download it. Should return `ok' whenever the file is
%% sourced, but exit with an error if it cannot locate or acquire the package.
ensure_dep(Socket, PackageID) ->
ZrpFile = filename:join("zrp", namify_zrp(PackageID)),
ok =
case filelib:is_regular(ZrpFile) of
true -> ok;
false -> fetch(Socket, PackageID)
end,
ok = install(PackageID),
build(PackageID).
%%% Set version
-spec set_version(VersionString) -> no_return()
when VersionString :: string().
%% @private
%% Convert a version string to a new version, sanitizing it in the process and returning
%% a reasonable error message on bad input.
set_version(VersionString) ->
NewVersion =
case string_to_version(VersionString) of
{_, _, z} ->
Message = "'set version' arguments must be complete, ex: 1.2.3",
ok = log(error, Message),
halt(22);
Version ->
Version
end,
update_version(NewVersion).
-spec update_version(Level) -> no_return()
when Level :: major
| minor
| patch
| VersionString,
VersionString :: string(). % Of the form "Major.Minor.Patch"
%% @private
%% Update a project's `zomp.meta' file by either incrementing the indicated component,
%% or setting the version number to the one specified in VersionString.
%% This part of the procedure guards for the case when the zomp.meta file cannot be
%% read for some reason.
update_version(Arg) ->
Meta = read_meta(),
PackageID = maps:get(package_id, Meta),
update_version(Arg, PackageID, Meta).
-spec update_version(Level, PackageID, Meta) -> no_return()
when Level :: major
| minor
| patch
| version(),
PackageID :: package_id(),
Meta :: [{atom(), term()}].
%% @private
%% Update a project's `zomp.meta' file by either incrementing the indicated component,
%% or setting the version number to the one specified in VersionString.
%% This part of the procedure does the actual update calculation, to include calling to
%% convert the VersionString (if it is passed) to a `version()' type and check its
%% validity (or halt if it is a bad string).
update_version(major, {Realm, Name, OldVersion = {Major, _, _}}, OldMeta) ->
NewVersion = {Major + 1, 0, 0},
update_version(Realm, Name, OldVersion, NewVersion, OldMeta);
update_version(minor, {Realm, Name, OldVersion = {Major, Minor, _}}, OldMeta) ->
NewVersion = {Major, Minor + 1, 0},
update_version(Realm, Name, OldVersion, NewVersion, OldMeta);
update_version(patch, {Realm, Name, OldVersion = {Major, Minor, Patch}}, OldMeta) ->
NewVersion = {Major, Minor, Patch + 1},
update_version(Realm, Name, OldVersion, NewVersion, OldMeta);
update_version(NewVersion, {Realm, Name, OldVersion}, OldMeta) ->
update_version(Realm, Name, OldVersion, NewVersion, OldMeta).
-spec update_version(Realm, Name, OldVersion, NewVersion, OldMeta) -> no_return()
when Realm :: realm(),
Name :: name(),
OldVersion :: version(),
NewVersion :: version(),
OldMeta :: [{atom(), term()}].
%% @private
%% Update a project's `zomp.meta' file by either incrementing the indicated component,
%% or setting the version number to the one specified in VersionString.
%% This part of the procedure updates the meta and does the final write, if the write
%% turns out to be possible. If successful it will indicate to the user what was
%% changed.
update_version(Realm, Name, OldVersion, NewVersion, OldMeta) ->
PackageID = {Realm, Name, NewVersion},
NewMeta = maps:put(package_id, PackageID, OldMeta),
ok = write_meta(NewMeta),
ok = log(info,
"Version changed from ~s to ~s.",
[version_to_string(OldVersion), version_to_string(NewVersion)]),
halt(0).
%%% Drop dependency
-spec drop_dep(package_id()) -> no_return().
%% @private
%% Remove the indicate dependency from the local project's zomp.meta record.
drop_dep(PackageID) ->
PackageString = package_string(PackageID),
Meta = read_meta(),
Deps = maps:get(deps, Meta),
case lists:member(PackageID, Deps) of
true ->
NewDeps = lists:delete(PackageID, Deps),
NewMeta = maps:put(deps, NewDeps, Meta),
ok = write_meta(NewMeta),
Message = "~ts removed from dependencies.",
ok = log(info, Message, [PackageString]),
halt(0);
false ->
ok = log(info, "~ts not found in dependencies.", [PackageString]),
halt(0)
end.
%%% Drop key
-spec drop_key(key_id()) -> no_return().
%% @private
%% Given a KeyID, remove the related public and private keys from the keystore, if they
%% exist. If not, exit with a message that no keys were found, but do not return an
%% error exit value (this instruction is idempotent if used in shell scripts).
drop_key({Realm, KeyName}) ->
ok = file:set_cwd(zomp_dir()),
Pattern = filename:join([zomp_dir(), "key", Realm, KeyName ++ ".{key,pub}.der"]),
case filelib:wildcard(Pattern) of
[] ->
ok = log(warning, "Key ~ts/~ts not found", [Realm, KeyName]),
halt(0);
Files ->
ok = lists:foreach(fun file:delete/1, Files),
ok = log(info, "Keyset ~ts/~ts removed", [Realm, KeyName]),
halt(0)
end.
%%% Update version
-spec verup(Level) -> no_return()
when Level :: string().
%% @private
%% Convert input string arguments to acceptable atoms for use in update_version/1.
verup("major") -> update_version(major);
verup("minor") -> update_version(minor);
verup("patch") -> update_version(patch);
verup(_) -> usage_exit(22).
%%% Run local project
-spec run_local(Args) -> no_return()
when Args :: [term()].
%% @private
%% Execute a local project from source from the current directory, satisfying dependency
%% requirements via the locally installed zomp lib cache. The project must be
%% initialized as a zomp project (it must have a valid `zomp.meta' file).
%%
%% The most common use case for this function is during development. Using zomp support
%% via the local lib cache allows project authors to worry only about their own code
%% and use zx commands to add or drop dependencies made available via zomp.
run_local(Args) ->
Meta = read_meta(),
{Realm, Name, Version} = maps:get(package_id, Meta),
Type = maps:get(type, Meta),
Deps = maps:get(deps, Meta),
ok = build(),
{ok, Dir} = file:get_cwd(),
ok = file:set_cwd(zomp_dir()),
State = #s{realm = Realm,
name = Name,
version = Version,
type = Type,
deps = Deps,
dir = Dir},
ok = ensure_deps(Deps),
ok = file:set_cwd(Dir),
execute(State, Args).
execute(State = #s{type = app, realm = Realm, name = Name, version = Version}, Args) ->
true = register(zx, self()),
ok = inets:start(),
ok = log(info, "Starting ~ts", [package_string({Realm, Name, Version})]),
AppMod = list_to_atom(Name),
{ok, Pid} = AppMod:start(normal, Args),
Mon = monitor(process, Pid),
Shell = spawn(shell, start, []),
ok = log(info, "Your shell is ~p, application is: ~p", [Shell, Pid]),
exec_wait(State#s{pid = Pid, mon = Mon});
execute(#s{type = lib, realm = Realm, name = Name, version = Version}, _) ->
Message = "Lib ~ts is available on the system, but is not a standalone app.",
PackageString = package_string({Realm, Name, Version}),
ok = log(info, Message, [PackageString]),
halt(0).
%%% Package generation
-spec package(TargetDir) -> no_return()
when TargetDir :: file:filename().
%% @private
%% Turn a target project directory into a package, prompting the user for appropriate
%% key selection or generation actions along the way.
package(TargetDir) ->
ok = log(info, "Packaging ~ts", [TargetDir]),
Meta = read_meta(TargetDir),
{Realm, _, _} = maps:get(package_id, Meta),
KeyDir = filename:join([zomp_dir(), "key", Realm]),
ok = force_dir(KeyDir),
Pattern = KeyDir ++ "/*.key.der",
case [filename:basename(F, ".key.der") || F <- filelib:wildcard(Pattern)] of
[] ->
ok = log(info, "Need to generate key"),
KeyID = prompt_keygen(),
{ok, _, _} = generate_rsa(KeyID),
package(KeyID, TargetDir);
[KeyName] ->
KeyID = {Realm, KeyName},
ok = log(info, "Using key: ~ts/~ts", [Realm, KeyName]),
package(KeyID, TargetDir);
KeyNames ->
KeyName = select_string(KeyNames),
package({Realm, KeyName}, TargetDir)
end.
-spec package(KeyID, TargetDir) -> no_return()
when KeyID :: key_id(),
TargetDir :: file:filename().
%% @private
%% Accept a KeyPrefix for signing and a TargetDir containing a project to package and
%% build a zrp package file ready to be submitted to a repository.
package(KeyID, TargetDir) ->
Meta = read_meta(TargetDir),
PackageID = maps:get(package_id, Meta),
true = element(1, PackageID) == element(1, KeyID),
PackageString = package_string(PackageID),
ZrpFile = PackageString ++ ".zrp",
TgzFile = PackageString ++ ".tgz",
ok = halt_if_exists(ZrpFile),
ok = remove_binaries(TargetDir),
{ok, Everything} = file:list_dir(TargetDir),
DotFiles = filelib:wildcard(".*", TargetDir),
Ignores = ["lib" | DotFiles],
Targets = lists:subtract(Everything, Ignores),
{ok, CWD} = file:get_cwd(),
ok = file:set_cwd(TargetDir),
ok = build(),
Modules = [filename:basename(M, ".beam") || M <- filelib:wildcard("*.beam", "ebin")],
ok = remove_binaries("."),
ok = erl_tar:create(filename:join(CWD, TgzFile), Targets, [compressed]),
ok = file:set_cwd(CWD),
{ok, Key} = loadkey(private, KeyID),
{ok, TgzBin} = file:read_file(TgzFile),
Sig = public_key:sign(TgzBin, sha512, Key),
Add = fun({K, V}, M) -> maps:put(K, V, M) end,
FinalMeta = lists:foldl(Add, Meta, [{modules, Modules}, {sig, {KeyID, Sig}}]),
ok = file:write_file("zomp.meta", term_to_binary(FinalMeta)),
ok = erl_tar:create(ZrpFile, ["zomp.meta", TgzFile]),
ok = file:delete(TgzFile),
ok = file:delete("zomp.meta"),
ok = log(info, "Wrote archive ~ts", [ZrpFile]),
halt(0).
-spec remove_binaries(TargetDir) -> ok
when TargetDir :: file:filename().
%% @private
%% Procedure to delete all .beam and .ez files from a given directory starting at
%% TargetDir. Called as part of the pre-packaging sanitization procedure.
remove_binaries(TargetDir) ->
Beams = filelib:wildcard("**/*.{beam,ez}", TargetDir),
case [filename:join(TargetDir, Beam) || Beam <- Beams] of
[] ->
ok;
ToDelete ->
ok = log(info, "Removing: ~tp", [ToDelete]),
lists:foreach(fun file:delete/1, ToDelete)
end.
%%% App execution loop
-spec exec_wait(State) -> no_return()
when State :: state().
%% @private
%% Execution maintenance loop.
%% Once an application is started by zompc this process will wait for a message from
%% the application if that application was written in a way to take advantage of zompc
%% facilities such as post-start upgrade checking.
%%
%% NOTE:
%% Adding clauses to this `receive' is where new functionality belongs.
%% It may make sense to add a `zompc_lib' as an available dependency authors could
%% use to interact with zompc without burying themselves under the complexity that
%% can come with naked send operations. (Would it make sense, for example, to have
%% the registered zompc process convert itself to a gen_server via zompc_lib to
%% provide more advanced functionality?)
exec_wait(State = #s{pid = Pid, mon = Mon}) ->
receive
{check_update, Requester, Ref} ->
{Response, NewState} = check_update(State),
Requester ! {Ref, Response},
exec_wait(NewState);
{exit, Reason} ->
ok = log(info, "Exiting with: ~tp", [Reason]),
halt(0);
{'DOWN', Mon, process, Pid, normal} ->
ok = log(info, "Application exited normally."),
halt(0);
{'DOWN', Mon, process, Pid, Reason} ->
ok = log(warning, "Application exited with: ~tp", [Reason]),
halt(1);
Unexpected ->
ok = log(warning, "Unexpected message: ~tp", [Unexpected]),
exec_wait(State)
end.
-spec check_update(State) -> {Response, NewState}
when State :: state(),
Response :: term(),
NewState :: state().
%% @private
%% Check for updated version availability of the current application.
%% The return value should probably provide up to three results, a Major, Minor and
%% Patch update, and allow the Requestor to determine what to do with it via some
%% interaction.
check_update(State) ->
ok = log(info, "Would be checking for an update of the current application now..."),
Response = "Nothing was checked, but you can imagine it to have been.",
{Response, State}.
%%% Package submission
-spec submit(PackageFile) -> no_return()
when PackageFile :: file:filename().
%% @private
%% Submit a package to the appropriate "prime" server for the given realm.
submit(PackageFile) ->
Files = extract_zrp(PackageFile),
{ok, PackageData} = file:read_file(PackageFile),
{"zomp.meta", MetaBin} = lists:keyfind("zomp.meta", 1, Files),
Meta = binary_to_term(MetaBin),
{package_id, {Realm, Package, Version}} = lists:keyfind(package_id, 1, Meta),
{sig, {KeyID = {Realm, KeyName}, _}} = lists:keyfind(sig, 1, Meta),
true = ensure_keypair(KeyID),
{ok, Socket} = connect_auth(Realm, KeyName),
ok = send(Socket, {submit, {Realm, Package, Version}}),
ok =
receive
{tcp, Socket, Response1} ->
case binary_to_term(Response1) of
ready ->
ok;
{error, Reason} ->
ok = log(info, "Server refused with ~tp", [Reason]),
halt(0)
end
after 5000 ->
ok = log(warning, "Server timed out!"),
halt(0)
end,
ok = send(Socket, PackageData),
ok = log(info, "Done sending contents of ~tp", [PackageFile]),
ok =
receive
{tcp, Socket, Response2} ->
log(info, "Response: ~tp", [Response2])
after 5000 ->
log(warning, "Server timed out!")
end,
ok = disconnect(Socket),
halt(0).
-spec send(Socket, Message) -> ok
when Socket :: gen_tcp:socket(),
Message :: term().
%% @private
%% Wrapper for the procedure necessary to send an internal message over the wire.
send(Socket, Message) ->
Bin = term_to_binary(Message),
gen_tcp:send(Socket, Bin).
-spec connect_user(realm()) -> gen_tcp:socket() | no_return().
%% @private
%% Connect to a given realm, whatever method is required.
connect_user(Realm) ->
ok = log(info, "Connecting to realm ~ts...", [Realm]),
Hosts =
case file:consult(hosts_cache_file(Realm)) of
{ok, Cached} -> Cached;
{error, enoent} -> []
end,
connect_user(Realm, Hosts).
-spec connect_user(realm(), [host()]) -> gen_tcp:socket() | no_return().
%% @private
%% Try to connect to a subordinate host, if there are none then connect to prime.
connect_user(Realm, []) ->
{Host, Port} = get_prime(Realm),
ok = log(info, "Trying prime at ~ts:~tp", [inet:ntoa(Host), Port]),
case gen_tcp:connect(Host, Port, connect_options(), 5000) of
{ok, Socket} ->
confirm_user(Realm, Socket, []);
{error, Error} ->
ok = log(warning, "Connection problem with prime: ~tp", [Error]),
halt(0)
end;
connect_user(Realm, Hosts = [Node = {Host, Port} | Rest]) ->
ok = log(info, "Trying node at ~ts:~tp", [inet:ntoa(Host), Port]),
case gen_tcp:connect(Host, Port, connect_options(), 5000) of
{ok, Socket} ->
confirm_user(Realm, Socket, Hosts);
{error, Error} ->
ok = log(warning, "Connection problem with ~tp: ~tp", [Node, Error]),
connect_user(Realm, Rest)
end.
-spec confirm_user(Realm, Socket, Hosts) -> Socket | no_return()
when Realm :: realm(),
Socket :: gen_tcp:socket(),
Hosts :: [host()].
%% @private
%% Confirm the zomp node can handle "OTPR USER 1" and is accepting connections or try
%% another node.
confirm_user(Realm, Socket, Hosts) ->
{ok, {Addr, Port}} = inet:peername(Socket),
Host = inet:ntoa(Addr),
ok = gen_tcp:send(Socket, <<"OTPR USER 1">>),
receive
{tcp, Socket, Bin} ->
case binary_to_term(Bin) of
ok ->
ok = log(info, "Connected to ~ts:~p", [Host, Port]),
confirm_serial(Realm, Socket, Hosts);
{redirect, Next} ->
ok = log(info, "Redirected..."),
ok = disconnect(Socket),
connect_user(Realm, Next ++ Hosts)
end
after 5000 ->
ok = log(warning, "Host ~ts:~p timed out.", [Host, Port]),
ok = disconnect(Socket),
connect_user(Realm, Hosts)
end.
-spec confirm_serial(Realm, Socket, Hosts) -> Socket | no_return()
when Realm :: realm(),
Socket :: gen_tcp:socket(),
Hosts :: [host()].
%% @private
%% Confirm that the connected host has a valid serial for the realm zx is trying to
%% reach, and if not retry on another node.
confirm_serial(Realm, Socket, Hosts) ->
SerialFile = filename:join(zomp_dir(), "realm.serials"),
Serials =
case file:consult(SerialFile) of
{ok, Ss} -> Ss;
{error, enoent} -> []
end,
Serial =
case lists:keyfind(Realm, 1, Serials) of
false -> 0;
{Realm, S} -> S
end,
ok = send(Socket, {latest, Realm}),
receive
{tcp, Socket, Bin} ->
case binary_to_term(Bin) of
{ok, Serial} ->
ok = log(info, "Node's serial same as ours."),
Socket;
{ok, Current} when Current > Serial ->
ok = log(info, "Node's serial newer than ours. Storing."),
NewSerials = lists:keystore(Realm, 1, Current, {Realm, Serials}),
{ok, Host} = inet:peername(Socket),
ok = write_terms(hosts_cache_file(Realm), [Host | Hosts]),
ok = write_terms(SerialFile, NewSerials),
Socket;
{ok, Current} when Current < Serial ->
log(info, "Our serial: ~tp, node serial: ~tp.", [Serial, Current]),
ok = log(info, "Node's serial older than ours. Trying another."),
ok = disconnect(Socket),
connect_user(Realm, Hosts);
{error, bad_realm} ->
ok = log(info, "Node is no longer serving realm. Trying another."),
ok = disconnect(Socket),
connect_user(Realm, Hosts)
end
after 5000 ->
ok = log(info, "Host timed out on confirm_serial. Trying another."),
ok = disconnect(Socket),
connect_user(Realm, Hosts)
end.
-spec connect_auth(Realm, KeyName) -> Result
when Realm :: realm(),
KeyName :: key_name(),
Result :: {ok, gen_tcp:socket()}
| {error, Reason :: term()}.
%% @private
%% Connect to one of the servers in the realm constellation.
connect_auth(Realm, KeyName) ->
{ok, Key} = loadkey(private, {Realm, KeyName}),
{Host, Port} = get_prime(Realm),
case gen_tcp:connect(Host, Port, connect_options(), 5000) of
{ok, Socket} ->
ok = log(info, "Connected to ~tp prime.", [Realm]),
confirm_auth(Socket, Key);
Error = {error, E} ->
ok = log(warning, "Connection problem: ~tp", [E]),
{error, Error}
end.
-spec confirm_auth(Socket, Key) -> Result
when Socket :: gen_tcp:socket(),
Key :: term(),
Result :: {ok, gen_tcp:socket()}
| {error, timeout}.
%% @private
%% Send a protocol ID string to notify the server what we're up to, disconnect
%% if it does not return an "OK" response within 5 seconds.
confirm_auth(Socket, Key) ->
ok = log(info, "Would be using key ~tp now", [Key]),
{ok, {Host, Port}} = inet:peername(Socket),
ok = gen_tcp:send(Socket, <<"OTPR AUTH 1">>),
receive
{tcp, Socket, <<"OK">>} ->
{ok, Socket}
after 5000 ->
ok = log(warning, "Host ~s:~p timed out.", [Host, Port]),
{error, auth_timeout}
end.
-spec connect_options() -> [gen_tcp:connect_option()].
%% @private
%% Hide away the default options used for TCP connections.
connect_options() ->
[{packet, 4}, {mode, binary}, {active, true}].
-spec get_prime(realm()) -> host().
%% @private
%% Check the given Realm's config file for the current prime node and return it.
get_prime(Realm) ->
RealmMeta = realm_meta(Realm),
{prime, Prime} = lists:keyfind(prime, 1, RealmMeta),
Prime.
-spec hosts_cache_file(realm()) -> file:filename().
%% @private
%% Given a Realm name, construct a realm's .hosts filename and return it.
hosts_cache_file(Realm) ->
filename:join(zomp_dir(), Realm ++ ".hosts").
-spec disconnect(gen_tcp:socket()) -> ok.
%% @private
%% Gracefully shut down a socket, logging (but sidestepping) the case when the socket
%% has already been closed by the other side.
disconnect(Socket) ->
case gen_tcp:shutdown(Socket, read_write) of
ok ->
log(info, "Disconnected from ~tp", [Socket]);
{error, Error} ->
Message = "Shutdown connection ~p failed with: ~p",
log(warning, Message, [Socket, Error])
end.
-spec ensure_keypair(key_id()) -> true | no_return().
%% @private
%% Check if both the public and private key based on KeyID exists.
ensure_keypair(KeyID = {Realm, KeyName}) ->
case {have_public_key(KeyID), have_private_key(KeyID)} of
{true, true} ->
true;
{false, true} ->
Message = "Public key for ~tp/~tp cannot be found",
ok = log(error, Message, [Realm, KeyName]),
halt(1);
{true, false} ->
Message = "Private key for ~tp/~tp cannot be found",
ok = log(error, Message, [Realm, KeyName]),
halt(1);
{false, false} ->
Message = "Key pair for ~tp/~tp cannot be found",
ok = log(error, Message, [Realm, KeyName]),
halt(1)
end.
-spec have_public_key(key_id()) -> boolean().
%% @private
%% Determine whether the public key indicated by KeyID is in the keystore.
have_public_key({Realm, KeyName}) ->
PublicKeyFile = KeyName ++ ".pub.der",
PublicKeyPath = filename:join([zomp_dir(), "key", Realm, PublicKeyFile]),
filelib:is_regular(PublicKeyPath).
-spec have_private_key(key_id()) -> boolean().
%% @private
%% Determine whether the private key indicated by KeyID is in the keystore.
have_private_key({Realm, KeyName}) ->
PrivateKeyFile = KeyName ++ ".key.der",
PrivateKeyPath = filename:join([zomp_dir(), "key", Realm, PrivateKeyFile]),
filelib:is_regular(PrivateKeyPath).
-spec realm_meta(Realm) -> Meta | no_return()
when Realm :: string(),
Meta :: [{atom(), term()}].
%% @private
%% Given a realm name, try to locate and read the realm's configuration file if it
%% exists, exiting with an appropriate error message if there is a problem reading
%% the file.
realm_meta(Realm) ->
RealmFile = filename:join(zomp_dir(), Realm ++ ".realm"),
case file:consult(RealmFile) of
{ok, Meta} ->
Meta;
{error, enoent} ->
ok = log(error, "No realm file for ~ts", [Realm]),
halt(1);
Error ->
Message = "Open realm file ~ts failed with ~ts",
error_exit(Message, [RealmFile, Error], ?FILE, ?LINE)
end.
%%% Key generation
-spec prompt_keygen() -> key_id().
%% @private
%% Prompt the user for a valid KeyPrefix to use for naming a new RSA keypair.
prompt_keygen() ->
Message =
"~n Enter a name for your new keys.~n~n"
" Valid names must start with a lower-case letter, and can include~n"
" only lower-case letters, numbers, and periods, but no series of~n"
" consecutive periods. (That is: [a-z0-9\\.])~n~n"
" To designate the key as realm-specific, enter the realm name and~n"
" key name separated by a space.~n~n"
" Example: some.realm my.key~n",
ok = io:format(Message),
Input = get_input(),
{Realm, KeyName} =
case string:lexemes(Input, " ") of
[R, K] -> {R, K};
[K] -> {"otpr", K}
end,
case {valid_lower0_9(Realm), valid_label(KeyName)} of
{true, true} ->
{Realm, KeyName};
{false, true} ->
ok = io:format("Bad realm name ~tp. Try again.~n", [Realm]),
prompt_keygen();
{true, false} ->
ok = io:format("Bad key name ~tp. Try again.~n", [KeyName]),
prompt_keygen();
{false, false} ->
ok = io:format("NUTS! Both key and realm names are illegal. Try again.~n"),
prompt_keygen()
end.
-spec create_keypair() -> no_return().
%% @private
%% Execute the key generation procedure for 16k RSA keys once and then terminate.
create_keypair() ->
ok = file:set_cwd(zomp_dir()),
KeyID = prompt_keygen(),
case generate_rsa(KeyID) of
{ok, _, _} -> halt(0);
Error -> error_exit("create_keypair/0 error: ~tp", [Error], ?FILE, ?LINE)
end.
-spec generate_rsa(KeyID) -> Result
when KeyID :: key_id(),
Result :: {ok, KeyFile, PubFile}
| {error, keygen_fail},
KeyFile :: file:filename(),
PubFile :: file:filename().
%% @private
%% Generate an RSA keypair and write them in der format to the current directory, using
%% filenames derived from Prefix.
%% NOTE: The current version of this command is likely to only work on a unix system.
generate_rsa({Realm, KeyName}) ->
KeyDir = filename:join([zomp_dir(), "key", Realm]),
ok = force_dir(KeyDir),
PemFile = filename:join(KeyDir, KeyName ++ ".pub.pem"),
KeyFile = filename:join(KeyDir, KeyName ++ ".key.der"),
PubFile = filename:join(KeyDir, KeyName ++ ".pub.der"),
ok = lists:foreach(fun halt_if_exists/1, [PemFile, KeyFile, PubFile]),
ok = log(info, "Generating ~p and ~p. Please be patient...", [KeyFile, PubFile]),
ok = gen_p_key(KeyFile),
ok = der_to_pem(KeyFile, PemFile),
{ok, PemBin} = file:read_file(PemFile),
[PemData] = public_key:pem_decode(PemBin),
Pub = public_key:pem_entry_decode(PemData),
PubDer = public_key:der_encode('RSAPublicKey', Pub),
ok = file:write_file(PubFile, PubDer),
case check_key(KeyFile, PubFile) of
true ->
ok = file:delete(PemFile),
ok = log(info, "~ts and ~ts agree", [KeyFile, PubFile]),
ok = log(info, "Wrote private key to: ~ts.", [KeyFile]),
ok = log(info, "Wrote public key to: ~ts.", [PubFile]),
{ok, KeyFile, PubFile};
false ->
ok = lists:foreach(fun file:delete/1, [PemFile, KeyFile, PubFile]),
ok = log(error, "Something has gone wrong."),
{error, keygen_fail}
end.
-spec halt_if_exists(file:filename()) -> ok | no_return().
%% @private
%% A helper function to guard against overwriting an existing file. Halts execution if
%% the file is found to exist.
halt_if_exists(Path) ->
case filelib:is_file(Path) of
true ->
ok = log(error, "~ts already exists! Halting.", [Path]),
halt(1);
false ->
ok
end.
-spec gen_p_key(KeyFile) -> ok
when KeyFile :: file:filename().
%% @private
%% Format an openssl shell command that will generate proper 16k RSA keys.
gen_p_key(KeyFile) ->
Command =
io_lib:format("~ts genpkey"
" -algorithm rsa"
" -out ~ts"
" -outform DER"
" -pkeyopt rsa_keygen_bits:16384",
[openssl(), KeyFile]),
Out = os:cmd(Command),
io:format(Out).
-spec der_to_pem(KeyFile, PemFile) -> ok
when KeyFile :: file:filename(),
PemFile :: file:filename().
%% @private
%% Format an openssl shell command that will convert the given keyfile to a pemfile.
%% The reason for this conversion is to sidestep some formatting weirdness that OpenSSL
%% injects into its generated DER formatted key output (namely, a few empty headers)
%% which Erlang's ASN.1 defintion files do not take into account. A conversion to PEM
%% then a conversion back to DER (via Erlang's ASN.1 module) resolves this in a reliable
%% way.
der_to_pem(KeyFile, PemFile) ->
Command =
io_lib:format("~ts rsa"
" -inform DER"
" -in ~ts"
" -outform PEM"
" -pubout"
" -out ~ts",
[openssl(), KeyFile, PemFile]),
Out = os:cmd(Command),
io:format(Out).
-spec check_key(KeyFile, PubFile) -> Result
when KeyFile :: file:filename(),
PubFile :: file:filename(),
Result :: true | false.
%% @private
%% Compare two keys for pairedness.
check_key(KeyFile, PubFile) ->
{ok, KeyBin} = file:read_file(KeyFile),
{ok, PubBin} = file:read_file(PubFile),
Key = public_key:der_decode('RSAPrivateKey', KeyBin),
Pub = public_key:der_decode('RSAPublicKey', PubBin),
TestMessage = <<"Some test data to sign.">>,
Signature = public_key:sign(TestMessage, sha512, Key),
public_key:verify(TestMessage, sha512, Signature, Pub).
-spec openssl() -> Executable | no_return()
when Executable :: file:filename().
%% @private
%% Attempt to locate the installed openssl executable for use in shell commands.
%% Halts execution with an error message if the executable cannot be found.
openssl() ->
OpenSSL =
case os:type() of
{unix, _} -> "openssl";
{win32, _} -> "openssl.exe"
end,
ok =
case os:find_executable(OpenSSL) of
false ->
ok = log(error, "OpenSSL could not be found in this system's PATH."),
ok = log(error, "Install OpenSSL and then retry."),
error_exit("Missing system dependenct: OpenSSL", ?FILE, ?LINE);
Path ->
log(info, "OpenSSL executable found at: ~ts", [Path])
end,
OpenSSL.
-spec loadkey(Type, KeyID) -> Result
when Type :: private | public,
KeyID :: key_id(),
Result :: {ok, DecodedKey :: term()}
| {error, Reason :: term()}.
%% @private
%% Hide the details behind reading and loading DER encoded RSA key files.
loadkey(Type, {Realm, KeyName}) ->
{DerType, Path} =
case Type of
private ->
P = filename:join([zomp_dir(), "key", Realm, KeyName ++ "key.der"]),
{'RSAPrivateKey', P};
public ->
P = filename:join([zomp_dir(), "key", Realm, KeyName ++ "pub.der"]),
{'RSAPublicKey', P}
end,
ok = log(info, "Loading key from file ~ts", [Path]),
case file:read_file(Path) of
{ok, Bin} -> {ok, public_key:der_decode(DerType, Bin)};
Error -> Error
end.
%%% Generate PLT
-spec create_plt() -> no_return().
%% @private
%% Generate a fresh PLT file that includes most basic core applications needed to
%% make a resonable estimate of a type system, write the name of the PLT to stdout,
%% and exit.
create_plt() ->
ok = build_plt(),
halt(0).
build_plt() ->
PLT = default_plt(),
Template =
"dialyzer --build_plt"
" --output_plt ~ts"
" --apps asn1 reltool wx common_test crypto erts eunit inets"
" kernel mnesia public_key sasl ssh ssl stdlib",
Command = io_lib:format(Template, [PLT]),
Message =
"Generating PLT file and writing to: ~tp~n"
" There will be a list of \"unknown functions\" in the final output.~n"
" Don't panic. This is normal. Turtles all the way down, after all...",
ok = log(info, Message, [PLT]),
ok = log(info, "This may take a while. Patience is a virtue."),
Out = os:cmd(Command),
log(info, Out).
default_plt() ->
filename:join(zomp_dir(), "basic.plt").
%%% Dialyze
-spec dialyze() -> no_return().
%% @private
%% Preps a copy of this script for typechecking with Dialyzer.
dialyze() ->
PLT = default_plt(),
ok =
case filelib:is_regular(PLT) of
true -> log(info, "Using PLT: ~tp", [PLT]);
false -> build_plt()
end,
TmpDir = filename:join(zomp_dir(), "tmp"),
Me = escript:script_name(),
EvilTwin = filename:join(TmpDir, filename:basename(Me ++ ".erl")),
ok = log(info, "Temporarily reconstructing ~tp as ~tp", [Me, EvilTwin]),
Sed = io_lib:format("sed 's/^#!.*$//' ~s > ~s", [Me, EvilTwin]),
"" = os:cmd(Sed),
ok = case dialyzer:run([{init_plt, PLT}, {from, src_code}, {files, [EvilTwin]}]) of
[] ->
io:format("Dialyzer found no errors and returned no warnings! Yay!~n");
Warnings ->
Mine = [dialyzer:format_warning({Tag, {Me, Line}, Msg})
|| {Tag, {_, Line}, Msg} <- Warnings],
lists:foreach(fun io:format/1, Mine)
end,
ok = file:delete(EvilTwin),
halt(0).
%%% Create Realm & Sysop
-spec create_realm() -> no_return().
%% @private
%% Prompt the user to input the information necessary to create a new zomp realm,
%% package the data appropriately for the server and deliver the final keys and
%% realm file to the user.
create_realm() ->
ConfFile = filename:join(zomp_dir(), "zomp.conf"),
case file:consult(ConfFile) of
{ok, ZompConf} -> create_realm(ZompConf);
{error, enoent} -> create_realm([])
end.
-spec create_realm(ZompConf) -> no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}].
create_realm(ZompConf) ->
Instructions =
"~n"
" Enter a name for your new realm.~n"
" Names can contain only lower-case letters, numbers and the underscore.~n"
" Names must begin with a lower-case letter.~n",
ok = io:format(Instructions),
Realm = get_input(),
case valid_lower0_9(Realm) of
true ->
RealmFile = filename:join(zomp_dir(), Realm ++ ".realm"),
case filelib:is_regular(RealmFile) of
false ->
create_realm(ZompConf, Realm);
true ->
ok = io:format("That realm already exists. Be more original.~n"),
create_realm(ZompConf)
end;
false ->
ok = io:format("Bad realm name \"~ts\". Try again.~n", [Realm]),
create_realm(ZompConf)
end.
-spec create_realm(ZompConf, Realm) -> no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}],
Realm :: realm().
create_realm(ZompConf, Realm) ->
ExAddress =
case lists:keyfind(external_address, 1, ZompConf) of
false -> prompt_external_address();
{external_address, none} -> prompt_external_address();
{external_address, Current} -> prompt_external_address(Current)
end,
create_realm(ZompConf, Realm, ExAddress).
-spec prompt_external_address() -> Result
when Result :: inet:hostname() | inet:ip_address().
prompt_external_address() ->
Message = external_address_prompt(),
ok = io:format(Message),
case get_input() of
"" ->
ok = io:format("You need to enter an address.~n"),
prompt_external_address();
String ->
parse_address(String)
end.
-spec prompt_external_address(Current) -> Result
when Current :: inet:hostname() | inet:ip_address(),
Result :: inet:hostname() | inet:ip_address().
prompt_external_address(Current) ->
XAString =
case inet:ntoa(Current) of
{error, einval} -> Current;
XAS -> XAS
end,
Message =
external_address_prompt() ++
" [The current public address is: ~ts. Press <ENTER> to keep this address.]~n",
ok = io:format(Message, [XAString]),
case get_input() of
"" -> Current;
String -> parse_address(String)
end.
-spec external_address_prompt() -> string().
external_address_prompt() ->
"~n"
" Enter a static, valid hostname or IPv4 or IPv6 address at which this host "
"can be reached from the public internet (or internal network if it will never "
"need to be reached from the internet).~n"
" DO NOT INCLUDE A PORT NUMBER IN THIS STEP~n".
-spec parse_address(string()) -> inet:hostname() | inet:ip_address().
parse_address(String) ->
case inet:parse_address(String) of
{ok, Address} -> Address;
{error, einval} -> String
end.
-spec create_realm(ZompConf, Realm, ExAddress) -> no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}],
Realm :: realm(),
ExAddress :: inet:hostname() | inet:ip_address().
create_realm(ZompConf, Realm, ExAddress) ->
Current =
case lists:keyfind(external_port, 1, ZompConf) of
false -> 11311;
{external_port, none} -> 11311;
{external_port, P} -> P
end,
Message =
"~n"
" Enter the public (external) port number at which this service should be "
"available. (This might be different from the local port number if you are "
"forwarding ports or have a complex network layout.)~n",
ok = io:format(Message),
ExPort = prompt_port_number(Current),
create_realm(ZompConf, Realm, ExAddress, ExPort).
-spec create_realm(ZompConf, Realm, ExAddress, ExPort) -> no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}],
Realm :: realm(),
ExAddress :: inet:hostname() | inet:ip_address(),
ExPort :: inet:port_number().
create_realm(ZompConf, Realm, ExAddress, ExPort) ->
Current =
case lists:keyfind(internal_port, 1, ZompConf) of
false -> 11311;
{internal_port, none} -> 11311;
{internal_port, P} -> P
end,
Message =
"~n"
" Enter the local (internal/LAN) port number at which this service should be "
"available. (This might be different from the public port visible from the internet"
"if you are port forwarding or have a complex network layout.)~n",
ok = io:format(Message),
InPort = prompt_port_number(Current),
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort).
-spec prompt_port_number(Current) -> Result
when Current :: inet:port_number(),
Result :: inet:port_number().
prompt_port_number(Current) ->
Instructions =
" A valid port is any number from 1 to 65535."
" [Press enter to accept the current setting: ~tw]~n",
ok = io:format(Instructions, [Current]),
case get_input() of
"" ->
Current;
S ->
try
case list_to_integer(S) of
Port when 16#ffff >= Port, Port > 0 ->
Port;
Illegal ->
Whoops = "Whoops! ~tw is out of bounds (1~65535). Try again...~n",
ok = io:format(Whoops, [Illegal]),
prompt_port_number(Current)
end
catch error:badarg ->
ok = io:format("~tp is not a port number. Try again...", [S]),
prompt_port_number(Current)
end
end.
-spec create_realm(ZompConf, Realm, ExAddress, ExPort, InPort) -> no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}],
Realm :: realm(),
ExAddress :: inet:hostname() | inet:ip_address(),
ExPort :: inet:port_number(),
InPort :: inet:port_number().
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort) ->
Instructions =
"~n"
" Enter a username for the realm sysop.~n"
" Names can contain only lower-case letters, numbers and the underscore.~n"
" Names must begin with a lower-case letter.~n",
ok = io:format(Instructions),
UserName = get_input(),
case valid_lower0_9(UserName) of
true ->
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName);
false ->
ok = io:format("Bad username ~tp. Try again.~n", [UserName]),
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort)
end.
-spec create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName) -> no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}],
Realm :: realm(),
ExAddress :: inet:hostname() | inet:ip_address(),
ExPort :: inet:port_number(),
InPort :: inet:port_number(),
UserName :: string().
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName) ->
Instructions =
"~n"
" Enter an email address for the realm sysop.~n"
" Valid email address rules apply though the checking done here is quite "
"minimal. Check the address you enter carefully. The only people who will "
"suffer from an invalid address are your users.~n",
ok = io:format(Instructions),
Email = get_input(),
[User, Host] = string:lexemes(Email, "@"),
case {valid_lower0_9(User), valid_label(Host)} of
{true, true} ->
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName, Email);
{false, true} ->
Message = "The user part of the email address seems invalid. Try again.~n",
ok = io:format(Message),
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName);
{true, false} ->
Message = "The host part of the email address seems invalid. Try again.~n",
ok = io:format(Message),
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName);
{false, false} ->
Message = "This email address seems like its totally bonkers. Try again.~n",
ok = io:format(Message),
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName)
end.
-spec create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName, Email) ->
no_return()
when ZompConf :: [{Key :: atom(), Value :: term()}],
Realm :: realm(),
ExAddress :: inet:hostname() | inet:ip_address(),
ExPort :: inet:port_number(),
InPort :: inet:port_number(),
UserName :: string(),
Email :: string().
create_realm(ZompConf, Realm, ExAddress, ExPort, InPort, UserName, Email) ->
Instructions =
"~n"
" Enter the real name (or whatever name people recognize) for the sysop.~n"
" There are no rules for this one. Any valid UTF-8 printables are legal.~n",
ok = io:format(Instructions),
RealName = get_input(),
ok = io:format("~nGenerating keys. This might take a while, so settle in...~n"),
{ok, RealmKey, RealmPub} = generate_rsa({Realm, Realm ++ ".1.realm"}),
{ok, PackageKey, PackagePub} = generate_rsa({Realm, Realm ++ ".1.package"}),
{ok, SysopKey, SysopPub} = generate_rsa({Realm, UserName ++ ".1"}),
AllKeys = [RealmKey, RealmPub, PackageKey, PackagePub, SysopKey, SysopPub],
DangerousKeys = [PackageKey, SysopKey],
Copy =
fun(From) ->
To = filename:basename(From),
case filelib:is_file(To) of
true ->
M = "Whoops! Keyfile local destination ~tp exists! Aborting",
ok = log(error, M, [To]),
ok = log(info, "Undoing all changes..."),
ok = lists:foreach(fun file:delete/1, AllKeys),
halt(0);
false ->
{ok, _} = file:copy(From, To),
log(info, "Copying to local directory: ~ts", [From])
end
end,
Drop =
fun(File) ->
ok = file:delete(File),
log(info, "Deleting ~ts", [File])
end,
ok = lists:foreach(Copy, AllKeys),
ok = lists:foreach(Drop, DangerousKeys),
Timestamp = calendar:now_to_universal_time(erlang:timestamp()),
{ok, RealmPubData} = file:read_file(RealmPub),
RealmPubRecord =
{{Realm, filename:basename(RealmPub)},
realm,
{realm, Realm},
crypto:hash(sha512, RealmPubData),
Timestamp},
{ok, PackagePubData} = file:read_file(PackagePub),
PackagePubRecord =
{{Realm, filename:basename(PackagePub)},
package,
{realm, Realm},
crypto:hash(sha512, PackagePubData),
Timestamp},
Message =
"~n"
" All of the keys generated have been moved to the current directory.~n"
"~n"
" MAKE AND SECURELY STORE COPIES OF THESE KEYS.~n"
"~n"
" The private package and sysop login keys have been deleted from the "
"key directory. These should only exist on your local system, not a prime "
"realm server (particularly if other services are run on that machine).~n"
" The package and sysop keys will need to be copied to the ~~/.zomp/keys/~s/~n"
" directory on your personal or dev machine.~n",
ok = io:format(Message, [Realm]),
UserRecord = {{UserName, Realm}, [SysopPub], Email, RealName, 1, Timestamp},
RealmFile = filename:join(zomp_dir(), Realm ++ ".realm"),
RealmMeta =
[{realm, Realm},
{revision, 0},
{prime, {ExAddress, ExPort}},
{private, []},
{mirrors, []},
{sysops, [UserRecord]},
{realm_keys, [RealmPubRecord]},
{package_keys, [PackagePubRecord]}],
Realms =
case lists:keyfind(managed, 1, ZompConf) of
{managed, M} -> [Realm | M];
false -> [Realm]
end,
ZompFile = filename:join(zomp_dir(), "zomp.conf"),
Update = fun({K, V}, ZC) -> lists:keystore(K, 1, ZC, {K, V}) end,
NewConf =
[{managed, Realms},
{external_address, ExAddress},
{external_port, ExPort},
{internal_port, InPort}],
NewZompConf = lists:foldl(Update, ZompConf, NewConf),
ok = write_terms(RealmFile, RealmMeta),
ok = write_terms(ZompFile, NewZompConf),
ok = log(info, "Realm ~ts created.", [Realm]),
halt(0).
-spec create_sysop() -> no_return().
create_sysop() ->
ok = log(info, "Fo' realz, yo! We be sysoppin up in hurr!"),
halt(0).
%%% Network operations and package utilities
-spec install(package_id()) -> ok.
%% @private
%% Install a package from the cache into the local system.
install(PackageID) ->
PackageString = package_string(PackageID),
ok = log(info, "Installing ~ts", [PackageString]),
ZrpFile = filename:join("zrp", namify_zrp(PackageID)),
Files = extract_zrp(ZrpFile),
TgzFile = namify_tgz(PackageID),
{TgzFile, TgzData} = lists:keyfind(TgzFile, 1, Files),
{"zomp.meta", MetaBin} = lists:keyfind("zomp.meta", 1, Files),
Meta = binary_to_term(MetaBin),
{sig, {KeyID, Signature}} = lists:keyfind(sig, 1, Meta),
{ok, PubKey} = loadkey(public, KeyID),
ok = ensure_package_dirs(PackageID),
PackageDir = filename:join("lib", PackageString),
ok = force_dir(PackageDir),
ok = verify(TgzData, Signature, PubKey),
ok = erl_tar:extract({binary, TgzData}, [compressed, {cwd, PackageDir}]),
log(info, "~ts installed", [PackageString]).
-spec extract_zrp(FileName) -> Files | no_return()
when FileName :: file:filename(),
Files :: [{file:filename(), binary()}].
%% @private
%% Extract a zrp archive, if possible. If not possible, halt execution with as accurate
%% an error message as can be managed.
extract_zrp(FileName) ->
case erl_tar:extract(FileName, [memory]) of
{ok, Files} ->
Files;
{error, {FileName, enoent}} ->
Message = "Can't find file ~ts.",
error_exit(Message, [FileName], ?FILE, ?LINE);
{error, invalid_tar_checksum} ->
Message = "~ts is not a valid zrp archive.",
error_exit(Message, [FileName], ?FILE, ?LINE);
{error, Reason} ->
Message = "Extracting package file failed with: ~tp.",
error_exit(Message, [Reason], ?FILE, ?LINE)
end.
-spec verify(Data, Signature, PubKey) -> ok | no_return()
when Data :: binary(),
Signature :: binary(),
PubKey :: public_key:rsa_public_key().
%% @private
%% Verify the RSA Signature of some Data against the given PubKey or halt execution.
%% This function always assumes sha512 is the algorithm being used.
verify(Data, Signature, PubKey) ->
case public_key:verify(Data, sha512, Signature, PubKey) of
true -> ok;
false -> error_exit("Bad package signature!", ?FILE, ?LINE)
end.
-spec fetch(Socket, PackageID) -> Result
when Socket :: gen_tcp:socket(),
PackageID :: package_id(),
Result :: ok.
%% @private
%% Download a package to the local cache.
fetch(Socket, PackageID) ->
{ok, LatestID} = request_zrp(Socket, PackageID),
ok = receive_zrp(Socket, LatestID),
log(info, "Fetched ~ts", [package_string(LatestID)]).
request_zrp(Socket, PackageID) ->
ok = send(Socket, {fetch, PackageID}),
receive
{tcp, Socket, Bin} ->
case binary_to_term(Bin) of
{sending, LatestID} ->
{ok, LatestID};
Error = {error, Reason} ->
PackageString = package_string(PackageID),
Message = "Error receiving package ~ts: ~tp",
ok = log(info, Message, [PackageString, Reason]),
Error
end
after 60000 ->
{error, timeout}
end.
receive_zrp(Socket, PackageID) ->
receive
{tcp, Socket, Bin} ->
ZrpPath = filename:join("zrp", namify_zrp(PackageID)),
ok = file:write_file(ZrpPath, Bin),
ok = send(Socket, ok),
log(info, "Wrote ~ts", [ZrpPath])
after 60000 ->
ok = log(error, "Timeout in socket receive for ~tp", [PackageID]),
{error, timeout}
end.
%%% Utility functions
-spec read_meta() -> package_meta() | no_return().
%% @private
%% @equiv read_meta(".")
read_meta() ->
read_meta(".").
-spec read_meta(Dir) -> package_meta() | no_return()
when Dir :: file:filename().
%% @private
%% Read the `zomp.meta' file from the indicated directory, if possible. If not possible
%% then halt execution with an appropriate error message.
read_meta(Dir) ->
Path = filename:join(Dir, "zomp.meta"),
case file:consult(Path) of
{ok, Meta} ->
maps:from_list(Meta);
Error ->
ok = log(error, "Failed to open \"zomp.meta\" with ~tp", [Error]),
ok = log(error, "Wrong directory?"),
halt(1)
end.
-spec write_meta(package_meta()) -> ok.
%% @private
%% @equiv write_meta(".")
write_meta(Meta) ->
write_meta(".", Meta).
-spec write_meta(Dir, Meta) -> ok
when Dir :: file:filename(),
Meta :: package_meta().
%% @private
%% Write the contents of the provided meta structure (a map these days) as a list of
%% Erlang K/V terms.
write_meta(Dir, Meta) ->
Path = filename:join(Dir, "zomp.meta"),
ok = write_terms(Path, maps:to_list(Meta)).
-spec write_terms(Filename, Terms) -> ok
when Filename :: file:filename(),
Terms :: [term()].
%% @private
%% Provides functionality roughly inverse to file:consult/1.
write_terms(Filename, List) ->
Format = fun(Term) -> io_lib:format("~tp.~n", [Term]) end,
Text = lists:map(Format, List),
file:write_file(Filename, Text).
-spec build(package_id()) -> ok.
%% @private
%% Given an AppID, build the project from source and add it to the current lib path.
build(PackageID) ->
{ok, CWD} = file:get_cwd(),
ok = file:set_cwd(package_home(PackageID)),
ok = build(),
file:set_cwd(CWD).
-spec build() -> ok.
%% @private
%% Run any local `zxmake' script needed by the project for non-Erlang code (if present),
%% then add the local `ebin/' directory to the runtime search path, and finally build
%% the Erlang part of the project with make:all/0 according to the local `Emakefile'.
build() ->
ZxMake = "zxmake",
ok =
case filelib:is_regular(ZxMake) of
true ->
Out = os:cmd(ZxMake),
log(info, Out);
false ->
ok
end,
true = code:add_patha(filename:absname("ebin")),
up_to_date = make:all(),
ok.
-spec scrub(Deps) -> Scrubbed
when Deps :: [package_id()],
Scrubbed :: [package_id()].
%% @private
%% Take a list of dependencies and return a list of dependencies that are not yet
%% installed on the system.
scrub([]) ->
[];
scrub(Deps) ->
lists:filter(fun(PackageID) -> not installed(PackageID) end, Deps).
-spec installed(package_id()) -> boolean().
%% @private
%% True to its name, returns `true' if the package is installed (its directory found),
%% `false' otherwise.
installed(PackageID) ->
PackageString = package_string(PackageID),
PackageDir = filename:join("lib", PackageString),
filelib:is_dir(PackageDir).
%%% Input argument mangling
-spec valid_lower0_9(string()) -> boolean().
%% @private
%% Check whether a provided string is a valid lower0_9.
valid_lower0_9([Char | Rest])
when $a =< Char, Char =< $z ->
valid_lower0_9(Rest, Char);
valid_lower0_9(_) ->
false.
-spec valid_lower0_9(String, Last) -> boolean()
when String :: string(),
Last :: char().
valid_lower0_9([$_ | _], $_) ->
false;
valid_lower0_9([Char | Rest], _)
when $a =< Char, Char =< $z;
$0 =< Char, Char =< $9;
Char == $_ ->
valid_lower0_9(Rest, Char);
valid_lower0_9([], _) ->
true;
valid_lower0_9(_, _) ->
false.
-spec valid_label(string()) -> boolean().
%% @private
%% Check whether a provided string is a valid label.
valid_label([Char | Rest])
when $a =< Char, Char =< $z ->
valid_label(Rest, Char);
valid_label(_) ->
false.
-spec valid_label(String, Last) -> boolean()
when String :: string(),
Last :: char().
valid_label([$. | _], $.) ->
false;
valid_label([$_ | _], $_) ->
false;
valid_label([$- | _], $-) ->
false;
valid_label([Char | Rest], _)
when $a =< Char, Char =< $z;
$0 =< Char, Char =< $9;
Char == $_; Char == $-;
Char == $. ->
valid_label(Rest, Char);
valid_label([], _) ->
true;
valid_label(_, _) ->
false.
-spec string_to_version(string()) -> version().
%% @private
%% @equiv string_to_version(string(), "", {z, z, z})
string_to_version(String) ->
string_to_version(String, "", {z, z, z}).
-spec string_to_version(String, Acc, Version) -> Result
when String :: string(),
Acc :: list(),
Version :: version(),
Result :: version().
%% @private
%% Accepts a full or partial version string of the form `X.Y.Z', `X.Y' or `X' and
%% returns a zomp-type version tuple or crashes on bad data.
string_to_version([Char | Rest], Acc, Version) when $0 =< Char andalso Char =< $9 ->
string_to_version(Rest, [Char | Acc], Version);
string_to_version([$. | Rest], Acc, {z, z, z}) ->
X = list_to_integer(lists:reverse(Acc)),
string_to_version(Rest, "", {X, z, z});
string_to_version([$. | Rest], Acc, {X, z, z}) ->
Y = list_to_integer(lists:reverse(Acc)),
string_to_version(Rest, "", {X, Y, z});
string_to_version("", "", Version) ->
Version;
string_to_version([], Acc, {z, z, z}) ->
X = list_to_integer(lists:reverse(Acc)),
{X, z, z};
string_to_version([], Acc, {X, z, z}) ->
Y = list_to_integer(lists:reverse(Acc)),
{X, Y, z};
string_to_version([], Acc, {X, Y, z}) ->
Z = list_to_integer(lists:reverse(Acc)),
{X, Y, Z}.
-spec version_to_string(version()) -> string().
%% @private
%% Inverse of string_to_version/3.
version_to_string({z, z, z}) ->
"";
version_to_string({X, z, z}) ->
integer_to_list(X);
version_to_string({X, Y, z}) ->
lists:flatten(lists:join($., [integer_to_list(Element) || Element <- [X, Y]]));
version_to_string({X, Y, Z}) ->
lists:flatten(lists:join($., [integer_to_list(Element) || Element <- [X, Y, Z]])).
-spec package_id(string()) -> package_id().
%% @private
%% Converts a proper package_string to a package_id().
%% This function takes into account missing version elements.
%% Examples:
%% `{"foo", "bar", {1, 2, 3}} = package_id("foo-bar-1.2.3")'
%% `{"foo", "bar", {1, 2, z}} = package_id("foo-bar-1.2")'
%% `{"foo", "bar", {1, z, z}} = package_id("foo-bar-1")'
%% `{"foo", "bar", {z, z, z}} = package_id("foo-bar")'
package_id(String) ->
case string:lexemes(String, [$-]) of
[Realm, Name, VersionString] ->
true = valid_lower0_9(Realm),
true = valid_lower0_9(Name),
Version = string_to_version(VersionString),
{Realm, Name, Version};
[A, B] ->
true = valid_lower0_9(A),
case valid_lower0_9(B) of
true -> {A, B, {z, z, z}};
false -> {"otpr", A, string_to_version(B)}
end;
[Name] ->
true = valid_lower0_9(Name),
{"otpr", Name, {z, z, z}}
end.
-spec package_string(package_id()) -> string().
%% @private
%% Map an PackageID to a correct string representation.
%% This function takes into account missing version elements.
%% Examples:
%% `"foo-bar-1.2.3" = package_string({"foo", "bar", {1, 2, 3}})'
%% `"foo-bar-1.2" = package_string({"foo", "bar", {1, 2, z}})'
%% `"foo-bar-1" = package_string({"foo", "bar", {1, z, z}})'
%% `"foo-bar" = package_string({"foo", "bar", {z, z, z}})'
package_string({Realm, Name, {z, z, z}}) ->
lists:flatten(lists:join($-, [Realm, Name]));
package_string({Realm, Name, Version}) ->
VersionString = version_to_string(Version),
lists:flatten(lists:join($-, [Realm, Name, VersionString])).
-spec namify_zrp(PackageID) -> ZrpFileName
when PackageID :: package_id(),
ZrpFileName :: file:filename().
%% @private
%% Map an PackageID to its correct .zrp package file name.
namify_zrp(PackageID) -> namify(PackageID, "zrp").
-spec namify_tgz(PackageID) -> TgzFileName
when PackageID :: package_id(),
TgzFileName :: file:filename().
%% @private
%% Map an PackageID to its correct gzipped tarball source bundle filename.
namify_tgz(PackageID) -> namify(PackageID, "tgz").
-spec namify(PackageID, Suffix) -> FileName
when PackageID :: package_id(),
Suffix :: string(),
FileName :: file:filename().
%% @private
%% Converts an PackageID to a canonical string, then appends the provided
%% filename Suffix.
namify(PackageID, Suffix) ->
PackageString = package_string(PackageID),
PackageString ++ "." ++ Suffix.
%%% User menu interface (terminal)
-spec get_input() -> string().
%% @private
%% Provide a standard input prompt and newline sanitized return value.
get_input() ->
string:trim(io:get_line("(^C to quit): ")).
-spec select(Options) -> Selected
when Options :: [option()],
Selected :: term().
%% @private
%% Take a list of Options to present the user, then return the indicated option to the
%% caller once the user selects something.
select(Options) ->
Max = show(Options),
case pick(string:to_integer(io:get_line("(or ^C to quit)~n ? ")), Max) of
error ->
ok = hurr(),
select(Options);
I ->
{_, Value} = lists:nth(I, Options),
Value
end.
-spec select_string(Strings) -> Selected
when Strings :: [string()],
Selected :: string().
%% @private
%% @equiv select([{S, S} || S <- Strings])
select_string(Strings) ->
select([{S, S} || S <- Strings]).
-spec show(Options) -> Index
when Options :: [option()],
Index :: pos_integer().
%% @private
%% @equiv show(Options, 0).
show(Options) ->
show(Options, 0).
-spec show(Options, Index) -> Count
when Options :: [option()],
Index :: non_neg_integer(),
Count :: pos_integer().
%% @private
%% Display the list of options needed to the user, and return the option total count.
show([], I) ->
I;
show([{Label, _} | Rest], I) ->
Z = I + 1,
ok = io:format(" ~2w - ~ts~n", [Z, Label]),
show(Rest, Z).
-spec pick({Selection, term()}, Max) -> Result
when Selection :: error | integer(),
Max :: pos_integer(),
Result :: pos_integer() | error.
%% @private
%% Interpret a user's selection returning either a valid selection index or `error'.
pick({error, _}, _) -> error;
pick({I, _}, Max) when 0 < I, I =< Max -> I;
pick(_, _) -> error.
-spec hurr() -> ok.
%% @private
%% Present an appropriate response when the user derps on selection.
hurr() -> io:format("That isn't an option.~n").
%%% Directory & File Management
-spec ensure_zomp_home() -> ok.
%% @private
%% Ensure the zomp home directory exists and is populated.
%% Every entry function should run this initially.
ensure_zomp_home() ->
ZompDir = zomp_dir(),
case filelib:is_dir(ZompDir) of
true ->
ok;
false ->
{ok, CWD} = file:get_cwd(),
force_dir(ZompDir),
ok = file:set_cwd(ZompDir),
SubDirs = ["tmp", "key", "var", "lib", "zrp", "etc"],
ok = lists:foreach(fun file:make_dir/1, SubDirs),
ok = write_terms(default_realm_file(), default_realm()),
ok = write_terms("zomp.conf", default_conf()),
ok = file:write_file(default_pubkey_file(), default_pubkey()),
ok = log(info, "Zomp userland directory initialized."),
file:set_cwd(CWD)
end.
-spec zomp_dir() -> file:filename().
%% @private
%% Check the host OS and return the absolute path to the zomp filesystem root.
zomp_dir() ->
case os:type() of
{unix, _} ->
Home = os:getenv("HOME"),
Dir = ".zomp",
filename:join(Home, Dir);
{win32, _} ->
Drive = os:getenv("HOMEDRIVE"),
Path = os:getenv("HOMEPATH"),
Dir = "zomp",
filename:join([Drive, Path, Dir])
end.
-spec ensure_package_dirs(package_id()) -> ok.
%% @private
%% Procedure to guarantee that directory locations necessary for the indicated app to
%% run have been created or halt execution.
ensure_package_dirs(PackageID) ->
PackageHome = package_home(PackageID),
PackageData = package_dir("var", PackageID),
PackageConf = package_dir("etc", PackageID),
Dirs = [PackageHome, PackageData, PackageConf],
ok = lists:foreach(fun force_dir/1, Dirs),
log(info, "Created dirs:~n\t~ts~n\t~ts~n\t~ts", Dirs).
-spec package_home(PackageID) -> PackageHome
when PackageID :: package_id(),
PackageHome :: file:filename().
%% @private
%% Accept an PackageID and return the installation directory for the indicated
%% application.
%% NOTE:
%% This system does NOT anticipate symlinks of incomplete versions to their latest
%% installed version (for example, an incomplete `{1, 2, z}' resolving to a symlink
%% `lib/foo-bar-1.2' which is always updated to point to the latest version 1.2.x).
package_home(PackageID) ->
filename:join([zomp_dir(), "lib", package_string(PackageID)]).
-spec package_dir(Prefix, PackageID) -> PackageDataDir
when Prefix :: string(),
PackageID :: package_id(),
PackageDataDir :: file:filename().
%% @private
%% Create an absolute path to an application directory prefixed by the inclued argument.
package_dir(Prefix, {Realm, Name, _}) ->
PackageName = Realm ++ "-" ++ Name,
filename:join([zomp_dir(), Prefix, PackageName]).
-spec force_dir(Path) -> Result
when Path :: file:filename(),
Result :: ok
| {error, file:posix()}.
%% @private
%% Guarantee a directory path is created if it is possible to create or if it already
%% exists.
force_dir(Path) ->
case filelib:is_dir(Path) of
true -> ok;
false -> filelib:ensure_dir(filename:join(Path, "foo"))
end.
%%% Persistent Zomp State
%%%
%%% The following functions maintain constants or very light convenience functions
%%% that make use of system-wide constants such as the default realm name, default
%%% public key, and other data necessary to bootstrap the system.
-spec default_realm_file() -> RealmFileName
when RealmFileName :: file:filename().
%% @private
%% Return the base filename of the default realm file.
default_realm_file() ->
realm_file(default_realm_name()).
-spec default_realm_name() -> Name
when Name :: string().
%% @private
%% Return the name of the default realm.
default_realm_name() ->
"otpr".
-spec realm_file(Realm) -> RealmFileName
when Realm :: string(),
RealmFileName :: file:filename().
%% @private
%% Take a realm name, and return the name of the realm filename that would result.
realm_file(Realm) ->
Realm ++ ".realm".
-spec default_realm() -> [{Key :: atom(), Value :: term()}].
%% @private
%% Returns the default realm file's data contents for the default "otpr" realm.
default_realm() ->
[{realm, "otpr"},
{revision, 0},
{prime, {"repo.psychobitch.party", 11311}},
{private, [{"localhost", 11311}]},
{mirrors, []},
{sysops, [{"otpr, ""zxq9"}]},
{realm_keys, []},
{package_keys, [default_pubkey_file()]}].
-spec default_conf() -> [{Key :: atom(), Value :: term()}].
%% @private
%% Return the default local config values for a zomp server.
%% The external and local port values are global values needed to make a zomp server
%% work in the face of unique port forwarding and NAT configurations outside the control
%% of the zomp server itself. zx references these values in a few places (namely when
%% setting up a mirror or prime realm).
default_conf() ->
[{external_port, 11311},
{local_port, 11311}].
-spec default_pubkey_file() -> file:filename().
%% @private
%% Returns the default filename of the default public key.
default_pubkey_file() ->
"key/otpr.1.pub.der".
-spec default_pubkey() -> binary().
%% @private
%% This function stores the binary contents of the default public key in DER format.
%% Doing this in a function is essentially like using a herefile in Bash.
default_pubkey() ->
<<1170526623609313331798826318972097080557896621948083159586373016346811570540623523814426011993490293167510658875163780852129579343891111576406428675491227868125570029553836721253582239727832008666977889522526670373902361492830918639140761847180559556687253204307494936306069307171528877400209962142787058308740221939755312361860413975531508150223291108422638532792576263104963638096818852870688582998502102536693308795214193253585166432265144396969870581676155216529809785753049835842318198805379857414606363727445230640910295705259948273015496668069952400995675937310182784823621435512613227257682702758407858036197683634666558131083559654726498186745235163628111760825026969986395769481087197994986427088838210048234736434112178729013032345213637282290815839027637504309538687095441687636356524193476275012030156571775013858217400602512194340193440681965829477411264954556799403863486012736713903706193506878410947578154040532592626008808497608835124296529017804159705286317715644155305350224257244260965453649874471033452253082499940845996170964558413968751507443986189697350023010630553524737002017543233621194508406455743465763341654345366274867913624544034721065244860576536017333528275040881674913063184272153529110886460286503455305330851192409414251325951739930514383412398798397169143552351929225078321776410580550088942920371869276662363003778677125037156672547734001647521245835866935294771855501141038223226549689862909953059166203977747766244019902323008152684587630882351278639697258019126733864910210128726118293540255959256597047563483255422642476502931615170150279457262340283463240052013184396583425577647694479205638188304711342708918448926127873312263215725459445847837288305565332375343953499300740443134048756072889091269830410360478466021318806219775513929766205963920179119585525683940978348051934951531003108279739296413836014878110298764281501544267131870022937730804080147990914120458451989661878314958524775077357936603530507381414681306510832486998678859256113064859502255575935373463709491675650991615474781558091560988205268798622776917923800097513069754689850980381850490662482961403587126912566501355644996590916922352735199214989138312856189875740424585814665007172318472691695957369820456341466786796592662135451831988129143024570641715114511174217352536557906484463741194647291182294337994718316817204867347695280457082728945911284833182013377663664430399865622471148347081767689841618546822415385957879982189694968028649835009229433349600455509536803831313830531746047425571328569634168722980491088303167148354034563578494773467308480373559768673286318322053544821433023042519594934353482721862948302631174310147010936830502360070216922584309962755494775082047690911998699570511078636376582952731884810583686700059291779239354983531555181641890341326596564548265142534064300496297926337825631921898202540803202984034394784105085299461195927463845508809485122164029528839799785844442443320039670416946533059409608926282019699119974258605650707621139750878861541251137000244133051922824004103328765954846809123299108643057388278106591988288588948726535195014652816533709432709443954841948958140326831643843906635067011302827793775757370405519240285135798743643797930642236731316466261629711900502696653563418054590076289653489719291121150266002099855392711464520928906433276097459061937053797457493166175864841786220404163949123451204756345296224150348843428777300804284267552332261715309580834396983346300530128191498649494481252342446265281499938013011901846865327797551832040198638001834019915656624142453248674154025598865589700532971711073725385563400552303085348956272116643141577079495146481883784661063082399836741351657205056526803513667042134368197760702297797779121467458147679998609606364108573808591354056588770173469993932525100580531597375569598234130308636537517111449993369547954653263045866310538500083896993112212303722148462970005994202673301481606806414256044693412925931019110552827804892050433228331280670562421203245853375417503339200768693046544396231856765919093252078432727627221414636522639011044239359484661269388619025699989119275623338551483041590123908337000853294371085777425084159087803966041644743349623092361390058115563570787103198976595362533473421958104661160820266906203090829648646902638295050336316799572281472144754384682003756790117478811155220025535420078485563985223415989335480370251115982845339833011445261624828025843177973576483738938303080242315615333593789609241843889852679993907685041671938947639167721054076202421174520920916996533102606039402530751673420224664619445635819542316713250359524898015718931583729548373297621243023115983588963506710418076848806241677618452223292483533560902680339825696167663170302616711331313490757011906928728140010004845723770802553281761773606296962670294026670439797097955228790673139658966545527614535446680187443733681726438681960897106751213102099950826404109307953852794370653372653043187474529370340385390651752792530497659674388660225:16496>>.
%%% Usage
-spec usage_exit(Code) -> no_return()
when Code :: integer().
%% @private
%% A convenience function that will display the zx usage message before halting
%% with the provided exit code.
usage_exit(Code) ->
ok = usage(),
halt(Code).
-spec usage() -> ok.
%% @private
%% Display the zx command line usage message.
usage() ->
T = "~n"
"zx~n"
"~n"
"Usage:~n"
" zx help~n"
" zx run~n"
" zx run PackageID [Args]~n"
" zx init Type PackageID~n"
" zx install PackageID~n"
" zx set dep PackageID~n"
" zx set version Version~n"
" zx drop dep PackageID~n"
" zx drop key Realm KeyName~n"
" zx verup Level~n"
" zx runlocal [Args]~n"
" zx package [Path]~n"
" zx submit Path~n"
" zx create keypair~n"
" zx create plt~n"
" zx create realm~n"
" zx create sysop~n"
"~n"
"Where~n"
" PackageID :: A string of the form Realm-Name[-Version]~n"
" Args :: Arguments to pass to the application~n"
" Type :: The project type: a standalone \"app\" or a \"lib\"~n"
" Version :: Version string X, X.Y, or X.Y.Z: \"1\", \"1.2\", \"1.2.3\"~n"
" Realm :: The name of a realm as a string [:a-z:]~n"
" KeyName :: The prefix of a keypair to drop~n"
" Level :: The version level, one of \"major\", \"minor\", or \"patch\"~n"
" Path :: Path to a valid project directory or .zrp file~n"
"~n",
io:format(T).
%%% Error exits
-spec error_exit(Error, Path, Line) -> no_return()
when Error :: term(),
Path :: file:filename(),
Line :: non_neg_integer().
%% @private
%% Format an error message in a way that makes it easy to locate.
error_exit(Error, Path, Line) ->
File = filename:basename(Path),
ok = log(error, "~ts:~tp: ~tp", [File, Line, Error]),
halt(1).
-spec error_exit(Format, Args, Path, Line) -> no_return()
when Format :: string(),
Args :: [term()],
Path :: file:filename(),
Line :: non_neg_integer().
%% @private
%% Format an error message in a way that makes it easy to locate.
error_exit(Format, Args, Path, Line) ->
File = filename:basename(Path),
ok = log(error, "~ts:~tp: " ++ Format, [File, Line | Args]),
halt(1).
%%% Logger
-spec log(Level, Format) -> ok
when Level :: info
| warning
| error,
Format :: string().
%% @private
%% @equiv log(Level, Format, [])
log(Level, Format) ->
log(Level, Format, []).
-spec log(Level, Format, Args) -> ok
when Level :: info
| warning
| error,
Format :: string(),
Args :: [term()].
%% @private
%% A logging abstraction to hide whatever logging back end is actually in use.
%% Format must adhere to Erlang format string rules, and the arity of Args must match
%% the provided format.
log(Level, Format, Args) ->
Tag =
case Level of
info -> "[INFO]";
warning -> "[WARNING]";
error -> "[ERROR]"
end,
io:format("~p ~s: " ++ Format ++ "~n", [self(), Tag | Args]).