Service interface for additional utilities

This commit is contained in:
Craig Everett 2019-09-19 00:07:25 +09:00
parent e4b698878f
commit 40714ac5df
39 changed files with 4105 additions and 2312 deletions

View File

@ -1 +1 @@
0.1.0 0.2.0

View File

@ -1,36 +0,0 @@
-export([log/2, log/3]).
-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,
Out = io_lib:format("~s ~w ~w: " ++ Format ++ "~n", [Tag, ?MODULE, self() | Args]),
UTF8 = unicode:characters_to_binary(Out),
io:format(UTF8).

View File

@ -1,598 +0,0 @@
%%% @doc
%%% ZX Auth
%%%
%%% This module is where all the AUTH type command code lives. AUTH commands are special
%%% because they do not involve the zx_daemon at all, though they do perform network
%%% operations.
%%%
%%% All AUTH procedures terminate the runtime once complete.
%%% @end
-module(zx_auth).
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([list_pending/1, list_approved/1,
submit/1, review/1, approve/1, reject/1, accept/1,
list_users/1, list_packagers/1, list_maintainers/1, list_sysops/1,
add_user/1,
add_packager/2, rem_packager/2,
add_maintainer/2, rem_maintainer/2,
add_sysop/1,
add_package/1]).
-include("zx_logger.hrl").
%%% Functions
-spec list_pending(PackageName :: string()) -> zx:outcome().
%% @private
%% List the versions of a package that are pending review. The package name is input by
%% the user as a string of the form "otpr-zomp" and the output is a list of full
%% package IDs, printed one per line to stdout (like "otpr-zomp-3.2.2").
list_pending(PackageName) ->
case zx_lib:package_id(PackageName) of
{ok, {Realm, Name, {z, z, z}}} -> list_pending2(Realm, Name);
Error -> Error
end.
list_pending2(Realm, Name) ->
case connect(Realm) of
{ok, Socket} -> list_pending3(Realm, Name, Socket);
Error -> Error
end.
list_pending3(Realm, Name, Socket) ->
Message = <<"ZOMP AUTH 1:", 0:24, 5:8, (term_to_binary({Realm, Name}))/binary>>,
ok = gen_tcp:send(Socket, Message),
receive
{tcp, Socket, <<0:8, Bin/binary>>} -> list_pending4(Realm, Name, Socket, Bin);
{tcp, Socket, Error} -> done(Socket, Error);
{tcp_closed, Socket} -> {error, "Socket closed unexpectedly."}
after 5000 -> done(Socket, timeout)
end.
list_pending4(Realm, Name, Socket, Bin) ->
ok = zx_net:disconnect(Socket),
case zx_lib:b_to_ts(Bin) of
{ok, Versions} -> list_pending5(Realm, Name, Versions);
Error -> Error
end.
list_pending5(Realm, Name, Versions) ->
Print =
fun(Version) ->
PackageID = {Realm, Name, Version},
{ok, PackageString} = zx_lib:package_string(PackageID),
io:format("~ts~n", [PackageString])
end,
lists:foreach(Print, Versions).
-spec list_approved(zx:realm()) -> zx:outcome().
%% @private
%% List the package ids of all packages waiting in the resign queue for the given realm,
%% printed to stdout one per line.
list_approved(Realm) ->
case connect(Realm) of
{ok, Socket} -> list_approved2(Realm, Socket);
Error -> Error
end.
list_approved2(Realm, Socket) ->
Message = <<"ZOMP AUTH 1:", 0:24, 7:8, (term_to_binary(Realm))/binary>>,
ok = gen_tcp:send(Socket, Message),
receive
{tcp, Socket, <<0:8, Bin/binary>>} -> list_approved3(Socket, Bin, Realm);
{tcp, Socket, Error} -> done(Socket, Error);
{tcp_closed, Socket} -> {error, "Socket closed unexpectedly."}
after 5000 -> done(Socket, timeout)
end.
list_approved3(Socket, Bin, Realm) ->
ok = zx_net:disconnect(Socket),
case zx_lib:b_to_ts(Bin) of
{ok, PackageIDs} -> list_approved4(Realm, PackageIDs);
Error -> Error
end.
list_approved4(Realm, PackageIDs) ->
Print =
fun({Name, Version}) ->
{ok, PackageString} = zx_lib:package_string({Realm, Name, Version}),
io:format("~ts~n", [PackageString])
end,
lists:foreach(Print, PackageIDs).
-spec submit(ZspPath :: file:filename()) -> zx:outcome().
%% @private
%% Submit a package to the appropriate "prime" server for the given realm.
submit(ZspPath) ->
case file:read_file(ZspPath) of
{ok, ZspBin} -> submit2(ZspBin);
Error -> Error
end.
submit2(ZspBin = <<SigSize:24, Sig:SigSize/binary, Signed/binary>>) ->
<<MetaSize:16, MetaBin:MetaSize/binary, _/binary>> = Signed,
{ok, {PackageID = {Realm, _, _}, KeyName, _, _}} = zx_lib:b_to_ts(MetaBin),
UserName = zx_local:select_user(Realm),
KeyID = {Realm, KeyName},
case zx_key:ensure_keypair(KeyID) of
true ->
{ok, PKey} = zx_key:load(public, KeyID),
{ok, DKey} = zx_key:load(private, KeyID),
case zx_key:verify(Signed, Sig, PKey) of
true -> submit3(PackageID, ZspBin, UserName, KeyName, DKey);
false -> {error, bad_sig}
end;
Error ->
Error
end.
submit3({Realm, Name, Ver}, ZspBin, UserName, KeyName, Key) ->
Payload = {Realm, UserName, KeyName, {Name, Ver}},
case connect(Realm) of
{ok, Socket} -> submit4(Socket, Payload, ZspBin, Key);
Error -> Error
end.
submit4(Socket, Payload, ZspBin, Key) ->
Command = 1,
Request = pack_and_sign(Command, Payload, Key),
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", Request/binary>>),
case zx_net:tx(Socket, ZspBin) of
ok -> done(Socket);
Error -> done(Socket, Error)
end.
-spec review(PackageString :: string()) -> zx:outcome().
review(PackageString) ->
case zx_lib:package_id(PackageString) of
{ok, PackageID} -> review2(PackageID);
Error -> Error
end.
review2(PackageID = {Realm, _, _}) ->
case connect(Realm) of
{ok, Socket} -> review3(PackageID, Socket);
Error -> Error
end.
review3(PackageID, Socket) ->
Command = 8,
TermBin = term_to_binary(PackageID),
Request = <<0:24, Command:8, TermBin/binary>>,
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", Request/binary>>),
receive
{tcp, Socket, <<0:1, 0:7>>} -> review4(PackageID, Socket);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
review4(PackageID, Socket) ->
case zx_net:rx(Socket) of
{ok, <<Size:24, Sig:Size/binary, Signed/binary>>} ->
ok = zx_net:disconnect(Socket),
review5(PackageID, Sig, Signed);
Error ->
done(Socket, Error)
end.
review5(PackageID, Sig, Signed = <<Size:16, MetaBin:Size/binary, TgzBin/binary>>) ->
case zx_lib:b_to_ts(MetaBin) of
{ok, {PackageID = {Realm, _, _}, KeyName, _, _}} ->
review6(PackageID, {Realm, KeyName}, Signed, Sig, TgzBin);
{ok, {UnexpectedID, _, _, _}} ->
{ok, Requested} = zx_lib:package_string(PackageID),
{ok, Unexpected} = zx_lib:package_string(UnexpectedID),
Message = "Requested ~ts, but inside was ~ts! Aborting.",
ok = log(warning, Message, [Requested, Unexpected]),
{error, "Wrong package received.", 29};
error ->
{error, bad_response}
end.
review6(PackageID, KeyID, Signed, Sig, TgzBin) ->
case zx_key:load(public, KeyID) of
{ok, Key} -> review7(PackageID, Key, Signed, Sig, TgzBin);
Error -> Error % TODO: Fetch unknown keys
end.
review7(PackageID, SigKey, Signed, Sig, TgzBin) ->
case zx_key:verify(Signed, Sig, SigKey) of
true -> review8(PackageID, TgzBin);
false -> {error, bad_sig}
end.
review8(PackageID, TgzBin) ->
{ok, PackageString} = zx_lib:package_string(PackageID),
case file:make_dir(PackageString) of
ok ->
review9(PackageString, TgzBin);
{error, Error} ->
Message = "Creating dir ./~ts failed with ~ts. Aborting.",
ok = log(error, Message, [PackageString, Error]),
{error, Error}
end.
review9(PackageString, TgzBin) ->
ok = erl_tar:extract({binary, TgzBin}, [compressed, {cwd, PackageString}]),
log(info, "Sources unpacked to ./~ts", [PackageString]).
approve(Package) -> package_operation(9, Package).
reject(Package) -> package_operation(10, Package).
-spec package_operation(Code :: 9 | 10, Package :: string()) -> zx:outcome().
package_operation(Code, Package) ->
case zx_lib:package_id(Package) of
{ok, {Realm, Name, Version}} -> make_su_request(Code, Realm, {Name, Version});
Error -> Error
end.
-spec accept(PackageString :: string()) -> zx:outcome().
accept(PackageString) ->
case zx_lib:package_id(PackageString) of
{ok, PackageID} -> accept2(PackageID);
Error -> Error
end.
accept2(PackageID = {Realm, Name, Version}) ->
case connect_auth(Realm) of
{ok, AuthConn} -> accept3(PackageID, {Name, Version}, AuthConn);
Error -> Error
end.
accept3(PackageID, PV, {UserName, KeyName, Key, Tag, Socket}) ->
Command = 11,
Payload = {Tag, UserName, KeyName, PV},
Request = pack_and_sign(Command, Payload, Key),
ok = gen_tcp:send(Socket, <<0:8, Request/binary>>),
ok = inet:setopts(Socket, [{active, once}]),
receive
{tcp, Socket, <<0:1, 0:7>>} -> accept4(PackageID, KeyName, Key, Socket);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
accept4(PackageID, KeyName, Key, Socket) ->
case zx_net:rx(Socket) of
{ok, <<Size:24, Sig:Size/binary, Signed/binary>>} ->
accept5(PackageID, {KeyName, Key, Socket}, Sig, Signed);
Error ->
done(Socket, Error)
end.
accept5(PackageID,
Auth,
Sig,
Signed = <<Size:16, MetaBin:Size/binary, TgzBin/binary>>) ->
case zx_lib:b_to_ts(MetaBin) of
{ok, Meta = {PackageID = {Realm, _, _}, SigKeyName, _, _}} ->
accept6(Meta, Auth, {Realm, SigKeyName}, Signed, Sig, TgzBin);
{ok, {UnexpectedID, _, _, _}} ->
{ok, Requested} = zx_lib:package_string(PackageID),
{ok, Unexpected} = zx_lib:package_string(UnexpectedID),
Message = "Requested ~ts, but inside was ~ts! Aborting.",
ok = log(warning, Message, [Requested, Unexpected]),
{error, "Wrong package received.", 29};
error ->
{error, bad_response}
end.
accept6(Meta, Auth, SigKeyID, Signed, Sig, TgzBin) ->
case zx_key:load(public, SigKeyID) of
{ok, SigKey} -> accept7(Meta, Auth, SigKey, Signed, Sig, TgzBin);
Error -> Error % TODO: Fetch unknown keys
end.
accept7(Meta, Auth, SigKey, Signed, Sig, TgzBin) ->
case zx_key:verify(Signed, Sig, SigKey) of
true -> accept8(Meta, Auth, TgzBin);
false -> {error, bad_sig}
end.
accept8({PackageID, _, Deps, Modules}, {KeyName, Key, Socket}, TgzBin) ->
MetaBin = term_to_binary({PackageID, KeyName, Deps, Modules}),
MetaSize = byte_size(MetaBin),
SignMe = <<MetaSize:16, MetaBin:MetaSize/binary, TgzBin/binary>>,
Sig = public_key:sign(SignMe, sha512, Key),
SigSize = byte_size(Sig),
ZspData = <<SigSize:24, Sig:SigSize/binary, SignMe/binary>>,
ok = zx_net:tx(Socket, ZspData),
done(Socket).
list_users(Realm) ->
list_users(2, Realm).
list_packagers(Package) ->
{ok, {Realm, Name, {z, z, z}}} = zx_lib:package_id(Package),
list_users(3, {Realm, Name}).
list_maintainers(Package) ->
{ok, {Realm, Name, {z, z, z}}} = zx_lib:package_id(Package),
list_users(4, {Realm, Name}).
list_sysops(Realm) ->
list_users(5, Realm).
-spec list_users(Command, Target) -> zx:outcome()
when Command :: 2..5,
Target :: zx:realm() | zx:package().
list_users(Command, Target) ->
case make_uu_request(Command, Target) of
{ok, Users} -> lists:foreach(fun print_user/1, Users);
Error -> Error
end.
print_user({UserName, RealName, [{"email", Email}]}) ->
io:format("~ts (~ts <~ts>) ~n", [UserName, RealName, Email]).
-spec add_user(file:filename()) -> zx:outcome().
add_user(ZPUF) ->
case file:read_file(ZPUF) of
{ok, Bin} -> add_user2(Bin);
Error -> Error
end.
add_user2(Bin) ->
case zx_lib:b_to_t(Bin) of
{ok, {UserInfo, KeyData}} ->
Realm = proplists:get_value(realm, UserInfo),
UserData = {proplists:get_value(username, UserInfo),
proplists:get_value(realname, UserInfo),
proplists:get_value(contact_info, UserInfo),
[setelement(2, KD, none) || KD <- KeyData]},
Command = 13,
make_su_request(Command, Realm, UserData);
error ->
{error, "Bad user file.", 1}
end.
add_packager(Package, User) -> user_auth_operation(15, Package, User).
rem_packager(Package, User) -> user_auth_operation(16, Package, User).
add_maintainer(Package, User) -> user_auth_operation(17, Package, User).
rem_maintainer(Package, User) -> user_auth_operation(18, Package, User).
-spec user_auth_operation(Code, Package, User)-> zx:outcome()
when Code :: 15..18,
Package :: string(),
User :: zx:user_name().
user_auth_operation(Code, Package, User) ->
case zx_lib:package_id(Package) of
{ok, {Realm, Name, {z, z, z}}} -> make_su_request(Code, Realm, {Name, User});
Error -> Error
end.
-spec add_sysop(file:filename()) -> zx:outcome().
add_sysop(UserFile) ->
ok = log(info, "Would add ~ts to sysop list.", [UserFile]),
{error, "Not yet implemented", 1}.
-spec add_package(zx:package()) -> zx:outcome().
add_package(PackageName) ->
ok = file:set_cwd(zx_lib:zomp_dir()),
case zx_lib:package_id(PackageName) of
{ok, {Realm, Name, {z, z, z}}} -> add_package2(Realm, Name);
Error -> Error
end.
add_package2(Realm, Name) ->
case connect_auth(Realm) of
{ok, AuthConn} -> add_package3(Realm, Name, AuthConn);
Error -> Error
end.
add_package3(Realm, Name, {UserName, KeyName, Key, Tag, Socket}) ->
Command = 12,
Package = {Realm, Name},
Payload = {Tag, UserName, KeyName, Package},
Request = pack_and_sign(Command, Payload, Key),
ok = gen_tcp:send(Socket, <<0:8, Request/binary>>),
done(Socket).
%%% Generic Request Forms
-spec make_uu_request(Command, Target) -> zx:outcome()
when Command :: pos_integer(),
Target :: zx:realm() | zx:package() | zx:package_id().
make_uu_request(Command, Target) when is_tuple(Target) ->
make_uu_request2(Command, element(1, Target), Target);
make_uu_request(Command, Target) when is_list(Target) ->
make_uu_request2(Command, Target, Target).
make_uu_request2(Command, Realm, Target) ->
case connect(Realm) of
{ok, Socket} -> make_uu_request3(Command, Target, Socket);
Error -> Error
end.
make_uu_request3(Command, Target, Socket) ->
TermBin = term_to_binary(Target),
Request = <<"ZOMP AUTH 1:", 0:24, Command:8, TermBin/binary>>,
ok = gen_tcp:send(Socket, Request),
ok = inet:setopts(Socket, [{active, once}]),
receive
{tcp, Socket, <<0:1, 0:7, Bin/binary>>} -> make_uu_request4(Bin);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
make_uu_request4(Bin) ->
case zx_lib:b_to_ts(Bin) of
error -> {error, bad_response};
Term -> Term
end.
-spec make_su_request(Command, Realm, Data) -> zx:outcome()
when Command :: 1 | 9 | 10 | 13..20,
Realm :: zx:realm(),
Data :: term().
make_su_request(Command, Realm, Data) ->
AuthData = prep_auth(Realm),
case connect(Realm) of
{ok, Socket} -> make_su_request2(Command, Realm, Data, AuthData, Socket);
Error -> Error
end.
make_su_request2(Command, Realm, Data, {Signatory, KeyName, Key}, Socket) ->
Payload = {Realm, Signatory, KeyName, Data},
Request = pack_and_sign(Command, Payload, Key),
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", Request/binary>>),
done(Socket).
%%% Connectiness with prime
-spec connect_auth(Realm) -> Result
when Realm :: zx:realm(),
Result :: {ok, AuthConn}
| {error, Reason},
AuthConn :: {UserName :: zx:user_name(),
KeyName :: zx:key_name(),
Key :: term(),
SSTag :: zx:ss_tag(),
Socket :: gen_tcp:socket()},
Reason :: term().
%% @private
%% Connect to one of the servers in the realm constellation.
connect_auth(Realm) ->
UserData = prep_auth(Realm),
case zx_lib:load_realm_conf(Realm) of
{ok, RealmConf} ->
connect_auth2(Realm, RealmConf, UserData);
Error ->
ok = log(error, "Realm ~160tp is not configured.", [Realm]),
Error
end.
connect_auth2(Realm, RealmConf, UserData) ->
{Host, Port} = maps:get(prime, RealmConf),
Options = [{packet, 4}, {mode, binary}, {active, once}],
case gen_tcp:connect(Host, Port, Options, 5000) of
{ok, Socket} ->
connect_auth3(Socket, Realm, UserData);
Error = {error, E} ->
ok = log(warning, "Connection problem: ~160tp", [E]),
{error, Error}
end.
connect_auth3(Socket, Realm, UD = {UserName, KeyName, Key}) ->
Null = 0,
Timestamp = calendar:universal_time(),
Payload = {Realm, Timestamp, UserName, KeyName},
NullRequest = pack_and_sign(Null, Payload, Key),
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", NullRequest/binary>>),
receive
{tcp, Socket, <<0:8, Bin/binary>>} -> connect_auth4(Socket, UD, Bin);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
connect_auth4(Socket, {UserName, KeyName, Key}, Bin) ->
case zx_lib:b_to_ts(Bin) of
{ok, Tag} -> {ok, {UserName, KeyName, Key, Tag, Socket}};
error -> done(Socket, bad_response)
end.
connect(Realm) ->
case zx_lib:load_realm_conf(Realm) of
{ok, RealmConf} ->
{Host, Port} = maps:get(prime, RealmConf),
Options = [{packet, 4}, {mode, binary}, {nodelay, true}, {active, once}],
gen_tcp:connect(Host, Port, Options, 5000);
Error ->
ok = log(error, "Realm ~160tp is not configured.", [Realm]),
Error
end.
-spec prep_auth(Realm) -> {User, KeyName, Key}
when Realm :: zx:realm(),
User :: zx:user_id(),
KeyName :: zx:key_id(),
Key :: term().
%% @private
%% Loads the appropriate User, KeyID and reads in a registered key for use in
%% connect_auth/4.
prep_auth(Realm) ->
UserName = zx_local:select_user(Realm),
KeyName = zx_local:select_private_key({Realm, UserName}),
{ok, Key} = zx_key:load(private, {Realm, KeyName}),
{UserName, KeyName, Key}.
pack_and_sign(Command, Payload, Key) ->
Bin = term_to_binary(Payload),
Signed = <<Command:8, Bin/binary>>,
Sig = public_key:sign(Signed, sha512, Key),
SSize = byte_size(Sig),
<<SSize:24, Sig/binary, Signed/binary>>.
done(Socket) ->
ok = inet:setopts(Socket, [{active, once}]),
receive
{tcp, Socket, <<0:1, 0:7>>} ->
zx_net:disconnect(Socket);
{tcp, Socket, Bin} ->
ok = zx_net:disconnect(Socket),
{error, zx_net:err_in(Bin)};
{tcp_closed, Socket} ->
{error, tcp_closed}
after 5000 ->
done(Socket, timeout)
end.
done(Socket, Reason) ->
ok = zx_net:disconnect(Socket),
case is_binary(Reason) of
true -> {error, zx_net:err_in(Reason)};
false -> {error, Reason}
end.

View File

@ -1,329 +0,0 @@
%%% @doc
%%% zx_sys_conf: An interface to etc/sys.conf
%%%
%%% It may seem overkill to write an interface module for a config file that only tracks
%%% five things, but scattering this all around the project is just a bit too l33t for
%%% an infrastructure project like ZX.
%%%
%%% Each exported function that is named after an attribute has two versions, one of
%%% arity-1 and one of arity-2. The arity-1 version is a "getter", and the arity-2
%%% version is a "setter". Other functions deal with the data in a way that returns
%%% an answer and updates the state accordingly.
%%%
%%% Bad configuration data causes a reset to defaults so that the system can function.
%%%
%%% TODO: Change this to a gen_server that just babysits the config data.
%%% @end
-module(zx_sys_conf).
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([load/0, save/1,
timeout/1, timeout/2,
retries/1, retries/2, retry/1, retries_left/1,
maxconn/1, maxconn/2,
managed/1, managed/2, add_managed/2, rem_managed/2,
mirrors/1, mirrors/2, add_mirror/2, rem_mirror/2,
reset/0]).
-export_type([data/0]).
-include("zx_logger.hrl").
%%% Type Definitions
-record(d,
{timeout = 5 :: pos_integer(),
retries = 3 :: non_neg_integer(),
maxconn = 5 :: pos_integer(),
managed = sets:new() :: sets:set(zx:realm()),
mirrors = sets:new() :: sets:set(zx:host())}).
-opaque data() :: #d{}.
%%% Interface functions
-spec load() -> data().
%% @doc
%% Read from etc/sys.conf and return a populated data() record if it exists, or
%% populate default values and write a new one if it does not. If a damaged sys.conf
%% is discovered it will be repaired. This function is side-effecty so should only
%% be called by zx_daemon and utility code.
load() ->
Path = path(),
case file:consult(Path) of
{ok, List} ->
populate_data(List);
{error, Reason} ->
ok = log(error, "Load ~160tp failed with: ~160tp", [Path, Reason]),
Data = #d{},
ok = save(Data),
Data
end.
populate_data(List) ->
Timeout =
case proplists:get_value(timeout, List, 5) of
TO when is_integer(TO) and TO > 0 -> TO;
_ -> 5
end,
Retries =
case proplists:get_value(retries, List, 3) of
RT when is_integer(RT) and RT > 0 -> RT;
_ -> 3
end,
MaxConn =
case proplists:get_value(maxconn, List, 5) of
MC when is_integer(MC) and MC > 0 -> MC;
_ -> 5
end,
Managed =
case proplists:get_value(managed, List, []) of
MN when is_list(MN) -> sets:from_list(MN);
_ -> sets:new()
end,
Mirrors =
case proplists:get_value(mirrors, List, []) of
MR when is_list(MR) -> sets:from_list(MR);
_ -> sets:new()
end,
#d{timeout = Timeout,
retries = Retries,
maxconn = MaxConn,
managed = Managed,
mirrors = Mirrors}.
-spec save(data()) -> ok.
%% @doc
%% Save the current etc/sys.conf to disk.
save(#d{timeout = Timeout,
retries = Retries,
maxconn = MaxConn,
managed = Managed,
mirrors = Mirrors}) ->
Terms =
[{timeout, Timeout},
{retries, Retries},
{maxconn, MaxConn},
{managed, sets:to_list(Managed)},
{mirrors, sets:to_list(Mirrors)}],
ok = zx_lib:write_terms(path(), Terms),
log(info, "Wrote etc/sys.conf").
-spec timeout(data()) -> pos_integer().
%% @doc
%% Return the timeout value.
timeout(#d{timeout = Timeout}) ->
Timeout.
-spec timeout(Value, Data) -> NewData
when Value :: pos_integer(),
Data :: data(),
NewData :: data().
%% @doc
%% Set the timeout attribute to a new value.
timeout(Value, Data) when Value > 0 ->
Data#d{timeout = Value}.
-spec retries(data()) -> non_neg_integer().
%% @doc
%% Return the retries value.
retries(#d{retries = Retries}) ->
Retries.
-spec retries(Value, Data) -> NewData
when Value :: non_neg_integer(),
Data :: data(),
NewData :: data().
%% @doc
%% Set the retries attribute to a new value.
retries(Value, Data) when Value > 0 ->
Data#d{retries = Value}.
-spec retry(Data) -> Result
when Data :: data(),
Result :: {ok, NewData}
| no_retries,
NewData :: data().
%% @doc
%% Tell the caller whether there are any more retries remaining or return `ok' and
%% update the state.
retry(#d{retries = {0, _}}) ->
no_retries;
retry(Data = #d{retries = {Remaining, Setting}}) ->
NewRemaining = Remaining - 1,
NewData = Data#d{retries = {NewRemaining, Setting}},
{ok, NewData}.
-spec retries_left(data()) -> non_neg_integer().
%% @doc
%% Return the number of retries remaining.
retries_left(#d{retries = {Remaining, _}}) ->
Remaining.
-spec maxconn(data()) -> pos_integer().
%% @doc
%% Return the value of maxconn.
maxconn(#d{maxconn = MaxConn}) ->
MaxConn.
-spec maxconn(Value, Data) -> NewData
when Value :: pos_integer(),
Data :: data(),
NewData :: data().
%% @doc
%% Set the value of maxconn.
maxconn(Value, Data) when is_integer(Value) and Value > 0 ->
Data#d{maxconn = Value}.
-spec managed(data()) -> [zx:realm()].
%% @doc
%% Return the list of realms managed by the current node.
managed(#d{managed = Managed}) ->
sets:to_list(Managed).
-spec managed(List, Data) -> NewData
when List :: [zx:realm()],
Data :: data(),
NewData :: data().
%% @doc
%% Reset the set of managed realms entirely.
%% The realms must be configured on the current realm at a minimum.
managed(List, Data) ->
Desired = sets:from_list(List),
Configured = sets:from_list(zx_lib:list_realms()),
NewManaged = sets:intersection(Desired, Configured),
Data#d{managed = NewManaged}.
-spec add_managed(Realm, Data) -> Result
when Realm :: zx:realm(),
Data :: data(),
Result :: {ok, NewData}
| {error, unconfigured},
NewData :: data().
%% @doc
%% Add a new realm to the list of managed realms. The new realm must be configured on
%% the current node. This node will then behave as the prime node for the realm (whether
%% it is or not).
add_managed(Realm, Data = #d{managed = Managed}) ->
case zx_lib:realm_exists(Realm) of
true ->
NewData = Data#d{managed = sets:add_element(Realm, Managed)},
ok = log(info, "Now managing realm: ~160tp", [Realm]),
{ok, NewData};
false ->
ok = log(warning, "Cannot manage unconfigured realm: ~160tp", [Realm]),
{error, unconfigured}
end.
-spec rem_managed(Realm, Data) -> Result
when Realm :: zx:realm(),
Data :: data(),
Result :: {ok, NewData}
| {error, unmanaged},
NewData :: data().
%% @doc
%% Stop managing a realm.
rem_managed(Realm, Data = #d{managed = Managed}) ->
case sets:is_element(Realm, Managed) of
true ->
NewData = Data#d{managed = sets:del_element(Realm, Managed)},
ok = log(info, "No longer managing realm: ~160tp", [Realm]),
{ok, NewData};
false ->
ok = log(warning, "Cannot stop managing unmanaged realm: ~160tp", [Realm]),
{error, unmanaged}
end.
-spec mirrors(data()) -> [zx:host()].
%% @doc
%% Return the list of private mirrors.
mirrors(#d{mirrors = Mirrors}) ->
sets:to_list(Mirrors).
-spec mirrors(Hosts, Data) -> NewData
when Hosts :: [zx:host()],
Data :: data(),
NewData :: data().
%% @private
%% Reset the mirror configuration.
mirrors(Hosts, Data) ->
Data#d{mirrors = sets:from_list(Hosts)}.
-spec add_mirror(Host, Data) -> NewData
when Host :: zx:host(),
Data :: data(),
NewData :: data().
%% @doc
%% Add a mirror to the permanent configuration.
add_mirror(Host, Data = #d{mirrors = Mirrors}) ->
Data#d{mirrors = sets:add_element(Host, Mirrors)}.
-spec rem_mirror(Host, Data) -> NewData
when Host :: zx:host(),
Data :: data(),
NewData :: data().
%% @private
%% Remove a host from the list of permanent mirrors.
rem_mirror(Host, Data = #d{mirrors = Mirrors}) ->
Data#d{mirrors = sets:del_element(Host, Mirrors)}.
-spec reset() -> data().
%% @private
%% Reset sys.conf.
reset() ->
Data = #d{},
save(Data),
Data.
-spec path() -> file:filename().
%% @private
%% Return the path to $ZOMP_DIR/etc/sys.conf.
path() ->
filename:join(zx_lib:path(etc), "sys.conf").

View File

@ -1,4 +0,0 @@
{deps,[]}.
{package_id,{"otpr","zx",{0,1,0}}}.
{prefix,"zx_"}.
{type,app}.

View File

@ -1,7 +1,8 @@
{application,zx, {application,zx,
[{description,"Zomp client program"}, [{description,"Zomp client program"},
{vsn,"0.1.0"}, {vsn,"0.2.0"},
{applications,[stdlib,kernel]}, {applications,[stdlib,kernel]},
{modules,[zx,zx_auth,zx_conn,zx_conn_sup,zx_daemon,zx_key, {modules,[zx,zx_auth,zx_conn,zx_conn_sup,zx_daemon,zx_key,
zx_lib,zx_local,zx_net,zx_sup,zx_sys_conf,zx_tty]}, zx_lib,zx_local,zx_net,zx_peer,zx_peer_man,
zx_peer_sup,zx_peers,zx_proxy,zx_sup,zx_tty,zx_zsp]},
{mod,{zx,none}}]}. {mod,{zx,none}}]}.

View File

@ -0,0 +1,63 @@
-export([log/2, tell/1, tell/2]).
-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 :: logger:level(),
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) ->
Raw = io_lib:format("~w ~w: " ++ Format, [?MODULE, self() | Args]),
Entry = unicode:characters_to_list(Raw),
logger:log(Level, Entry).
-spec tell(Message) -> ok
when Message :: string().
tell(Message) ->
tell(Message, []).
tell(Format, Args) when is_list(Format) ->
tell(info, Format, Args);
tell(Level, Message) when is_atom(Level) ->
tell(Level, Message, []).
-spec tell(Level, Format, Args) -> ok
when Level :: logger:level(),
Format :: string(),
Args :: [term()].
tell(Level, Format, Args) ->
ok = log(Level, Format, Args),
Out = io_lib:format(Format, Args),
Message = unicode:characters_to_list([Out, "~n"]),
io:format(Message).
%-spec show(Parent, Format, Args) -> ok
% when Parent :: wx:frame(),
% Format :: string(),
% Args :: [term()].
%
% TODO: Convenience log + info/error modal for WX
%
%show(Parent, Format, Args) ->

View File

@ -24,24 +24,25 @@
%%% @end %%% @end
-module(zx). -module(zx).
-vsn("0.2.0").
-behavior(application). -behavior(application).
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0"). -license("GPL-3.0").
-export([do/0, do/1]). -export([do/0]).
-export([subscribe/1, unsubscribe/0]). -export([subscribe/1, unsubscribe/0]).
-export([list/0, list/1, list/2, list/3, latest/1]).
-export([start/2, stop/1, stop/0]). -export([start/2, stop/1, stop/0]).
-export([usage_exit/1]).
-export_type([serial/0, package_id/0, package/0, realm/0, name/0, version/0, -export_type([serial/0, package_id/0, package/0, realm/0, name/0, version/0,
identifier/0, identifier/0,
host/0, host/0,
key_id/0, key_name/0, key_data/0, key_bin/0, key_id/0, key_name/0,
user_id/0, user_name/0, contact_info/0, user_data/0, user_id/0, user_name/0, contact_info/0, user_data/0,
lower0_9/0, label/0, lower0_9/0, label/0,
package_meta/0, ss_tag/0, package_meta/0, ss_tag/0, search_tag/0,
outcome/0]). outcome/0]).
-include("zx_logger.hrl"). -include("zx_logger.hrl").
@ -60,10 +61,13 @@
Patch :: non_neg_integer() | z}. Patch :: non_neg_integer() | z}.
-type host() :: {string() | inet:ip_address(), inet:port_number()}. -type host() :: {string() | inet:ip_address(), inet:port_number()}.
-type key_data() :: {Name :: key_name(), -type key_data() :: {Name :: key_name(),
Public :: none | {SHA512 :: binary(), DER :: binary()}, Public :: none | key_bin(),
Private :: none | {SHA512 :: binary(), DER :: binary()}}. Private :: none | key_bin()}.
-type key_bin() :: {Sig :: none | {key_name(), binary()},
Der :: binary()}.
-type key_id() :: {realm(), key_name()}. -type key_id() :: {realm(), key_name()}.
-type key_name() :: lower0_9(). -type key_name() :: key_hash().
-type key_hash() :: binary().
-type user_data() :: {ID :: user_id(), -type user_data() :: {ID :: user_id(),
RealName :: string(), RealName :: string(),
Contact :: [contact_info()], Contact :: [contact_info()],
@ -73,10 +77,12 @@
-type contact_info() :: {Type :: string(), Data :: string()}. -type contact_info() :: {Type :: string(), Data :: string()}.
-type lower0_9() :: [$a..$z | $0..$9 | $_]. -type lower0_9() :: [$a..$z | $0..$9 | $_].
-type label() :: [$a..$z | $0..$9 | $_ | $- | $.]. -type label() :: [$a..$z | $0..$9 | $_ | $- | $.].
-type package_meta() :: #{package_id := package_id(), -type package_meta() :: #{package_id := package_id(),
deps := [package_id()], search_tags := [search_tag()],
type := app | lib}. deps := [package_id()],
type := app | lib}.
-type ss_tag() :: {serial(), calendar:timestamp()}. -type ss_tag() :: {serial(), calendar:timestamp()}.
-type search_tag() :: string().
-type outcome() :: ok -type outcome() :: ok
| {error, Reason :: term()} | {error, Reason :: term()}
@ -91,7 +97,9 @@
do() -> do() ->
ok = io:setopts([{encoding, unicode}]), ok = io:setopts([{encoding, unicode}]),
do([]). ok = start(),
Args = init:get_plain_arguments(),
do(Args).
-spec do(Args) -> no_return() -spec do(Args) -> no_return()
@ -107,50 +115,62 @@ do(["help", "dev"]) ->
do(["help", "sysop"]) -> do(["help", "sysop"]) ->
done(help(sysop)); done(help(sysop));
do(["run", PackageString | ArgV]) -> do(["run", PackageString | ArgV]) ->
ok = start(), ok = zx_daemon:connect(),
not_done(run(PackageString, ArgV)); not_done(run(PackageString, ArgV));
do(["list", "realms"]) -> do(["list", "realms"]) ->
done(zx_local:list_realms()); done(zx_local:list_realms());
do(["list", "packages", Realm]) -> do(["list", "packages", Realm]) ->
ok = start(), ok = zx_daemon:connect(),
done(zx_local:list_packages(Realm)); done(zx_local:list_packages(Realm));
do(["list", "versions", PackageName]) -> do(["list", "versions", PackageName]) ->
ok = start(), ok = zx_daemon:connect(),
done(zx_local:list_versions(PackageName)); done(zx_local:list_versions(PackageName));
do(["latest", PackageString]) -> do(["latest", PackageString]) ->
ok = start(), ok = zx_daemon:connect(),
done(zx_local:latest(PackageString)); done(zx_local:latest(PackageString));
do(["import", "realm", RealmFile]) -> do(["import", "realm", RealmFile]) ->
done(zx_local:import_realm(RealmFile)); done(zx_local:import_realm(RealmFile));
do(["drop", "realm", Realm]) -> do(["drop", "realm", Realm]) ->
done(zx_local:drop_realm(Realm)); done(zx_local:drop_realm(Realm));
do(["logpath", Package, Run]) -> do(["logpath", PackageString, AgoString]) ->
done(zx_local:logpath(Package, Run)); case try list_to_integer(AgoString) catch Error:Reason -> {Error, Reason} end of
do(["status"]) -> {error, badarg} -> done(help(user));
done(zx_local:status()); Ago -> done(zx_local:logpath(PackageString, Ago))
end;
do(["set", "timeout", String]) -> do(["set", "timeout", String]) ->
done(zx_local:set_timeout(String)); done(zx_local:set_timeout(String));
do(["add", "mirror"]) -> do(["add", "mirror"]) ->
done(zx_local:add_mirror()); done(zx_local:add_mirror());
do(["drop", "mirror"]) -> do(["drop", "mirror"]) ->
done(zx_local:drop_mirror()); done(zx_local:drop_mirror());
do(["upgrade"]) ->
ok = zx_daemon:connect(),
done(upgrade());
do(["create", "project"]) -> do(["create", "project"]) ->
ok = zx_daemon:connect(),
done(zx_local:create_project()); done(zx_local:create_project());
do(["runlocal" | ArgV]) -> do(["runlocal" | ArgV]) ->
ok = start(), ok = zx_daemon:connect(),
not_done(run_local(ArgV)); not_done(run_local(ArgV));
do(["rundir", Path | ArgV]) ->
ok = zx_daemon:connect(),
not_done(run_dir(Path, ArgV));
do(["init"]) -> do(["init"]) ->
ok = zx_daemon:connect(),
ok = compatibility_check([unix]), ok = compatibility_check([unix]),
done(zx_local:initialize()); done(zx_local:initialize());
do(["list", "deps"]) -> do(["list", "deps"]) ->
done(zx_local:list_deps()); done(zx_local:list_deps());
do(["list", "deps", PackageString]) -> do(["list", "deps", PackageString]) ->
ok = zx_daemon:connect(),
done(zx_local:list_deps(PackageString)); done(zx_local:list_deps(PackageString));
do(["set", "dep", PackageString]) -> do(["set", "dep", PackageString]) ->
done(zx_local:set_dep(PackageString)); done(zx_local:set_dep(PackageString));
do(["drop", "dep", PackageString]) -> do(["drop", "dep", PackageString]) ->
PackageID = zx_lib:package_id(PackageString), done(zx_local:drop_dep(PackageString));
done(zx_local:drop_dep(PackageID)); do(["provides", Module]) ->
ok = zx_daemon:connect(),
done(zx_local:provides(Module));
do(["verup", Level]) -> do(["verup", Level]) ->
ok = compatibility_check([unix]), ok = compatibility_check([unix]),
done(zx_local:verup(Level)); done(zx_local:verup(Level));
@ -159,10 +179,6 @@ do(["set", "version", VersionString]) ->
done(zx_local:set_version(VersionString)); done(zx_local:set_version(VersionString));
do(["update", ".app"]) -> do(["update", ".app"]) ->
done(zx_local:update_app_file()); done(zx_local:update_app_file());
do(["create", "plt"]) ->
done(zx_local:create_plt());
do(["dialyze"]) ->
done(zx_local:dialyze());
do(["package"]) -> do(["package"]) ->
{ok, TargetDir} = file:get_cwd(), {ok, TargetDir} = file:get_cwd(),
done(zx_local:package(TargetDir)); done(zx_local:package(TargetDir));
@ -183,8 +199,9 @@ do(["approve", PackageString]) ->
done(zx_auth:approve(PackageString)); done(zx_auth:approve(PackageString));
do(["reject", PackageString]) -> do(["reject", PackageString]) ->
done(zx_auth:reject(PackageString)); done(zx_auth:reject(PackageString));
do(["add", "key"]) -> do(["sync", "keys"]) ->
done(zx_auth:add_key()); ok = zx_daemon:connect(),
done(zx_auth:sync_keys());
do(["create", "user"]) -> do(["create", "user"]) ->
done(zx_local:create_user()); done(zx_local:create_user());
do(["create", "userfile"]) -> do(["create", "userfile"]) ->
@ -195,32 +212,30 @@ do(["export", "user"]) ->
done(zx_local:export_user()); done(zx_local:export_user());
do(["import", "user", ZdufFile]) -> do(["import", "user", ZdufFile]) ->
done(zx_local:import_user(ZdufFile)); done(zx_local:import_user(ZdufFile));
do(["list", "users", Realm]) ->
done(zx_auth:list_users(Realm));
do(["list", "packagers", PackageName]) -> do(["list", "packagers", PackageName]) ->
done(zx_auth:list_packagers(PackageName)); done(zx_auth:list_packagers(PackageName));
do(["list", "maintainers", PackageName]) -> do(["list", "maintainers", PackageName]) ->
done(zx_auth:list_maintainers(PackageName)); done(zx_auth:list_maintainers(PackageName));
do(["list", "sysops", Realm]) -> do(["list", "sysops", Realm]) ->
done(zx_auth:list_sysops(Realm)); ok = zx_daemon:connect(),
done(zx_local:list_sysops(Realm));
do(["create", "realmfile"]) -> do(["create", "realmfile"]) ->
done(zx_local:create_realmfile()); done(zx_local:create_realmfile());
do(["install", PackageFile]) -> do(["install", PackageFile]) ->
case filelib:is_regular(PackageFile) of case filelib:is_regular(PackageFile) of
true -> true -> done(zx_daemon:install(PackageFile));
ok = start(), false -> done({error, ".zsp file does not exist", 22})
done(zx_daemon:install(PackageFile));
false ->
done({error, "Target directory does not exist", 22})
end; end;
do(["accept", PackageString]) -> do(["accept", PackageString]) ->
done(zx_auth:accept(PackageString)); done(zx_auth:accept(PackageString));
do(["add", "package", PackageName]) -> do(["add", "package", PackageName]) ->
done(zx_auth:add_package(PackageName)); done(zx_auth:add_package(PackageName));
do(["list", "users", Realm]) ->
done(zx_auth:list_users(Realm));
do(["add", "user", ZpuFile]) -> do(["add", "user", ZpuFile]) ->
done(zx_auth:add_user(ZpuFile)); done(zx_auth:add_user(ZpuFile));
do(["rem", "user", ZpuFile]) -> do(["rem", "user", Realm, UserName]) ->
done(zx_auth:rem_user(ZpuFile)); done(zx_auth:rem_user(Realm, UserName));
do(["add", "packager", Package, UserName]) -> do(["add", "packager", Package, UserName]) ->
done(zx_auth:add_packager(Package, UserName)); done(zx_auth:add_packager(Package, UserName));
do(["rem", "packager", Package, UserName]) -> do(["rem", "packager", Package, UserName]) ->
@ -229,31 +244,37 @@ do(["add", "maintainer", Package, UserName]) ->
done(zx_auth:add_maintainer(Package, UserName)); done(zx_auth:add_maintainer(Package, UserName));
do(["rem", "maintainer", Package, UserName]) -> do(["rem", "maintainer", Package, UserName]) ->
done(zx_auth:rem_maintainer(Package, UserName)); done(zx_auth:rem_maintainer(Package, UserName));
do(["add", "sysop", Package, UserName]) -> do(["add", "sysop", Realm, UserName]) ->
done(zx_auth:add_sysop(Package, UserName)); done(zx_auth:add_sysop(Realm, UserName));
do(["create", "realm"]) -> do(["create", "realm"]) ->
done(zx_local:create_realm()); done(zx_local:create_realm());
do(["takeover", Realm]) -> do(["takeover", Realm]) ->
done(zx_local:takeover(Realm)); done(zx_daemon:takeover(Realm));
do(["abdicate", Realm]) -> do(["abdicate", Realm]) ->
done(zx_local:abdicate(Realm)); done(zx_daemon:abdicate(Realm));
do(_) -> do(_) ->
usage_exit(22). done(help(top)).
-spec done(outcome()) -> no_return(). -spec done(outcome()) -> no_return().
done(ok) -> done(ok) ->
halt(0); ok = zx_daemon:idle(),
init:stop(0);
done({error, Code}) when is_integer(Code) -> done({error, Code}) when is_integer(Code) ->
ok = log(error, "Operation failed with code: ~w", [Code]), ok = zx_daemon:idle(),
halt(Code); Message = "Operation failed with code: ~w",
ok = tell(error, Message, [Code]),
init:stop(Code);
done({error, Reason}) -> done({error, Reason}) ->
ok = log(error, "Operation failed with: ~160tp", [Reason]), ok = zx_daemon:idle(),
halt(1); Message = "Operation failed with: ~160tp",
ok = tell(error, Message, [Reason]),
init:stop(1);
done({error, Info, Code}) -> done({error, Info, Code}) ->
ok = log(error, Info), ok = zx_daemon:idle(),
halt(Code). ok = tell(error, "Error: ~160tp: ~160tp", [Info, Code]),
init:stop(Code).
-spec not_done(outcome()) -> ok | no_return(). -spec not_done(outcome()) -> ok | no_return().
@ -279,8 +300,8 @@ compatibility_check(Platforms) ->
ok; ok;
false -> false ->
Message = "Unfortunately this command is not available on ~tw ~tw", Message = "Unfortunately this command is not available on ~tw ~tw",
ok = log(error, Message, [Family, Name]), ok = tell(error, Message, [Family, Name]),
halt(0) init:stop()
end. end.
@ -298,9 +319,46 @@ compatibility_check(Platforms) ->
%% @equiv application:ensure_started(zx). %% @equiv application:ensure_started(zx).
start() -> start() ->
% ok = application:ensure_started(sasl), LogPath =
ok = application:ensure_started(zx), case init:get_plain_arguments() of
zx_daemon:init_connections(). ["run", PackageString | _] ->
case zx_lib:package_id(PackageString) of
{ok, PackageID} -> zx_lib:new_logpath(PackageID);
Error -> done(Error)
end;
_ ->
{ok, Version} = zx_lib:string_to_version(os:getenv("ZX_VERSION")),
zx_lib:new_logpath({"otpr", "zx", Version})
end,
ok = logger:remove_handler(default),
LoggerConf =
#{config =>
#{burst_limit_enable => true,
burst_limit_max_count => 500,
burst_limit_window_time => 1000,
drop_mode_qlen => 200,
filesync_repeat_interval => no_repeat,
flush_qlen => 1000,
overload_kill_enable => false,
overload_kill_mem_size => 3000000,
overload_kill_qlen => 20000,
overload_kill_restart_after => 5000,
sync_mode_qlen => 10,
type => {file, LogPath}},
filter_default =>
stop,
filters =>
[{remote_gl, {fun logger_filters:remote_gl/2, stop}},
{domain, {fun logger_filters:domain/2, {log, super, [otp, sasl]}}},
{no_domain, {fun logger_filters:domain/2, {log, undefined,[]}}}],
formatter =>
{logger_formatter, #{legacy_header => false, single_line => true}},
id => default,
level => all,
module => logger_std_h},
ok = logger:add_handler(default, logger_std_h, LoggerConf),
ok = logger:set_primary_config(level, debug),
application:ensure_started(zx).
-spec stop() -> ok | {error, Reason :: term()}. -spec stop() -> ok | {error, Reason :: term()}.
@ -309,10 +367,16 @@ start() ->
%% `ok' in the case that zx is already stopped. %% `ok' in the case that zx is already stopped.
stop() -> stop() ->
ok = tell("Shutting down runtime."),
ok = zx_daemon:idle(),
case application:stop(zx) of case application:stop(zx) of
ok -> ok; ok ->
{error, {not_started, zx}} -> ok; init:stop();
Error -> Error {error, {not_started, zx}} ->
init:stop();
Error ->
ok = tell(error, "zx:stop/0 failed with ~tp", [Error]),
init:stop(1)
end. end.
@ -369,9 +433,75 @@ unsubscribe() ->
%%% Query Functions
-spec list() -> Result
when Result :: {ok, [realm()]}
| {error, no_realms}.
list() ->
case zx_lib:list_realms() of
[] -> {error, no_realms};
Realms -> {ok, Realms}
end.
-spec list(realm()) -> Result
when Result :: {ok, [realm()]}
| {error, Reason},
Reason :: bad_realm
| timeout
| network.
list(Realm) ->
{ok, ID} = zx_daemon:list(Realm),
wait_result(ID).
-spec list(realm(), name()) -> Result
when Result :: {ok, [version()]}
| {error, Reason},
Reason :: bad_realm
| bad_package
| timeout
| network.
list(Realm, Name) ->
list(Realm, Name, {z, z, z}).
-spec list(realm(), name(), version()) -> Result
when Result :: {ok, [version()]}
| {error, Reason},
Reason :: bad_realm
| bad_package
| bad_version
| timeout
| network.
list(Realm, Name, Version) ->
{ok, ID} = zx_daemon:list(Realm, Name, Version),
wait_result(ID).
-spec latest(package_id()) -> Result
when Result :: {ok, package_id()}
| {error, Reason},
Reason :: bad_realm
| bad_package
| bad_version
| timeout
| network.
latest(PackageID) ->
{ok, ID} = zx_daemon:latest(PackageID),
wait_result(ID).
%%% Execution of application %%% Execution of application
-spec run(PackageString, RunArgs) -> no_return() -spec run(PackageString, RunArgs) -> zx:outcome()
when PackageString :: string(), when PackageString :: string(),
RunArgs :: [string()]. RunArgs :: [string()].
%% @private %% @private
@ -393,32 +523,43 @@ unsubscribe() ->
run(PackageString, RunArgs) -> run(PackageString, RunArgs) ->
case zx_lib:package_id(PackageString) of case zx_lib:package_id(PackageString) of
{ok, FuzzyID} -> run2(FuzzyID, RunArgs); {ok, {"otpr", "zomp", Version}} -> run2_maybe(Version, RunArgs);
Error -> log(info, "run/2 got ~tp", [Error]), Error {ok, FuzzyID} -> run2(FuzzyID, RunArgs);
Error -> Error
end. end.
run2(FuzzyID = {Realm, Name, _}, RunArgs) -> run2_maybe(Version, RunArgs) ->
case resolve_installed_version(FuzzyID) of {ok, Managed} = zx_daemon:conf(managed),
exact -> run3(FuzzyID, RunArgs); case lists:member("otpr", Managed) of
{ok, Installed} -> run3({Realm, Name, Installed}, RunArgs); true -> run_zomp(RunArgs);
not_found -> run3_maybe(FuzzyID, RunArgs) false -> run2({"otpr", "zomp", Version}, RunArgs)
end.
run_zomp(RunArgs) ->
{ok, Dirs} = file:list_dir(zx_lib:path(lib, "otpr", "zomp")),
Versions = lists:foldl(fun tuplize/2, [], Dirs),
case zx_lib:find_latest_compatible({z, z, z}, Versions) of
not_found -> {error, not_found};
{ok, Latest} -> run3({"otpr", "zomp", Latest}, RunArgs)
end.
tuplize(String, Acc) ->
case zx_lib:string_to_version(String) of
{ok, Version} -> [Version | Acc];
_ -> Acc
end.
run2(FuzzyID, RunArgs) ->
case resolve_version(FuzzyID) of
{installed, PackageID} -> run3(PackageID, RunArgs);
{fetch, PackageID} -> run3_maybe(PackageID, RunArgs);
Error -> Error
end. end.
run3_maybe(PackageID, RunArgs) -> run3_maybe(PackageID, RunArgs) ->
{ok, ID} = zx_daemon:latest(PackageID),
case wait_result(ID) of
{ok, Version} ->
NewID = setelement(3, PackageID, Version),
{ok, PackageString} = zx_lib:package_string(NewID),
ok = log(info, "Fetching ~ts", [PackageString]),
run3_maybe2(NewID, RunArgs);
Error ->
Error
end.
run3_maybe2(PackageID, RunArgs) ->
case fetch(PackageID) of case fetch(PackageID) of
ok -> run3(PackageID, RunArgs); ok -> run3(PackageID, RunArgs);
Error -> Error Error -> Error
@ -434,8 +575,33 @@ run3(PackageID, RunArgs) ->
execute(Type, PackageID, Meta, Dir, RunArgs). execute(Type, PackageID, Meta, Dir, RunArgs).
-spec run_local(RunArgs) -> no_return() -spec resolve_version(PackageID) -> Result
when RunArgs :: [term()]. 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_version(PackageID = {_, _, {X, Y, Z}})
when is_integer(X), is_integer(Y), is_integer(Z) ->
case zx_lib:installed(PackageID) of
true -> {installed, PackageID};
false -> {fetch, PackageID}
end;
resolve_version(PackageID = {Realm, Name, _}) ->
{ok, ID} = zx_daemon:latest(PackageID),
case wait_result(ID) of
{ok, Latest} -> resolve_version({Realm, Name, Latest});
Error -> Error
end.
-spec run_local(RunArgs) -> zx:outcome() | no_return()
when RunArgs :: [string()].
%% @private %% @private
%% Execute a local project from source from the current directory, satisfying dependency %% Execute a local project from source from the current directory, satisfying dependency
%% requirements via the locally installed zomp lib cache. The project must be %% requirements via the locally installed zomp lib cache. The project must be
@ -446,6 +612,30 @@ run3(PackageID, RunArgs) ->
%% and use zx commands to add or drop dependencies made available via zomp. %% and use zx commands to add or drop dependencies made available via zomp.
run_local(RunArgs) -> run_local(RunArgs) ->
{ok, ProjectDir} = file:get_cwd(),
run_project(ProjectDir, ProjectDir, RunArgs).
-spec run_dir(TargetDir, RunArgs) -> zx:outcome() | no_return()
when TargetDir :: file:filename(),
RunArgs :: [string()].
run_dir(TargetDir, RunArgs) ->
{ok, ExecDir} = file:get_cwd(),
case file:set_cwd(TargetDir) of
ok ->
{ok, ProjectDir} = file:get_cwd(),
run_project(ProjectDir, ExecDir, RunArgs);
Error -> Error
end.
-spec run_project(ProjectDir, ExecDir, RunArgs) -> zx:outcome() | no_return()
when ProjectDir :: file:filename(),
ExecDir :: file:filename(),
RunArgs :: [string()].
run_project(ProjectDir, ExecDir, RunArgs) ->
{ok, Meta} = zx_lib:read_project_meta(), {ok, Meta} = zx_lib:read_project_meta(),
PackageID = {_, Name, _} = maps:get(package_id, Meta), PackageID = {_, Name, _} = maps:get(package_id, Meta),
Type = maps:get(type, Meta), Type = maps:get(type, Meta),
@ -454,15 +644,14 @@ run_local(RunArgs) ->
true = os:putenv(Name ++ "_include", filename:join(Dir, "include")), true = os:putenv(Name ++ "_include", filename:join(Dir, "include")),
case prepare(Deps) of case prepare(Deps) of
ok -> ok ->
ok = file:set_cwd(Dir), ok = file:set_cwd(ProjectDir),
ok = zx_lib:build(), ok = zx_lib:build(),
ok = file:set_cwd(zx_lib:zomp_dir()), ok = file:set_cwd(ExecDir),
execute(Type, PackageID, Meta, Dir, RunArgs); execute(Type, PackageID, Meta, Dir, RunArgs);
Error -> Error ->
Error Error
end. end.
-spec prepare([zx:package_id()]) -> ok. -spec prepare([zx:package_id()]) -> ok.
%% @private %% @private
%% Execution prep common to all packages. %% Execution prep common to all packages.
@ -488,15 +677,45 @@ make([Dep | Rest]) ->
Error -> Error Error -> Error
end; end;
make([]) -> make([]) ->
log(info, "Deps prepared."). tell("Builds complete.").
include_env(PackageID = {_, Name, _}) -> include_env(PackageID = {_, Name, _}) ->
Path = filename:join(zx_lib:ppath(lib, PackageID), "include"), Path = filename:join(zx_lib:ppath(lib, PackageID), "include"),
os:putenv(Name ++ "_include", Path). os:putenv(Name ++ "_include", Path).
-spec upgrade() -> zx:outcome().
%% @private
%% Upgrade ZX itself to the latest version..
upgrade() ->
ZxDir = os:getenv("ZX_DIR"),
{ok, Meta} = zx_lib:read_project_meta(ZxDir),
PackageID = {Realm, Name, Current} = maps:get(package_id, Meta),
{ok, PackageString} = zx_lib:package_string(PackageID),
ok = tell("Current version: ~s~n", [PackageString]),
{ok, ID} = zx_daemon:latest({Realm, Name}),
case wait_result(ID) of
{ok, Current} ->
tell("Running latest version.~n");
{ok, Latest} when Latest > Current ->
NewID = {Realm, Name, Latest},
ok = acquire([NewID], [NewID]),
{ok, LatestString} = zx_lib:version_to_string(Latest),
VersionTxt = filename:join(zx_lib:path(etc), "version.txt"),
ok = file:write_file(VersionTxt, LatestString),
{ok, NewString} = zx_lib:package_string(NewID),
tell("Upgraded to ~s~n.", [NewString]);
{ok, Available} when Available < Current ->
{ok, AvailableString} = zx_lib:version_to_string(Available),
Message = "Local version is newer than ~s. Nothing to do.~n",
ok = tell(Message, [AvailableString]);
Error ->
Error
end.
-spec fetch(zx:package_id()) -> zx:outcome(). -spec fetch(zx:package_id()) -> zx:outcome().
fetch(PackageID) -> fetch(PackageID) ->
@ -508,12 +727,12 @@ fetch2(ID) ->
{result, ID, done} -> {result, ID, done} ->
ok; ok;
{result, ID, {hops, Count}} -> {result, ID, {hops, Count}} ->
ok = log(info, "Inbound; ~w hops away.", [Count]), ok = tell("Inbound; ~w hops away.", [Count]),
fetch2(ID); fetch2(ID);
{result, ID, {error, Reason}} -> {result, ID, Error} ->
{error, Reason, 1} Error
after 10000 -> after 10000 ->
{error, timeout, 62} {error, timeout}
end. end.
@ -529,17 +748,17 @@ fetch2(ID) ->
execute(app, PackageID, Meta, Dir, RunArgs) -> execute(app, PackageID, Meta, Dir, RunArgs) ->
{ok, PackageString} = zx_lib:package_string(PackageID), {ok, PackageString} = zx_lib:package_string(PackageID),
ok = log(info, "Starting ~ts.", [PackageString]), ok = tell("Starting ~ts.", [PackageString]),
Name = element(2, PackageID), Name = element(2, PackageID),
ok = zx_daemon:pass_meta(Meta, Dir, RunArgs), ok = zx_daemon:pass_meta(Meta, Dir, RunArgs),
AppTag = list_to_atom(Name), AppTag = list_to_atom(Name),
ok = ensure_all_started(AppTag), ok = ensure_all_started(AppTag),
log(info, "Launcher complete."); tell("Launcher complete.");
execute(lib, PackageID, _, _, _) -> execute(lib, PackageID, _, _, _) ->
Message = "Lib ~ts is available on the system, but is not a standalone app.", Message = "Lib ~ts is available on the system, but is not a standalone app.",
{ok, PackageString} = zx_lib:package_string(PackageID), {ok, PackageString} = zx_lib:package_string(PackageID),
ok = log(info, Message, [PackageString]), ok = tell(Message, [PackageString]),
halt(0). init:stop().
-spec ensure_all_started(AppMod) -> ok -spec ensure_all_started(AppMod) -> ok
@ -554,39 +773,7 @@ execute(lib, PackageID, _, _, _) ->
ensure_all_started(AppMod) -> ensure_all_started(AppMod) ->
case application:ensure_all_started(AppMod) of case application:ensure_all_started(AppMod) of
{ok, []} -> ok; {ok, []} -> ok;
{ok, Apps} -> log(info, "Started ~160tp", [Apps]) {ok, Apps} -> tell("Started ~160tp", [Apps])
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({Realm, Name, Version}) ->
PackageDir = zx_lib:path(lib, Realm, Name),
case filelib:is_dir(PackageDir) of
true -> resolve_installed_version(PackageDir, Version);
false -> not_found
end.
resolve_installed_version(PackageDir, Version) ->
DirStrings = filelib:wildcard("*", PackageDir),
Versions = lists:foldl(fun tuplize/2, [], DirStrings),
zx_lib:find_latest_compatible(Version, Versions).
tuplize(String, Acc) ->
case zx_lib:string_to_version(String) of
{ok, Version} -> [Version | Acc];
_ -> Acc
end. end.
@ -600,17 +787,6 @@ wait_result(ID) ->
%%% Usage %%% 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 = lists:foreach(fun io:format/1, usage_all()),
halt(Code).
help(top) -> show_help(); help(top) -> show_help();
help(user) -> show_help([usage_header(), usage_user(), usage_spec()]); help(user) -> show_help([usage_header(), usage_user(), usage_spec()]);
help(dev) -> show_help([usage_header(), usage_dev(), usage_spec()]); help(dev) -> show_help([usage_header(), usage_dev(), usage_spec()]);
@ -628,15 +804,11 @@ show_help() ->
show_help(Info) -> lists:foreach(fun io:format/1, Info). show_help(Info) -> lists:foreach(fun io:format/1, Info).
usage_all() ->
[usage_header(), usage_user(), usage_dev(), usage_sysop(), usage_spec()].
usage_header() -> usage_header() ->
"ZX usage: zx [command] [object] [args]~n~n". "ZX usage: zx [command] [object] [args]~n~n".
usage_user() -> usage_user() ->
"User Actions:~n" "User Actions:~n"
" zx help~n"
" zx run PackageID [Args]~n" " zx run PackageID [Args]~n"
" zx list realms~n" " zx list realms~n"
" zx list packages Realm~n" " zx list packages Realm~n"
@ -654,15 +826,15 @@ usage_dev() ->
"Developer/Packager/Maintainer Actions:~n" "Developer/Packager/Maintainer Actions:~n"
" zx create project~n" " zx create project~n"
" zx runlocal [Args]~n" " zx runlocal [Args]~n"
" zx rundir Path [Args]~n"
" zx init~n" " zx init~n"
" zx list deps [PackageID]~n" " zx list deps [PackageID]~n"
" zx set dep PackageID~n" " zx set dep PackageID~n"
" zx drop dep PackageID~n" " zx drop dep PackageID~n"
" zx provides Module~n"
" zx verup Level~n" " zx verup Level~n"
" zx set version Version~n" " zx set version Version~n"
" zx update .app~n" " zx update .app~n"
" zx create plt~n"
" zx dialyze~n"
" zx package Path~n" " zx package Path~n"
" zx submit ZSP~n" " zx submit ZSP~n"
" zx list pending PackageName~n" " zx list pending PackageName~n"
@ -675,9 +847,11 @@ usage_dev() ->
" zx create keypair~n" " zx create keypair~n"
" zx export user~n" " zx export user~n"
" zx import user [ZPUF | ZDUF]~n" " zx import user [ZPUF | ZDUF]~n"
" zx list users Realm~n"
" zx list packagers PackageName~n" " zx list packagers PackageName~n"
" zx list maintainers PackageName~n" " zx list maintainers PackageName~n"
" zx list sysops Realm~n" " zx list sysops Realm~n"
" zx create realmfile~n"
" zx install ZSP~n~n". " zx install ZSP~n~n".
usage_sysop() -> usage_sysop() ->
@ -685,13 +859,11 @@ usage_sysop() ->
" zx list approved Realm~n" " zx list approved Realm~n"
" zx accept PackageID~n" " zx accept PackageID~n"
" zx add package PackageName~n" " zx add package PackageName~n"
" zx list users Realm~n"
" zx add user ZPUF~n" " zx add user ZPUF~n"
" zx add packager PackageName UserID~n" " zx add packager PackageName UserID~n"
" zx add maintainer PackageName UserID~n" " zx add maintainer PackageName UserID~n"
" zx add sysop UserID~n" " zx add sysop UserID~n"
" zx create realm~n" " zx create realm~n"
" zx create realmfile~n"
" zx takeover Realm~n" " zx takeover Realm~n"
" zx abdicate Realm~n~n". " zx abdicate Realm~n~n".
@ -703,6 +875,7 @@ usage_spec() ->
" Version :: Version string X, X.Y, or X.Y.Z: \"1\", \"1.2\", \"1.2.3\"~n" " Version :: Version string X, X.Y, or X.Y.Z: \"1\", \"1.2\", \"1.2.3\"~n"
" RealmFile :: Path to a valid .zrf realm file~n" " RealmFile :: Path to a valid .zrf realm file~n"
" Realm :: The name of a realm as a string [:a-z:]~n" " Realm :: The name of a realm as a string [:a-z:]~n"
" Module :: Name of a code module.~n"
" KeyName :: The prefix of a keypair to drop~n" " KeyName :: The prefix of a keypair to drop~n"
" Level :: The version level, one of \"major\", \"minor\", or \"patch\"~n" " Level :: The version level, one of \"major\", \"minor\", or \"patch\"~n"
" Path :: Path or filename.~n" " Path :: Path or filename.~n"

View File

@ -0,0 +1,588 @@
%%% @doc
%%% ZX Auth
%%%
%%% This module is where all the AUTH type command code lives. AUTH commands are special
%%% because they do not involve the zx_daemon at all, though they do perform network
%%% operations.
%%%
%%% All AUTH procedures terminate the runtime once complete.
%%% @end
-module(zx_auth).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([list_users/1, list_packagers/1, list_maintainers/1,
add_packager/2, rem_packager/2,
add_maintainer/2, rem_maintainer/2,
list_pending/1, list_approved/1,
submit/1, review/1, approve/1, reject/1, accept/1,
add_package/1,
keychain/1, list_user_keys/1,
add_user/1]).
-include("zx_logger.hrl").
%%% Functions
list_users(Realm) -> list_users(1, Realm).
list_packagers(PackageString) -> list_users(2, PackageString).
list_maintainers(PackageString) -> list_users(3, PackageString).
-spec list_users(Command, Target) -> zx:outcome()
when Command :: 1..3,
Target :: zx:realm() | zx:package().
list_users(Command, Target) ->
case uu_package_request(Command, Target) of
{ok, Users} -> lists:foreach(fun zx_lib:print_user/1, Users);
Error -> Error
end.
add_packager(Package, User) -> su_user_request(4, Package, User).
rem_packager(Package, User) -> su_user_request(5, Package, User).
add_maintainer(Package, User) -> su_user_request(6, Package, User).
rem_maintainer(Package, User) -> su_user_request(7, Package, User).
-spec list_pending(PackageString :: string()) -> zx:outcome().
%% @private
%% List the versions of a package that are pending review. The package name is input by
%% the user as a string of the form "otpr-zomp" and the output is a list of full
%% package IDs, printed one per line to stdout (like "otpr-zomp-3.2.2").
list_pending(PackageString) ->
Command = 8,
case uu_package_request(Command, PackageString) of
{ok, Versions} -> lists:foreach(fun print_version/1, Versions);
Error -> Error
end.
print_version(Tuple) ->
{ok, VersionString} = zx_lib:version_to_string(Tuple),
io:format("~ts~n", [VersionString]).
-spec list_approved(zx:realm()) -> zx:outcome().
%% @private
%% List the package ids of all packages waiting in the resign queue for the given realm,
%% printed to stdout one per line.
list_approved(Realm) ->
{ok, Realms} = zx_daemon:list(),
case lists:member(Realm, Realms) of
true -> list_approved2(Realm);
false -> {error, bad_realm}
end.
list_approved2(Realm) ->
Command = 9,
case make_uu_request(Command, Realm) of
{ok, PackageIDs} ->
Print =
fun({Name, Version}) ->
{ok, PackageString} = zx_lib:package_string({Realm, Name, Version}),
io:format("~ts~n", [PackageString])
end,
lists:foreach(Print, PackageIDs);
Error ->
Error
end.
-spec submit(ZspPath :: file:filename()) -> zx:outcome().
%% @private
%% Submit a package to the appropriate "prime" server for the given realm.
submit(ZspPath) ->
case file:read_file(ZspPath) of
{ok, ZspBin} -> submit2(ZspBin);
Error -> Error
end.
submit2(ZspBin) ->
case zx_zsp:verify(ZspBin) of
ok -> submit3(ZspBin);
Error -> Error
end.
submit3(ZspBin) ->
{ok, {{Realm, Name, Version}, KeyName, _, _, _}} = zx_zsp:meta(ZspBin),
UserName = select_auth(Realm),
case zx_daemon:get_key(private, {Realm, KeyName}) of
{ok, DKey} ->
Payload = {Realm, UserName, KeyName, {Name, Version}},
submit4(Payload, Realm, ZspBin, DKey);
Error ->
Message =
"The private half of the key used to sign this package is not present "
"on the local system.~n"
"Import it and try again or do `zx resign ZspPath`.~n",
ok = io:format(Message),
Error
end.
submit4(Payload, Realm, ZspBin, DKey) ->
case connect(Realm) of
{ok, Socket} -> submit5(Socket, Payload, ZspBin, DKey);
Error -> Error
end.
submit5(Socket, Payload, ZspBin, DKey) ->
Command = 10,
Request = pack_and_sign(Command, Payload, DKey),
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", Request/binary>>),
case zx_net:tx(Socket, ZspBin) of
ok -> done(Socket);
{error, Reason} -> done(Socket, Reason)
end.
-spec review(PackageString :: string()) -> zx:outcome().
review(PackageString) ->
case zx_lib:package_id(PackageString) of
{ok, PackageID} -> review2(PackageID);
Error -> Error
end.
review2(PackageID = {Realm, _, _}) ->
case connect(Realm) of
{ok, Socket} -> review3(PackageID, Socket);
Error -> Error
end.
review3(PackageID, Socket) ->
Command = 11,
TermBin = term_to_binary(PackageID),
Request = <<0:24, Command:8, TermBin/binary>>,
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", Request/binary>>),
receive
{tcp, Socket, <<0:1, 0:7>>} -> review4(PackageID, Socket);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
review4(PackageID, Socket) ->
case zx_net:rx(Socket) of
{ok, ZspBin} ->
ok = zx_net:disconnect(Socket),
review5(PackageID, ZspBin);
{error, Reason} ->
done(Socket, Reason)
end.
review5(PackageID, ZspBin) ->
{ok, Requested} = zx_lib:package_string(PackageID),
case zx_zsp:meta(ZspBin) of
{ok, {PackageID, _, _, _, _}} ->
zx_zsp:extract(ZspBin, cwd);
{ok, {UnexpectedID, _, _, _, _}} ->
{ok, Unexpected} = zx_lib:package_string(UnexpectedID),
Message = "Requested ~ts, but inside was ~ts! Aborting.",
ok = log(warning, Message, [Requested, Unexpected]),
{error, "Wrong package received.", 29};
Error ->
Error
end.
approve(Package) -> su_package_request(12, Package).
reject(Package) -> su_package_request(13, Package).
-spec accept(ZspPath :: file:filename()) -> zx:outcome().
accept(ZspPath) ->
case file:read_file(ZspPath) of
{ok, ZspBin} -> accept2(ZspBin);
Error -> Error
end.
accept2(ZspBin) ->
case zx_zsp:meta(ZspBin) of
{ok, Meta} -> accept3(ZspBin, Meta);
error -> {error, bad_package}
end.
accept3(ZspBin, Meta) ->
Realm = element(1, element(1, Meta)),
case connect_auth(Realm) of
{ok, AuthConn} -> accept4(ZspBin, Meta, AuthConn);
Error -> Error
end.
accept4(ZspBin, Meta = {_, KeyName, _, _, _}, AuthConn = {_, KeyName, Key, _, _}) ->
case zx_zsp:verify(ZspBin, Key) of
true ->
accept5(ZspBin, Meta, AuthConn);
false ->
Message =
"~nALERT!~n"
"This package is not signed with the key it claims!~n"
"Resign this package with `zx resign [ZspPath]` to fix the problem.~n",
ok = io:format(Message),
{error, bad_sig}
end;
accept4(_, {_, PackageKey, _, _, _}, {_, UserKey, _, _, _}) ->
Message =
"~nERROR: BAD KEY~n"
"The package signature key and your auth key do not match.~n"
"PackageKey: ~tp~n"
"UserKey : ~tp~n"
"Resign this package with `zx resign [ZspPath]` or select the same key~n",
ok = io:format(Message, [PackageKey, UserKey]),
{error, bad_key}.
accept5(ZspBin,
{{Realm, Name, Version}, KeyName, Tags, Deps, Mods},
{UserName, KeyName, Key, SSTag, Socket}) ->
Command = 14,
Payload = {Realm, {Name, Version}, Tags, Deps, Mods, byte_size(ZspBin)},
Message = {SSTag, UserName, KeyName, Payload},
Request = pack_and_sign(Command, Message, Key),
ok = gen_tcp:send(Socket, <<0:8, Request/binary>>),
ok = inet:setopts(Socket, [{active, once}]),
receive
{tcp, Socket, <<0:8>>} -> accept6(ZspBin, Socket);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
accept6(ZspBin, Socket) ->
ok = zx_net:tx(Socket, ZspBin),
done(Socket).
add_package(PackageString) ->
case zx_lib:package_id(PackageString) of
{ok, {R, N, {z, z, z}}} ->
{ok, Realms} = zx_daemon:list(),
case lists:member(R, Realms) of
true -> add_package2({R, N});
false -> {error, bad_realm}
end;
{ok, _} ->
{error, "Must not include a version number.", 1};
Error ->
Error
end.
add_package2(Target) ->
Realm = element(1, Target),
case connect_auth(Realm) of
{ok, AuthConn} -> add_package3(Target, AuthConn);
Error -> Error
end.
add_package3(Target, {UserName, KeyName, Key, Tag, Socket}) ->
Command = 15,
Payload = {Tag, UserName, KeyName, Target},
Request = pack_and_sign(Command, Payload, Key),
ok = gen_tcp:send(Socket, <<0:8, Request/binary>>),
done(Socket).
-spec add_user(file:filename()) -> zx:outcome().
add_user(ZPUF) ->
case file:read_file(ZPUF) of
{ok, Bin} -> add_user2(Bin);
Error -> Error
end.
add_user2(Bin) ->
case zx_lib:b_to_t(Bin) of
{ok, {UserInfo, KeyData}} -> add_user3(UserInfo, KeyData);
error -> {error, "Bad user file.", 1}
end.
add_user3(UserInfo, KeyData) ->
Realm = proplists:get_value(realm, UserInfo),
case prep_auth(Realm) of
{ok, AuthData = {_, KeyName, Key}} ->
UserData = {proplists:get_value(username, UserInfo),
proplists:get_value(realname, UserInfo),
proplists:get_value(contact_info, UserInfo),
[sign_and_sterilize(KeyName, Key, KD) || KD <- KeyData]},
add_user4(Realm, UserData, AuthData);
Error ->
Error
end.
add_user4(Realm, UserData, AuthData) ->
case connect(Realm) of
{ok, Socket} -> make_su_request3(16, Realm, UserData, AuthData, Socket);
Error -> Error
end.
-spec list_user_keys(zx:user_id()) -> zx:outcome().
list_user_keys(UserID) -> make_uu_request(17, UserID).
keychain(KeyID) ->
Command = 19,
Realm = element(1, KeyID),
case make_uu_request(Command, KeyID) of
{ok, KeyData} -> keychain2(Realm, KeyData);
Error -> Error
end.
keychain2(Realm, [{UserName, Key = {_, {{SigKeyName, Sig}, Bin}, none}} | Rest]) ->
{ok, SigKey} = zx_daemon:get_key(public, {Realm, SigKeyName}),
true = zx_key:verify(Bin, Sig, SigKey),
ok = zx_daemon:register_key({Realm, UserName}, Key),
keychain2(Realm, Rest);
keychain2(_, []) ->
ok.
%%% Generic Request Forms
uu_package_request(Command, PackageString) ->
case zx_lib:package_id(PackageString) of
{ok, {Realm, Name, _}} -> make_uu_request(Command, {Realm, Name});
Error -> Error
end.
-spec make_uu_request(Command, Target) -> zx:outcome()
when Command :: 1..3 | 8 | 9 | 11 | 17 | 22,
Target :: zx:realm() | zx:package() | zx:package_id() | zx:user_id().
make_uu_request(Command, Target) when is_tuple(Target) ->
make_uu_request2(Command, element(1, Target), Target);
make_uu_request(Command, Target) when is_list(Target) ->
make_uu_request2(Command, Target, Target).
make_uu_request2(Command, Realm, Target) ->
case connect(Realm) of
{ok, Socket} -> make_uu_request3(Command, Target, Socket);
Error -> Error
end.
make_uu_request3(Command, Target, Socket) ->
TermBin = term_to_binary(Target),
Request = <<"ZOMP AUTH 1:", 0:24, Command:8, TermBin/binary>>,
ok = gen_tcp:send(Socket, Request),
done(Socket).
-spec su_user_request(Command, Package, User)-> zx:outcome()
when Command :: 4..7,
Package :: string(),
User :: zx:user_name().
su_user_request(Code, Package, User) ->
case zx_lib:package_id(Package) of
{ok, {Realm, Name, {z, z, z}}} -> make_su_request(Code, Realm, {Name, User});
Error -> Error
end.
-spec su_package_request(Code :: 11 | 12, Package :: string()) -> zx:outcome().
su_package_request(Code, Package) ->
case zx_lib:package_id(Package) of
{ok, {Realm, Name, Version}} -> make_su_request(Code, Realm, {Name, Version});
Error -> Error
end.
-spec make_su_request(Command, Realm, Data) -> zx:outcome()
when Command :: 4..7 | 10 | 12 | 13 | 16 | 18,
Realm :: zx:realm(),
Data :: term().
make_su_request(Command, Realm, Data) ->
case prep_auth(Realm) of
{ok, AuthData} -> make_su_request2(Command, Realm, Data, AuthData);
Error -> Error
end.
make_su_request2(Command, Realm, Data, AuthData) ->
case connect(Realm) of
{ok, Socket} -> make_su_request3(Command, Realm, Data, AuthData, Socket);
Error -> Error
end.
make_su_request3(Command, Realm, Data, {Signatory, KeyName, Key}, Socket) ->
Payload = {Realm, Signatory, KeyName, Data},
Request = pack_and_sign(Command, Payload, Key),
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", Request/binary>>),
done(Socket).
%%% Utility Functions
-spec prep_auth(Realm) -> {User, KeyName, Key}
when Realm :: zx:realm(),
User :: zx:user_id(),
KeyName :: zx:key_id(),
Key :: term().
%% @private
%% Loads the appropriate User, KeyID and reads in a registered key for use in
%% connect_auth/4.
prep_auth(Realm) ->
UserName = select_auth(Realm),
case zx_local:select_private_key({Realm, UserName}) of
{ok, {KeyName, Key}} ->
{ok, {UserName, KeyName, Key}};
error ->
ok = log(error, "No private key exists for user ~tp.", [UserName]),
{error, no_key}
end.
pack_and_sign(Command, Payload, Key) ->
Bin = term_to_binary(Payload),
Signed = <<Command:8, Bin/binary>>,
Sig = zx_key:sign(Signed, Key),
SSize = byte_size(Sig),
<<SSize:24, Sig/binary, Signed/binary>>.
sign_and_sterilize(SigKeyName, SigKey, {Name, {_, Der}, _}) ->
Sig = zx_key:sign(Der, SigKey),
{Name, {{SigKeyName, Sig}, Der}, none}.
%%% Connectiness with prime
-spec select_auth(zx:realm()) -> zx:user_name().
select_auth(Realm) ->
Pattern = filename:join(zx_lib:path(etc, Realm), "*.user"),
LocalUsers = [filename:basename(UN, ".user") || UN <- filelib:wildcard(Pattern)],
case LocalUsers of
[] ->
Message =
"A user record is required to complete this action. Creating now...",
ok = log(info, Message),
zx_local:create_user(Realm);
[UserName] ->
UserName;
UserNames ->
Message = "Under what user's authority are you taking this action?~n",
ok = io:format(Message),
zx_tty:select_string(UserNames)
end.
-spec connect_auth(Realm) -> Result
when Realm :: zx:realm(),
Result :: {ok, AuthConn}
| {error, Reason},
AuthConn :: {UserName :: zx:user_name(),
KeyName :: zx:key_name(),
Key :: term(),
SSTag :: zx:ss_tag(),
Socket :: gen_tcp:socket()},
Reason :: term().
%% @private
%% Connect to one of the servers in the realm constellation.
connect_auth(Realm) ->
case zx_lib:load_realm_conf(Realm) of
{ok, RealmConf} ->
connect_auth2(Realm, RealmConf);
Error ->
ok = log(error, "Realm ~160tp is not configured.", [Realm]),
Error
end.
connect_auth2(Realm, RealmConf) ->
case prep_auth(Realm) of
{ok, UserData} -> connect_auth3(Realm, RealmConf, UserData);
Error -> Error
end.
connect_auth3(Realm, RealmConf, UserData) ->
{Host, Port} = maps:get(prime, RealmConf),
Options = [{packet, 4}, {mode, binary}, {active, once}],
case gen_tcp:connect(Host, Port, Options, 5000) of
{ok, Socket} ->
connect_auth4(Socket, Realm, UserData);
Error = {error, E} ->
ok = log(warning, "Connection problem: ~160tp", [E]),
{error, Error}
end.
connect_auth4(Socket, Realm, UD = {UserName, KeyName, Key}) ->
Null = 0,
Timestamp = calendar:universal_time(),
Payload = {Realm, Timestamp, UserName, KeyName},
NullRequest = pack_and_sign(Null, Payload, Key),
ok = gen_tcp:send(Socket, <<"ZOMP AUTH 1:", NullRequest/binary>>),
receive
{tcp, Socket, <<0:8, Bin/binary>>} -> connect_auth5(Socket, UD, Bin);
{tcp, Socket, Bin} -> done(Socket, Bin);
{tcp_closed, Socket} -> {error, tcp_closed}
after 5000 -> done(Socket, timeout)
end.
connect_auth5(Socket, {UserName, KeyName, Key}, Bin) ->
case zx_lib:b_to_ts(Bin) of
{ok, Tag} -> {ok, {UserName, KeyName, Key, Tag, Socket}};
error -> done(Socket, bad_response)
end.
connect(Realm) ->
case zx_lib:load_realm_conf(Realm) of
{ok, RealmConf} ->
{Host, Port} = maps:get(prime, RealmConf),
Options = [{packet, 4}, {mode, binary}, {nodelay, true}, {active, once}],
gen_tcp:connect(Host, Port, Options, 5000);
Error ->
ok = log(error, "Realm ~160tp is not configured.", [Realm]),
Error
end.
done(Socket) ->
ok = inet:setopts(Socket, [{active, once}]),
receive
{tcp, Socket, <<0:1, 0:7>>} ->
zx_net:disconnect(Socket);
{tcp, Socket, <<0:1, 0:7, Bin/binary>>} ->
ok = zx_net:disconnect(Socket),
case zx_lib:b_to_ts(Bin) of
error -> {error, bad_response};
Term -> Term
end;
{tcp, Socket, Bin} ->
ok = zx_net:disconnect(Socket),
{error, zx_net:err_in(Bin)};
{tcp_closed, Socket} ->
{error, tcp_closed}
after 5000 ->
done(Socket, timeout)
end.
done(Socket, Reason) ->
ok = zx_net:disconnect(Socket),
case is_binary(Reason) of
true -> {error, zx_net:err_in(Reason)};
false -> {error, Reason}
end.

View File

@ -7,12 +7,13 @@
%%% @end %%% @end
-module(zx_conn). -module(zx_conn).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0"). -license("GPL-3.0").
-export([subscribe/2, unsubscribe/2, request/3]). -export([subscribe/2, unsubscribe/2, request/3]).
-export([start/1, stop/1]). -export([start/1, retire/1, stop/1]).
-export([start_link/1, init/2]). -export([start_link/1, init/2]).
-include("zx_logger.hrl"). -include("zx_logger.hrl").
@ -67,6 +68,13 @@ start(Target) ->
zx_conn_sup:start_conn(Target). zx_conn_sup:start_conn(Target).
-spec retire(Conn :: pid()) -> ok.
retire(Conn) ->
Conn ! retire,
ok.
-spec stop(Conn :: pid()) -> ok. -spec stop(Conn :: pid()) -> ok.
%% @doc %% @doc
%% Signals the connection to disconnect and retire immediately. %% Signals the connection to disconnect and retire immediately.
@ -114,7 +122,8 @@ connect(Parent, Debug, {Host, Port}) ->
{ok, Socket} -> {ok, Socket} ->
confirm_service(Parent, Debug, Socket); confirm_service(Parent, Debug, Socket);
{error, Error} -> {error, Error} ->
ok = log(warning, "Connection problem with ~160tp: ~160tp", [Host, Error]), HS = zx_net:host_string({Host, Port}),
ok = log(warning, "Connection problem with ~ts: ~160tp", [HS, Error]),
ok = zx_daemon:report(failed), ok = zx_daemon:report(failed),
terminate() terminate()
end. end.
@ -148,11 +157,21 @@ confirm_service(Parent, Debug, Socket) ->
{tcp, Socket, <<2:8, Version:16>>} -> {tcp, Socket, <<2:8, Version:16>>} ->
ok = zx_daemon:report({use_version, Version}), ok = zx_daemon:report({use_version, Version}),
terminate(); terminate();
{tcp, Socket, <<3:8, Reason:16>>} -> {tcp, Socket, <<3:8, Reason/utf8>>} ->
ok = zx_daemon:report({no_service, Reason}), ok = zx_daemon:report({no_service, Reason}),
terminate(); terminate();
{tcp_closed, Socket} -> {tcp_closed, Socket} ->
handle_unexpected_close() ok = zx_daemon:report(failed),
terminate();
retire ->
ok = zx_net:disconnect(Socket),
ok = zx_daemon:report(retired),
terminate();
stop ->
ok = zx_net:disconnect(Socket),
terminate();
Other ->
log(error, "Received: ~tp", [Other])
after 5000 -> after 5000 ->
handle_timeout(Socket) handle_timeout(Socket)
end. end.
@ -198,11 +217,17 @@ loop(Parent, Debug, Socket) ->
{unsubscribe, Package} -> {unsubscribe, Package} ->
ok = do_unsubscribe(Socket, Package), ok = do_unsubscribe(Socket, Package),
loop(Parent, Debug, Socket); loop(Parent, Debug, Socket);
{tcp_closed, Socket} ->
ok = log(info, "Connection closed unexpectedly."),
ok = zx_daemon:report(disconnected),
terminate();
retire ->
ok = zx_net:disconnect(Socket),
ok = zx_daemon:report(retired),
terminate();
stop -> stop ->
ok = zx_net:disconnect(Socket), ok = zx_net:disconnect(Socket),
terminate(); terminate();
{tcp_closed, Socket} ->
handle_unexpected_close();
Unexpected -> Unexpected ->
ok = log(warning, "Unexpected message: ~160tp", [Unexpected]), ok = log(warning, "Unexpected message: ~160tp", [Unexpected]),
loop(Parent, Debug, Socket) loop(Parent, Debug, Socket)
@ -255,25 +280,25 @@ wait_ok(Socket) ->
dispatch(Socket, ID, Action) -> dispatch(Socket, ID, Action) ->
case Action of case Action of
{list, R} -> {list, R} -> send_query(Socket, 3, R);
send_query(Socket, <<0:1, 3:7, (term_to_binary(R))/binary>>); {list, R, N} -> send_query(Socket, 4, {R, N});
{list, R, N} -> {list, R, N, V} -> send_query(Socket, 4, {R, N, V});
send_query(Socket, <<0:1, 4:7, (term_to_binary({R, N}))/binary>>); {latest, R, N} -> send_query(Socket, 5, {R, N});
{list, R, N, V} -> {latest, R, N, V} -> send_query(Socket, 5, {R, N, V});
send_query(Socket, <<0:1, 4:7, (term_to_binary({R, N, V}))/binary>>); {provides, R, M} -> send_query(Socket, 6, {R, M});
{latest, R, N} -> {list_deps, R, N, V} -> send_query(Socket, 7, {R, N, V});
send_query(Socket, <<0:1, 5:7, (term_to_binary({R, N}))/binary>>); {list_sysops, R} -> send_query(Socket, 8, R);
{latest, R, N, V} -> {fetch, R, N, V} -> fetch(Socket, ID, {R, N, V});
send_query(Socket, <<0:1, 5:7, (term_to_binary({R, N, V}))/binary>>); {keychain, R, K} -> send_query(Socket, 10, {R, K});
{fetch, R, N, V} -> Unexpected ->
make_fetch(Socket, ID, {R, N, V});
_ ->
Message = "Received unexpected request action. ID: ~tp, Action: ~200tp", Message = "Received unexpected request action. ID: ~tp, Action: ~200tp",
log(warning, Message, [ID, Action]) log(warning, Message, [ID, Unexpected])
end. end.
send_query(Socket, Message) -> send_query(Socket, Command, Payload) ->
TermBin = term_to_binary(Payload),
Message = <<0:1, Command:7, TermBin/binary>>,
ok = gen_tcp:send(Socket, Message), ok = gen_tcp:send(Socket, Message),
wait_query(Socket). wait_query(Socket).
@ -298,38 +323,39 @@ pong(Socket) ->
gen_tcp:send(Socket, <<1:1, 0:7>>). gen_tcp:send(Socket, <<1:1, 0:7>>).
-spec make_fetch(Socket, ID, PackageID) -> Result -spec fetch(Socket, ID, PackageID) -> Result
when Socket :: gen_tcp:socket(), when Socket :: gen_tcp:socket(),
ID :: zx_daemon:id(), ID :: zx_daemon:id(),
PackageID :: zx:package_id(), PackageID :: zx:package_id(),
Result :: {done, binary()}. Result :: {done, binary()}
| {error, Reason :: term()}.
%% @private %% @private
%% Download a package to the local cache. %% Download a package to the local cache.
make_fetch(Socket, ID, PackageID) -> fetch(Socket, ID, PackageID) ->
TermBin = term_to_binary(PackageID), PIDB = term_to_binary(PackageID),
Message = <<0:1, 6:7, TermBin/binary>>, Message = <<0:1, 9:7, PIDB/binary>>,
ok = gen_tcp:send(Socket, Message), ok = gen_tcp:send(Socket, Message),
ok = wait_hops(Socket, ID), case wait_hops(Socket, ID, PIDB) of
{ok, Bin} = zx_net:rx(Socket), ok ->
{done, Bin}. {ok, Bin} = zx_net:rx(Socket),
{done, Bin};
Error ->
Error
end.
wait_hops(Socket, ID) -> wait_hops(Socket, ID, PIDB) ->
ok = inet:setopts(Socket, [{active, once}]), ok = inet:setopts(Socket, [{active, once}]),
receive receive
{tcp, Socket, <<0:1, 0:7, 0:8>>} -> {tcp, Socket, <<1:1, 3:7, 0:8, PIDB/binary>>} ->
ok; ok;
{tcp, Socket, <<0:1, 0:7, Distance:8>>} -> {tcp, Socket, <<1:1, 3:7, Distance:8, PIDB/binary>>} ->
ok = zx_daemon:result(ID, {hops, Distance}), ok = zx_daemon:result(ID, {hops, Distance}),
wait_hops(Socket, ID); wait_hops(Socket, ID, PIDB);
{tcp, Socket, <<0:1, 2:7>>} ->
handle_timeout(Socket);
{tcp, Socket, Bin} -> {tcp, Socket, Bin} ->
Reason = zx_net:err_in(Bin), Reason = zx_net:err_in(Bin),
ok = log(error, "Failed in wait_hops/2 with reason: ~tp", [Reason]), {error, Reason}
ok = zx_net:disconnect(Socket),
terminate()
after 60000 -> after 60000 ->
handle_timeout(Socket) handle_timeout(Socket)
end. end.
@ -338,14 +364,6 @@ wait_hops(Socket, ID) ->
%%% Terminal handlers %%% Terminal handlers
-spec handle_unexpected_close() -> no_return().
handle_unexpected_close() ->
ok = log(info, "Connection closed unexpectedly."),
ok = zx_daemon:report(disconnected),
terminate().
-spec handle_timeout(gen_tcp:socket()) -> no_return(). -spec handle_timeout(gen_tcp:socket()) -> no_return().
handle_timeout(Socket) -> handle_timeout(Socket) ->

View File

@ -5,6 +5,7 @@
%%% @end %%% @end
-module(zx_conn_sup). -module(zx_conn_sup).
-vsn("0.2.0").
-behavior(supervisor). -behavior(supervisor).
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").

View File

@ -8,118 +8,53 @@
%%% @end %%% @end
-module(zx_key). -module(zx_key).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0"). -license("GPL-3.0").
-export([ensure_keypair/1, have_key/2, path/2, -export([path/2,
prompt_keygen/1, generate_rsa/1, generate_rsa/1,
load/2, verify/3]). load/2, sign/2, verify/3]).
-include("zx_logger.hrl"). -include("zx_logger.hrl").
%%% Functions %%% Functions
-spec ensure_keypair(zx:key_id()) -> zx:outcome(). -spec path(public | private, zx:key_id()) -> file:filename().
%% @private
%% Check if both the public and private key based on KeyID exists.
ensure_keypair(KeyID = {Realm, KeyName}) -> path(Type, {Realm, KeyHash}) ->
case {have_key(public, KeyID), have_key(private, KeyID)} of Size = byte_size(KeyHash) * 8,
{true, true} -> <<N:Size>> = KeyHash,
true; String = integer_to_list(N, 36),
{false, true} -> Name =
Format = "Public key ~ts/~ts cannot be found", case Type of
Message = io_lib:format(Format, [Realm, KeyName]), public -> String ++ ".pub.der";
{error, Message, 2}; private -> String ++ ".key.der"
{true, false} -> end,
Format = "Private key ~ts/~ts cannot be found", zx_lib:path(key, Realm, Name).
Message = io_lib:format(Format, [Realm, KeyName]),
{error, Message, 2};
{false, false} ->
Format = "Key pair ~ts/~ts cannot be found",
Message = io_lib:format(Format, [Realm, KeyName]),
{error, Message, 2}
end.
-spec have_key(Type, KeyID) -> boolean()
when Type :: public | private,
KeyID :: zx:key_id().
%% @private
%% Determine whether the indicated key is present.
have_key(Type, KeyID) ->
filelib:is_regular(path(Type, KeyID)).
-spec path(Type, KeyID) -> Path
when Type :: public | private,
KeyID :: zx:key_id(),
Path :: file:filename().
%% @private
%% Given KeyID, return the path to the key type indicated.
path(public, {Realm, KeyName}) ->
filename:join(zx_lib:path(key, Realm), KeyName ++ ".pub.der");
path(private, {Realm, KeyName}) ->
filename:join(zx_lib:path(key, Realm), KeyName ++ ".key.der").
%%% Key generation %%% Key generation
-spec prompt_keygen(zx:user_id()) -> zx:key_name().
%% @private
%% Prompt the user for a valid KeyPrefix to use for naming a new RSA keypair.
prompt_keygen(UserID = {Realm, UserName}) -> -spec generate_rsa(Owner) -> Result
Message = when Owner :: zx:realm() | zx:user_id(),
"~nKEY NAME~n" Result :: {ok, zx:key_hash()}
"Enter a name for your new key pair.~n" | {error, keygen_fail}.
"Valid names must start with a lower-case letter, and can include "
"only lower-case letters, numbers, and underscores, but no series of "
"consecutive underscores. (That is: [a-z0-9_])~n"
" Example: my_key~n",
ok = io:format(Message),
KeyTag = zx_tty:get_input(),
case zx_lib:valid_lower0_9(KeyTag) of
true ->
KeyName = UserName ++ "-" ++ KeyTag,
ok = zx_key:generate_rsa({Realm, KeyName}),
KeyName;
false ->
ok = io:format("Bad key name ~ts. Try again.~n", [KeyTag]),
prompt_keygen(UserID)
end.
-spec generate_rsa(KeyID) -> Result
when KeyID :: zx:key_id(),
Result :: ok
| {error, Reason},
Reason :: keygen_fail
| exists.
%% @private %% @private
%% Generate an RSA keypair and write them in der format to the current directory, using %% Generate an RSA keypair and write them in der format to the current directory, using
%% filenames derived from Prefix. %% filenames derived from Prefix.
%% NOTE: The current version of this command is likely to only work on a unix system. %% NOTE: The current version of this command is likely to only work on a unix system.
generate_rsa(KeyID = {Realm, KeyName}) -> generate_rsa(Owner) ->
BaseName = filename:join(zx_lib:path(key, Realm), KeyName), {ok, TmpDir} = zx_lib:mktemp_dir({"otpr", "zx"}),
Pattern = BaseName ++ ".*.der", PemFile = filename:join(TmpDir, "zx-tmp.pem"),
case filelib:wildcard(Pattern) of PubFile = filename:join(TmpDir, "zx-tmp.pub.der"),
[] -> generate_rsa(KeyID, BaseName); KeyFile = filename:join(TmpDir, "zx-tmp.key.der"),
_ -> {error, exists} ok = tell("Generating keys. Please be patient..."),
end.
generate_rsa(KeyID, BaseName) ->
PemFile = BaseName ++ ".pub.pem",
KeyFile = path(private, KeyID),
PubFile = path(public, KeyID),
ok = log(info, "Generating ~s and ~s. Please be patient...", [KeyFile, PubFile]),
case gen_p_key(KeyFile) of case gen_p_key(KeyFile) of
ok -> ok ->
ok = der_to_pem(KeyFile, PemFile), ok = der_to_pem(KeyFile, PemFile),
@ -128,17 +63,32 @@ generate_rsa(KeyID, BaseName) ->
Pub = public_key:pem_entry_decode(PemData), Pub = public_key:pem_entry_decode(PemData),
PubDer = public_key:der_encode('RSAPublicKey', Pub), PubDer = public_key:der_encode('RSAPublicKey', Pub),
ok = file:write_file(PubFile, PubDer), ok = file:write_file(PubFile, PubDer),
case check_key(KeyFile, PubFile) of generate_rsa2(Owner, PemFile, KeyFile, PubFile);
true ->
ok = file:delete(PemFile),
log(info, "~ts and ~ts agree", [KeyFile, PubFile]);
false ->
ok = lists:foreach(fun file:delete/1, [PemFile, KeyFile, PubFile]),
ok = log(error, "Something has gone wrong."),
{error, keygen_fail}
end;
{error, no_ssl} -> {error, no_ssl} ->
ok = log(error, "OpenSSL not found."), ok = tell(error, "OpenSSL not found."),
{error, keygen_fail}
end.
generate_rsa2(Owner, PemFile, KeyFile, PubFile) ->
{ok, PubBin} = file:read_file(PubFile),
{ok, KeyBin} = file:read_file(KeyFile),
Pub = public_key:der_decode('RSAPublicKey', PubBin),
Key = public_key:der_decode('RSAPrivateKey', KeyBin),
TestMessage = <<"Some test data to sign.">>,
Signature = public_key:sign(TestMessage, sha512, Key),
case public_key:verify(TestMessage, sha512, Signature, Pub) of
true ->
ok = tell(info, "~ts and ~ts agree", [KeyFile, PubFile]),
PubHash = crypto:hash(sha512, PubBin),
KeyHash = crypto:hash(sha512, KeyBin),
PairHash = crypto:hash(sha512, <<PubHash/binary, KeyHash/binary>>),
KeyData = {PairHash, {none, PubBin}, {none, KeyBin}},
ok = zx_daemon:register_key(Owner, KeyData),
ok = zx_lib:rm_rf(filename:dirname(KeyFile)),
{ok, PairHash};
false ->
ok = lists:foreach(fun file:delete/1, [PemFile, KeyFile, PubFile]),
ok = tell(error, "Something has gone wrong."),
{error, keygen_fail} {error, keygen_fail}
end. end.
@ -196,23 +146,6 @@ der_to_pem(KeyFile, PemFile) ->
end. end.
-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() -> Result -spec openssl() -> Result
when Result :: {ok, Executable} when Result :: {ok, Executable}
| {error, no_ssl}, | {error, no_ssl},
@ -230,11 +163,11 @@ openssl() ->
end, end,
case os:find_executable(OpenSSL) of case os:find_executable(OpenSSL) of
false -> false ->
ok = log(error, "OpenSSL could not be found in this system's PATH."), M = "OpenSSL not foud in PATH. Install OpenSSL or add to path and retry.",
ok = log(error, "Install OpenSSL and then retry."), ok = tell(error, M),
{error, no_ssl}; {error, no_ssl};
Path -> Path ->
log(info, "OpenSSL executable found at: ~ts", [Path]), ok = tell("OpenSSL executable found at: ~ts", [Path]),
{ok, OpenSSL} {ok, OpenSSL}
end. end.
@ -260,6 +193,15 @@ load(Type, KeyID) ->
end. end.
-spec sign(Data, Key) -> Signature
when Data :: binary(),
Key :: public_key:rsa_private_key(),
Signature :: boolean().
sign(Data, Key) ->
public_key:sign(Data, sha512, Key).
-spec verify(Data, Signature, PubKey) -> boolean() -spec verify(Data, Signature, PubKey) -> boolean()
when Data :: binary(), when Data :: binary(),
Signature :: binary(), Signature :: binary(),

View File

@ -10,13 +10,15 @@
%%% @end %%% @end
-module(zx_lib). -module(zx_lib).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0"). -license("GPL-3.0").
-export([zomp_dir/0, find_zomp_dir/0, -export([zomp_dir/0, find_zomp_dir/0,
path/1, path/2, path/3, path/4, ppath/2, path/1, path/2, path/3, path/4, ppath/2,
force_dir/1, mktemp_dir/1, new_logpath/1, userconf/1,
force_dir/1, mktemp_dir/1, random_string/0,
list_realms/0, realm_exists/1, list_realms/0, realm_exists/1,
get_prime/1, realm_meta/1, get_prime/1, realm_meta/1,
read_project_meta/0, read_project_meta/1, read_package_meta/1, read_project_meta/0, read_project_meta/1, read_package_meta/1,
@ -26,10 +28,12 @@
string_to_version/1, version_to_string/1, string_to_version/1, version_to_string/1,
package_id/1, package_string/1, package_id/1, package_string/1,
zsp_name/1, zsp_path/1, zsp_name/1, zsp_path/1,
print_user/1,
find_latest_compatible/2, installed/1, find_latest_compatible/2, installed/1,
realm_conf/1, load_realm_conf/1, realm_conf/1, load_realm_conf/1,
build/0, build/0,
rm_rf/1, rm/1, rm_rf/1, rm/1,
enqueue_unique/2,
time_diff/2, elapsed_time/1, time_diff/2, elapsed_time/1,
b_to_t/1, b_to_ts/1]). b_to_t/1, b_to_ts/1]).
@ -64,7 +68,7 @@ find_zomp_dir() ->
case os:type() of case os:type() of
{unix, _} -> {unix, _} ->
Home = os:getenv("HOME"), Home = os:getenv("HOME"),
Dir = ".zomp", Dir = "zomp",
filename:join(Home, Dir); filename:join(Home, Dir);
{win32, _} -> {win32, _} ->
Home = os:getenv("LOCALAPPDATA"), Home = os:getenv("LOCALAPPDATA"),
@ -113,11 +117,34 @@ path(Type, Realm, Name, Version) ->
-spec ppath(core_dir(), zx:package_id()) -> file:filename(). -spec ppath(core_dir(), zx:package_id()) -> file:filename().
%% @private %% @private
%% An alias for path/4, but more convenient when needing a path from a closed %% An alias for path/3,4, but more convenient when needing a path from a closed
%% package_id(). %% package_id().
ppath(Type, {Realm, Name, {z, z, z}}) ->
path(Type, Realm, Name);
ppath(Type, {Realm, Name, Version}) -> ppath(Type, {Realm, Name, Version}) ->
path(Type, Realm, Name, Version). path(Type, Realm, Name, Version);
ppath(Type, {Realm, Name}) ->
path(Type, Realm, Name).
-spec new_logpath(zx:package_id()) -> file:filename().
new_logpath(PackageID = {Realm, Name, _}) ->
Dir = path(log, Realm, Name),
ok = force_dir(Dir),
{{Year, Month, Day}, {Hour, Minute, Second}} = calendar:universal_time(),
Format = "~4..0w~2..0w~2..0w_~2..0w~2..0w~2..0w",
Timestamp = io_lib:format(Format, [Year, Month, Day, Hour, Minute, Second]),
{ok, PackageString} = package_string(PackageID),
FileName = string:join([Timestamp, PackageString, "log"], "."),
filename:join(Dir, FileName).
-spec userconf(zx:user_id()) -> file:filename().
userconf({Realm, UserName}) ->
filename:join(path(etc, Realm), UserName ++ ".user").
-spec force_dir(Path) -> Result -spec force_dir(Path) -> Result
@ -141,14 +168,20 @@ force_dir(Path) ->
| {error, Reason :: file:posix()}. | {error, Reason :: file:posix()}.
mktemp_dir({Realm, Name}) -> mktemp_dir({Realm, Name}) ->
Rand = integer_to_list(binary:decode_unsigned(crypto:strong_rand_bytes(8)), 36), Rand = random_string(),
TempDir = filename:join(path(etc, Realm, Name), Rand), TempDir = filename:join(path(tmp, Realm, Name), Rand),
case force_dir(TempDir) of case force_dir(TempDir) of
ok -> {ok, TempDir}; ok -> {ok, TempDir};
Error -> Error Error -> Error
end. end.
-spec random_string() -> string().
random_string() ->
integer_to_list(binary:decode_unsigned(crypto:strong_rand_bytes(8)), 36).
-spec list_realms() -> [zx:realm()]. -spec list_realms() -> [zx:realm()].
%% @private %% @private
%% Check the filesystem for etc/[Realm Name]/realm.conf files. %% Check the filesystem for etc/[Realm Name]/realm.conf files.
@ -546,9 +579,9 @@ package_string(_) ->
{error, invalid_package_id}. {error, invalid_package_id}.
-spec zsp_name(PackageID) -> ZrpFileName -spec zsp_name(PackageID) -> ZspFileName
when PackageID :: zx:package_id(), when PackageID :: zx:package_id(),
ZrpFileName :: file:filename(). ZspFileName :: file:filename().
%% @private %% @private
%% Map a PackageID to its correct .zsp package file name. %% Map a PackageID to its correct .zsp package file name.
@ -563,6 +596,12 @@ zsp_path(PackageID = {Realm, _, _}) ->
filename:join(path(zsp, Realm), zsp_name(PackageID)). filename:join(path(zsp, Realm), zsp_name(PackageID)).
-spec print_user({zx:user_name(), zx:real_name(), [zx:contact_info()]}) -> ok.
print_user({UserName, RealName, [{"email", Email}]}) ->
io:format("~ts (~ts <~ts>) ~n", [UserName, RealName, Email]).
-spec find_latest_compatible(Version, Versions) -> Result -spec find_latest_compatible(Version, Versions) -> Result
when Version :: zx:version(), when Version :: zx:version(),
Versions :: [zx:version()], Versions :: [zx:version()],
@ -582,6 +621,8 @@ find_latest_compatible(Version, Versions) ->
latest_compatible(Version, Descending). latest_compatible(Version, Descending).
latest_compatible(_, []) ->
not_found;
latest_compatible({z, z, z}, Versions) -> latest_compatible({z, z, z}, Versions) ->
{ok, hd(Versions)}; {ok, hd(Versions)};
latest_compatible({X, z, z}, Versions) -> latest_compatible({X, z, z}, Versions) ->
@ -607,7 +648,7 @@ latest_compatible(Version, Versions) ->
%% True to its name, tells whether a package's install directory is found. %% True to its name, tells whether a package's install directory is found.
installed(PackageID) -> installed(PackageID) ->
filelib:is_dir(path(lib, PackageID)). filelib:is_dir(ppath(lib, PackageID)).
-spec realm_conf(Realm) -> Path -spec realm_conf(Realm) -> Path
@ -665,25 +706,38 @@ build() ->
ok. ok.
-spec rm_rf(file:filename()) -> ok | {error, file:posix()}. -spec rm_rf(Target) -> Result
when Target :: file:filename(),
Result :: ok | {error, file:posix()}.
%% @private %% @private
%% Recursively remove files and directories. Equivalent to `rm -rf'. %% Recursively remove files and directories. Equivalent to `rm -rf'.
%% Does not return an error on a nonexistant path. %% Does not return an error on a nonexistant path.
rm_rf(Path) -> rm_rf(Target) ->
case filelib:is_dir(Path) of case filelib:is_dir(Target) of
true -> true ->
Pattern = filename:join(Path, "**"), Pattern = filename:join(Target, "**"),
Contents = lists:reverse(lists:sort(filelib:wildcard(Pattern))), Contents = lists:reverse(lists:sort(filelib:wildcard(Pattern))),
ok = lists:foreach(fun rm/1, Contents), Targets = rm_filter(Contents),
file:del_dir(Path); ok = lists:foreach(fun rm/1, Targets),
case file:list_dir(Target) of
{ok, []} -> file:del_dir(Target);
_ -> ok
end;
false -> false ->
case filelib:is_regular(Path) of case filelib:is_regular(Target) of
true -> file:delete(Path); true -> file:delete(Target);
false -> ok false -> ok
end end
end. end.
rm_filter(Contents) ->
P1 = path(lib, "otpr", "zx"),
P2 = path(lib, "otpr", "zomp"),
F1 = fun(C) -> not lists:prefix(P1, C) end,
F2 = fun(C) -> not lists:prefix(P2, C) end,
lists:filter(F2, lists:filter(F1, Contents)).
-spec rm(file:filename()) -> ok | {error, file:posix()}. -spec rm(file:filename()) -> ok | {error, file:posix()}.
%% @private %% @private
@ -696,6 +750,15 @@ rm(Path) ->
end. end.
-spec enqueue_unique(term(), queue:queue()) -> queue:queue().
enqueue_unique(Term, Queue) ->
case queue:member(Term, Queue) of
true -> Queue;
false -> queue:in(Term, Queue)
end.
-spec time_diff(Before, After) -> Diff -spec time_diff(Before, After) -> Diff
when Before :: calendar:datetime(), when Before :: calendar:datetime(),
After :: calendar:datetime(), After :: calendar:datetime(),

View File

@ -5,6 +5,7 @@
%%% @end %%% @end
-module(zx_net). -module(zx_net).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0"). -license("GPL-3.0").
@ -170,6 +171,8 @@ rx(Socket, Timeout) ->
%% @doc %% @doc
%% Abstract large receives with a fixed timeout between segments and progress update %% Abstract large receives with a fixed timeout between segments and progress update
%% messages to listening processes. %% messages to listening processes.
%% NOTE: The gen_tcp:send/2 on the second line of this function mimics the behavior of
%% the {packet, 4} option which is standard outside of bulk RX/TX.
rx(Socket, Timeout, Watchers) -> rx(Socket, Timeout, Watchers) ->
ok = inet:setopts(Socket, [{active, once}, {packet, 0}]), ok = inet:setopts(Socket, [{active, once}, {packet, 0}]),
@ -230,7 +233,8 @@ err_ex(bad_auth) -> <<0:1, 15:7>>;
err_ex(unauthorized_key) -> <<0:1, 16:7>>; err_ex(unauthorized_key) -> <<0:1, 16:7>>;
err_ex(already_exists) -> <<0:1, 17:7>>; err_ex(already_exists) -> <<0:1, 17:7>>;
err_ex(busy) -> <<0:1, 18:7>>; err_ex(busy) -> <<0:1, 18:7>>;
err_ex({retry, Seconds}) -> <<0:1, 19:7, Seconds:24>>; err_ex(not_sysop) -> <<0:1, 19:7>>;
err_ex({retry, Seconds}) -> <<0:1, 20:7, Seconds:24>>;
err_ex(Reason) -> [<<0:1, 127:7>>, io_lib:format("~tw", [Reason])]. err_ex(Reason) -> [<<0:1, 127:7>>, io_lib:format("~tw", [Reason])].
@ -252,5 +256,6 @@ err_in(<<0:1, 15:7>>) -> bad_auth;
err_in(<<0:1, 16:7>>) -> unauthorized_key; err_in(<<0:1, 16:7>>) -> unauthorized_key;
err_in(<<0:1, 17:7>>) -> already_exists; err_in(<<0:1, 17:7>>) -> already_exists;
err_in(<<0:1, 18:7>>) -> busy; err_in(<<0:1, 18:7>>) -> busy;
err_in(<<0:1, 19:7, Seconds:24>>) -> {retry, Seconds}; err_in(<<0:1, 19:7>>) -> not_sysop;
err_in(<<0:1, 20:7, Seconds:24>>) -> {retry, Seconds};
err_in(<<0:1, 127:7, Reason/binary>>) -> unicode:characters_to_list(Reason). err_in(<<0:1, 127:7, Reason/binary>>) -> unicode:characters_to_list(Reason).

View File

@ -0,0 +1,265 @@
%%% @doc
%%% ZX Peer
%%%
%%% A process that handles connections from local ZX instances.
%%% These act as client processes within the local node, shuttling requests from
%%% other nodes to the zx_daemon, and receiving return responses and passing them
%%% back over the local socket.
%%% @end
-module(zx_peer).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([notify/3, takeover/2]).
-export([start/1]).
-export([start_link/1, init/2]).
-export([system_continue/3, system_terminate/4,
system_get_state/1, system_replace_state/2]).
-include("zx_logger.hrl").
%%% Type and Record Definitions
-record(s, {socket = none :: none | gen_tcp:socket()}).
-type state() :: #s{}.
%%% Service Interface
-spec notify(Pid, Channel, Message) -> ok
when Pid :: pid(),
Channel :: term(),
Message :: term().
notify(Pid, Channel, Message) ->
Pid ! {z_sub, Channel, Message},
ok.
-spec takeover(Pid, ID) -> ok | timeout
when Pid :: pid(),
ID :: zx_daemon:id().
takeover(Pid, ID) ->
Ref = make_ref(),
Pid ! {takeover, Ref, ID},
receive
{Ref, ok} -> ok
after 1000 -> timeout
end.
-spec start(ListenSocket) -> Result
when ListenSocket :: gen_tcp:socket(),
Result :: {ok, pid()}
| {error, Reason},
Reason :: {already_started, pid()}
| {shutdown, term()}
| term().
start(ListenSocket) ->
zx_peer_sup:start_acceptor(ListenSocket).
-spec start_link(ListenSocket) -> Result
when ListenSocket :: gen_tcp:socket(),
Result :: {ok, pid()}
| {error, Reason},
Reason :: {already_started, pid()}
| {shutdown, term()}
| term().
start_link(ListenSocket) ->
proc_lib:start_link(?MODULE, init, [self(), ListenSocket]).
-spec init(Parent, ListenSocket) -> no_return()
when Parent :: pid(),
ListenSocket :: gen_tcp:socket().
init(Parent, ListenSocket) ->
Debug = sys:debug_options([]),
ok = proc_lib:init_ack(Parent, {ok, self()}),
listen(Parent, Debug, ListenSocket).
-spec listen(Parent, Debug, ListenSocket) -> no_return()
when Parent :: pid(),
Debug :: [sys:dbg_opt()],
ListenSocket :: gen_tcp:socket().
%% @private
%% This function waits for a TCP connection. The owner of the socket is still
%% the zx_peer_man (so it can close it on a call to zx_peer_man:ignore/0),
%% but the only one calling gen_tcp:accept/1 on it is this process. Closing the socket
%% is one way a manager process can gracefully unblock child workers that are blocking
%% on a network accept.
%%
%% Once it makes a TCP connection it will call start/1 to spawn its successor.
listen(Parent, Debug, ListenSocket) ->
case gen_tcp:accept(ListenSocket) of
{ok, Socket} ->
{ok, _} = start(ListenSocket),
State = #s{socket = Socket},
loop(Parent, Debug, State);
{error, closed} ->
exit(normal)
end.
-spec loop(Parent, Debug, State) -> no_return()
when Parent :: pid(),
Debug :: [sys:dbg_opt()],
State :: state().
loop(Parent, Debug, State = #s{socket = Socket}) ->
receive
{tcp, Socket, Bin} ->
Result = handle_message(Bin),
ok = gen_tcp:send(Socket, Result),
loop(Parent, Debug, State);
{result, ID, Result} ->
Bin = term_to_binary({ID, Result}),
Message = <<0:8, Bin/binary>>,
ok = gen_tcp:send(Socket, Message),
loop(Parent, Debug, State);
{z_sub, Channel, Message} ->
Bin = term_to_binary({Channel, Message}),
Message = <<1:1, 1:7, Bin/binary>>,
ok = gen_tcp:send(Socket, Message),
loop(Parent, Debug, State);
{takeover, Ref, ID} ->
ok = gen_tcp:send(Socket, <<1:1, 1:7, ID:32>>),
zx_peer_man ! {Ref, ok},
loop(Parent, Debug, State);
{new_proxy, Port} ->
Message = <<2:8, Port:16>>,
ok = gen_tcp:send(Socket, Message),
ok = zx_net:disconnect(Socket),
exit(normal);
{tcp_closed, Socket} ->
exit(normal);
{system, From, Request} ->
sys:handle_system_msg(Request, From, Parent, ?MODULE, Debug, State);
Unexpected ->
ok = log(warning, "~p Unexpected message: ~tp", [self(), Unexpected]),
loop(Parent, Debug, State)
end.
handle_message(<<Command:8, Bin/binary>>) ->
Payload = binary_to_term(Bin, [safe]),
Result =
case Command of
1 -> zx_daemon:subscribe(Payload);
2 -> zx_daemon:unsubscribe(Payload);
3 -> deferred(fun list/1, Payload);
4 -> deferred(fun zx_daemon:latest/1, Payload);
5 -> deferred(fun provides/1, Payload);
6 -> deferred(fun zx_daemon:list_deps/1, Payload);
7 -> deferred(fun zx_daemon:list_sysops/1, Payload);
8 -> deferred(fun zx_daemon:fetch/1, Payload);
9 -> zx_daemon:install(Payload);
10 -> zx_daemon:build(Payload);
11 -> zx_daemon:list_mirrors();
12 -> zx_daemon:add_mirror(Payload);
13 -> zx_daemon:drop_mirror(Payload);
14 -> register_key(Payload);
15 -> get_key(Payload);
16 -> keybin(Payload);
17 -> zx_daemon:find_keypair(Payload);
18 -> have_key(Payload);
19 -> list_keys(Payload);
20 -> zx_daemon:takeover(Payload);
21 -> zx_daemon:abdicate(Payload);
22 -> zx_daemon:drop_realm(Payload);
23 -> deferred(fun zx_daemon:keychain/1, Payload)
end,
pack(Result).
deferred(Query, Payload) ->
{ok, ID} = Query(Payload),
receive
{result, ID, Result} -> Result
after 5000 -> {error, timeout}
end.
pack(ok) -> <<0:8>>;
pack({ok, Result}) -> <<0:8, (term_to_binary(Result))/binary>>;
pack({error, Reason}) -> zx_net:err_ex(Reason);
pack(done) -> <<0:8>>.
list({R, N, V}) -> zx_daemon:list(R, N, V);
list({R, N}) -> zx_daemon:list(R, N);
list(R) -> zx_daemon:list(R).
provides({R, M}) -> zx_daemon:provides(R, M).
register_key({O, D}) -> zx_daemon:register_key(O, D).
get_key({T, K}) -> zx_daemon:get_key(T, K).
keybin({T, K}) -> zx_daemon:keybin(T, K).
have_key({T, K}) -> zx_daemon:have_key(T, K).
list_keys({T, O}) -> zx_daemon:list_keys(T, O).
%%% OTP System Message Handling
-spec system_continue(Parent, Debug, State) -> no_return()
when Parent :: pid(),
Debug :: [sys:dbg_opt()],
State :: state().
%% @private
%% The function called by the OTP internal functions after a system message has been
%% handled. If the worker process has several possible states this is one place
%% resumption of a specific state can be specified and dispatched.
system_continue(Parent, Debug, State) ->
loop(Parent, Debug, State).
-spec system_terminate(Reason, Parent, Debug, State) -> no_return()
when Reason :: term(),
Parent :: pid(),
Debug :: [sys:dbg_opt()],
State :: state().
%% @private
%% Called by the OTP inner bits to allow the process to terminate gracefully.
%% Exactly when and if this is callback gets called is specified in the docs:
%% See: http://erlang.org/doc/design_principles/spec_proc.html#msg
system_terminate(Reason, _Parent, _Debug, _State) ->
exit(Reason).
-spec system_get_state(State) -> {ok, State}
when State :: state().
%% @private
%% This function allows the runtime (or anything else) to inspect the running state
%% of the worker process at any arbitrary time.
system_get_state(State) -> {ok, State}.
-spec system_replace_state(StateFun, State) -> {ok, NewState, State}
when StateFun :: fun(),
State :: state(),
NewState :: term().
%% @private
%% This function allows the system to update the process state in-place. This is most
%% useful for state transitions between code types, like when performing a hot update
%% (very cool, but sort of hard) or hot patching a running system (living on the edge!).
system_replace_state(StateFun, State) ->
{ok, StateFun(State), State}.

View File

@ -0,0 +1,307 @@
%%% @doc
%%% ZX Peer Manager
%%%
%%% Manages the peer connection aggregation subsystem for ZX.
%%% When ZX nodes need to connec to to get data from upstream Zomp nodes they proxy
%%% their connections through whatever ZX nodes is already providing this service
%%% locally. In addition to aggregating network resource usage, ZX also aggregates
%%% it also sequentializes (and effectively atomizes) local disk operations.
%%% @end
-module(zx_peer_man).
-vsn("0.2.0").
-behavior(gen_server).
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([listen/0, ignore/0, retire/1]).
-export([enroll/0, broadcast/2]).
-export([start_link/0]).
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
code_change/3, terminate/2]).
-include("zx_logger.hrl").
%%% Type and Record Definitions
-record(s, {listener = none :: none | gen_tcp:socket(),
secondary = none :: none | pid(),
peers = [] :: [{reference(), pid()}]}).
-type state() :: #s{}.
%%% Service Interface
-spec listen() -> Result
when Result :: {ok, inet:port_number()}
| error.
%% @doc
%% Tell the service to start listening. The port number selection here is left up
%% to the host OS, so when it is determined then the number will be returned to the
%% caller (should always be zx_daemon calling). There shouldn't be any reasons why
%% this call should fail, so zx_daemon is expecting it to always succeed and errors
%% are not specified.
listen() ->
gen_server:call(?MODULE, listen).
-spec ignore() -> ok.
%% @doc
%% Tell the service to stop listening.
%% It is not an error to call this function when the service is not listening.
ignore() ->
gen_server:cast(?MODULE, ignore).
-spec retire(ID) -> ok | no_peers
when ID :: integer().
retire(ID) ->
gen_server:call(?MODULE, {retire, ID}).
-spec enroll() -> ok.
%% @private
%% zx_peer processes have to enroll themselves so that the zx_peer_man can monitor them
%% and know which one has been alive the longest. In the event that this node retires
%% or goes down it will need to designate a successor. Because there is no guarantee
%% that any of the code being executed by ZX is reliable (and may be calling halt(N)
%% or any other hard shutdown functions or breaks), successor designation occurs
%% pre-emptively and not just on shutdown.
enroll() ->
gen_server:cast(?MODULE, {enroll, self()}).
-spec broadcast(Channel, Message) -> ok
when Channel :: term(),
Message :: term().
broadcast(Channel, Message) ->
gen_server:cast(?MODULE, {broadcast, Channel, Message}).
%%% Startup Functions
-spec start_link() -> Result
when Result :: {ok, pid()}
| {error, Reason :: term()}.
%% @private
%% This should only ever be called by zx_peers (the service-level supervisor).
start_link() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, none, []).
-spec init(none) -> {ok, state()}.
%% @private
%% Called by the supervisor process to give the process a chance to perform any
%% preparatory work necessary for proper function.
init(none) ->
State = #s{},
{ok, State}.
%%% gen_server Message Handling Callbacks
-spec handle_call(Message, From, State) -> Result
when Message :: term(),
From :: {pid(), reference()},
State :: state(),
Result :: {reply, Response, NewState}
| {noreply, State},
Response :: ok
| {error, {listening, inet:port_number()}},
NewState :: state().
%% @private
%% The gen_server:handle_call/3 callback.
%% See: http://erlang.org/doc/man/gen_server.html#Module:handle_call-3
handle_call(listen, _, State) ->
{Response, NewState} = do_listen(State),
{reply, Response, NewState};
handle_call({retire, ID}, _, State) ->
Result = do_retire(ID, State),
{reply, Result, State};
handle_call(Unexpected, From, State) ->
ok = io:format("~p Unexpected call from ~tp: ~tp~n", [self(), From, Unexpected]),
{noreply, State}.
-spec handle_cast(Message, State) -> {noreply, NewState}
when Message :: term(),
State :: state(),
NewState :: state().
%% @private
%% The gen_server:handle_cast/2 callback.
%% See: http://erlang.org/doc/man/gen_server.html#Module:handle_cast-2
handle_cast({enroll, Pid}, State) ->
NewState = do_enroll(Pid, State),
{noreply, NewState};
handle_cast({broadcast, Channel, Message}, State) ->
ok = do_broadcast(Channel, Message, State),
{noreply, State};
handle_cast(ignore, State) ->
NewState = do_ignore(State),
{noreply, NewState};
handle_cast(Unexpected, State) ->
ok = io:format("~p Unexpected cast: ~tp~n", [self(), Unexpected]),
{noreply, State}.
-spec handle_info(Message, State) -> {noreply, NewState}
when Message :: term(),
State :: state(),
NewState :: state().
%% @private
%% The gen_server:handle_info/2 callback.
%% See: http://erlang.org/doc/man/gen_server.html#Module:handle_info-2
handle_info({'DOWN', Mon, process, Pid, Info}, State) ->
NewState = handle_down(Mon, Pid, Info, State),
{noreply, NewState};
handle_info(Unexpected, State) ->
ok = io:format("~p Unexpected info: ~tp~n", [self(), Unexpected]),
{noreply, State}.
%%% OTP Service Functions
-spec code_change(OldVersion, State, Extra) -> Result
when OldVersion :: {down, Version} | Version,
Version :: term(),
State :: state(),
Extra :: term(),
Result :: {ok, NewState}
| {error, Reason :: term()},
NewState :: state().
%% @private
%% The gen_server:code_change/3 callback.
%% See: http://erlang.org/doc/man/gen_server.html#Module:code_change-3
code_change(_, State, _) ->
{ok, State}.
-spec terminate(Reason, State) -> no_return()
when Reason :: normal
| shutdown
| {shutdown, term()}
| term(),
State :: state().
%% @private
%% The gen_server:terminate/2 callback.
%% See: http://erlang.org/doc/man/gen_server.html#Module:terminate-2
terminate(_, _) ->
ok.
%%% Doer Functions
-spec do_listen(State) -> {Result, NewState}
when State :: state(),
Result :: {ok, inet:port_number()}
| error,
NewState :: state().
%% @private
%% The "doer" procedure called when a "listen" message is received.
do_listen(State = #s{listener = none}) ->
Options =
[inet6,
{ip, {0,0,0,0,0,0,0,1}},
{active, true},
{mode, binary},
{keepalive, true},
{reuseaddr, true},
{packet, 4}],
{ok, Listener} = gen_tcp:listen(0, Options),
{ok, Port} = inet:port(Listener),
{ok, _} = zx_peer:start(Listener),
{{ok, Port}, State#s{listener = Listener}};
do_listen(State) ->
ok = log(warning, "Already listening."),
{error, State}.
-spec do_enroll(Pid, State) -> NewState
when Pid :: pid(),
State :: state(),
NewState :: state().
do_enroll(Pid, State = #s{peers = []}) ->
ok = zx_peer:become_secondary(Pid),
Mon = monitor(process, Pid),
State#s{secondary = Pid, peers = [{Mon, Pid}]};
do_enroll(Pid, State = #s{peers = Peers}) ->
Mon = monitor(process, Pid),
State#s{peers = [{Mon, Pid} | Peers]}.
do_broadcast(Channel, Message, #s{peers = Peers}) ->
Notify = fun({_, Pid}) -> zx_peer:notify(Pid, Channel, Message) end,
lists:foreach(Notify, Peers).
-spec handle_down(Mon, Pid, Info, State) -> NewState
when Mon :: reference(),
Pid :: pid(),
Info :: term(),
State :: state(),
NewState :: state().
handle_down(Mon, Pid, Info, State = #s{secondary = Pid, peers = Peers}) ->
Peer = {Mon, Pid},
ok = log(info, "Secondary peer ~p retired with ~tp.", [Pid, Info]),
case lists:delete(Peer, Peers) of
[] ->
State#s{secondary = none, peers = []};
NewPeers ->
{_, NextPid} = tl(NewPeers),
ok = zx_peer:become_secondary(NextPid),
State#s{secondary = NextPid, peers = NewPeers}
end;
handle_down(Mon, Pid, Info, State = #s{peers = Peers}) ->
Peer = {Mon, Pid},
case lists:member(Peer, Peers) of
true ->
ok = log(info, "Peer ~p retired.", [Pid]),
State#s{peers = lists:delete(Peer, Peers)};
false ->
Unexpected = {'DOWN', Mon, process, Pid, Info},
ok = log(warning, "Unexpected info: ~160tp", [Unexpected]),
State
end.
-spec do_ignore(State) -> NewState
when State :: state(),
NewState :: state().
%% @private
%% The "doer" procedure called when an "ignore" message is received.
do_ignore(State = #s{listener = none}) ->
State;
do_ignore(State = #s{listener = Listener}) ->
ok = gen_tcp:close(Listener),
State#s{listener = none}.
do_retire(_, #s{secondary = none}) -> halt;
do_retire(ID, #s{secondary = Pid}) -> zx_peer:takeover(Pid, ID).

View File

@ -0,0 +1,61 @@
%%% @doc
%%% ZX Peer Supervisor
%%%
%%% This process supervises the peer socket handlers themselves. It is a peer of the
%%% zx_peer_man, and a child of the supervisor named zx_peers.
%%% @end
-module(zx_peer_sup).
-vsn("0.2.0").
-behaviour(supervisor).
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([start_acceptor/1]).
-export([start_link/0]).
-export([init/1]).
-spec start_acceptor(ListenSocket) -> Result
when ListenSocket :: gen_tcp:socket(),
Result :: {ok, pid()}
| {error, Reason},
Reason :: {already_started, pid()}
| {shutdown, term()}
| term().
%% @private
%% Spawns the first listener at the request of the zx_peer_man when es:listen/1
%% is called, or the next listener at the request of the currently listening zx_peer
%% when a connection is made.
%%
%% Error conditions, supervision strategies and other important issues are
%% explained in the supervisor module docs:
%% http://erlang.org/doc/man/supervisor.html
start_acceptor(ListenSocket) ->
supervisor:start_child(?MODULE, [ListenSocket]).
-spec start_link() -> {ok, pid()}.
%% @private
%% This supervisor's own start function.
start_link() ->
supervisor:start_link({local, ?MODULE}, ?MODULE, none).
-spec init(none) -> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
%% @private
%% The OTP init/1 function.
init(none) ->
RestartStrategy = {simple_one_for_one, 1, 60},
Peer = {zx_peer,
{zx_peer, start_link, []},
temporary,
brutal_kill,
worker,
[zx_peer]},
{ok, {RestartStrategy, [Peer]}}.

View File

@ -0,0 +1,49 @@
%%% @doc
%%% ZX Peer Service Supervisor
%%%
%%% The service-level supervisor of the peer subsystem.
%%% The peer subsystem makes sure that external connections and write access to
%%% system resources are all passed through a single instance of zx_daemon. Once a
%%% zx_daemon recognizes that it is the first instance of ZX running on a system it
%%% declares itself the system proxy by writing a lock file in the main Zomp directory
%%% and opening a local port to listen to connections from other local ZX instances.
%%% @end
-module(zx_peers).
-vsn("0.2.0").
-behavior(supervisor).
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([start_link/0]).
-export([init/1]).
-spec start_link() -> {ok, pid()}.
%% @private
%% This supervisor's own start function.
start_link() ->
supervisor:start_link({local, ?MODULE}, ?MODULE, none).
-spec init(none) -> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
%% @private
%% The OTP init/1 function.
init(none) ->
RestartStrategy = {rest_for_one, 1, 60},
PeerSup = {zx_peer_sup,
{zx_peer_sup, start_link, []},
permanent,
5000,
supervisor,
[zx_peer_sup]},
PeerMan = {zx_peer_man,
{zx_peer_man, start_link, []},
permanent,
5000,
worker,
[zx_peer_man]},
Children = [PeerSup, PeerMan],
{ok, {RestartStrategy, Children}}.

View File

@ -0,0 +1,250 @@
%%% @doc
%%% ZX Proxy
%%%
%%% Abstraction to the local zx_daemon proxy.
%%% @end
-module(zx_proxy).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([subscribe/1, unsubscribe/1, request/1]).
-export([connect/1, disconnect/0]).
-export([start_link/0, init/1]).
-export([system_continue/3, system_terminate/4,
system_get_state/1, system_replace_state/2]).
-include("zx_logger.hrl").
%%% Type and Record Definitions
-record(s, {socket = none :: none | gen_tcp:socket()}).
-type state() :: #s{}.
%%% Service Interface
-spec subscribe(zx:package()) -> ok.
subscribe(Realm) ->
?MODULE ! {subscribe, Realm},
ok.
-spec unsubscribe(zx:package()) -> ok.
unsubscribe(Package) ->
?MODULE ! {unsubscribe, Package},
ok.
-spec request(Action) -> Result
when Action :: zx_daemon:action(),
Result :: term()
| {error, Reason :: timeout | term()}.
request(Action) ->
Proxy = whereis(?MODULE),
Mon = monitor(process, Proxy),
Proxy ! {request, self(), Mon, Action},
receive
{result, Mon, Result} ->
true = demonitor(Mon),
Result;
{'DOWN', Mon, process, Proxy, Info} ->
{error, Info}
after 5000 ->
{error, timeout}
end.
-spec connect(Port) -> Result
when Port :: inet:port_number(),
Result :: ok.
connect(Port) ->
?MODULE ! {connect, self(), Port},
receive
{connect, Outcome} -> Outcome
after 5000 -> error
end.
-spec disconnect() -> ok.
disconnect() ->
?MODULE ! disconnect,
ok.
-spec start_link() -> Result
when Result :: {ok, pid()}
| {error, Reason},
Reason :: {already_started, pid()}
| {shutdown, term()}
| term().
start_link() ->
proc_lib:start_link(?MODULE, init, [self()]).
-spec init(Parent) -> no_return()
when Parent :: pid().
init(Parent) ->
Debug = sys:debug_options([]),
Self = self(),
true = register(?MODULE, Self),
ok = proc_lib:init_ack(Parent, {ok, Self}),
loop(Parent, Debug, #s{}).
-spec loop(Parent, Debug, State) -> no_return()
when Parent :: pid(),
Debug :: [sys:dbg_opt()],
State :: state().
loop(Parent, Debug, State = #s{socket = Socket}) ->
receive
{request, From, Ref, Action} ->
Result = dispatch(Socket, Action),
From ! {result, Ref, Result},
loop(Parent, Debug, State);
{tcp, Socket, Bin} ->
ok = handle_message(Bin),
loop(Parent, Debug, State);
{connect, From, Port} ->
{Outcome, NewState} = connect(Port, State),
From ! {connect, Outcome},
loop(Parent, Debug, NewState);
disconnect ->
NewState = disconnect(State),
loop(Parent, Debug, NewState);
{tcp_closed, Socket} ->
ok = log(info, "Socket closed."),
NewState = State#s{socket = none},
loop(Parent, Debug, NewState);
{system, From, Request} ->
sys:handle_system_msg(Request, From, Parent, ?MODULE, Debug, State);
Unexpected ->
ok = io:format("~p Unexpected message: ~tp", [self(), Unexpected]),
loop(Parent, Debug, State)
end.
dispatch(Socket, Action) ->
case Action of
{list, R} -> make_query(Socket, 3, R);
{list, R, N} -> make_query(Socket, 3, {R, N});
{list, R, N, V} -> make_query(Socket, 3, {R, N, V});
{latest, R, N} -> make_query(Socket, 4, {R, N});
{latest, R, N, V} -> make_query(Socket, 4, {R, N, V});
{provides, R, M} -> make_query(Socket, 5, {R, M});
{list_deps, R, N, V} -> make_query(Socket, 6, {R, N, V});
{list_sysops, R} -> make_query(Socket, 7, R);
% {fetch, R, N, V} -> fetch(Socket, {R, N, V});
{fetch, R, N, V} -> make_query(Socket, 8, {R, N, V});
{install, R, N, V} -> make_query(Socket, 9, {R, N, V});
{build, R, N, V} -> make_query(Socket, 10, {R, N, V});
{list_mirrors} -> make_query(Socket, 11, none);
{add_mirror, Host} -> make_query(Socket, 12, Host);
{drop_mirror, Host} -> make_query(Socket, 13, Host);
{register_key, Data} -> make_query(Socket, 14, Data);
{get_key, KeyID} -> make_query(Socket, 15, KeyID);
{keybin, KeyID} -> make_query(Socket, 16, KeyID);
{find_keypair, KeyID} -> make_query(Socket, 17, KeyID);
{have_key, Type, KID} -> make_query(Socket, 18, {Type, KID});
{list_keys, R} -> make_query(Socket, 19, R);
{takeover, R} -> make_query(Socket, 20, R);
{abdicate, R} -> make_query(Socket, 21, R);
{drop_realm, R} -> make_query(Socket, 22, R);
{keychain, R, K} -> make_query(Socket, 23, {R, K});
Unexpected ->
Message = "Received unexpected request action. Action: ~200tp",
ok = log(warning, Message, [Unexpected]),
{error, bad_message}
end.
make_query(Socket, Command, Payload) ->
Message = pack(Command, Payload),
ok = gen_tcp:send(Socket, Message),
receive
{tcp, Socket, <<0:8>>} -> ok;
{tcp, Socket, <<0:8, Bin/binary>>} -> zx_lib:b_to_t(Bin);
{tcp, Socket, Bin} -> {error, zx_net:err_in(Bin)}
after 5000 -> {error, timeout}
end.
pack(Command, none) -> <<0:1, Command:7>>;
pack(Command, Payload) -> <<0:1, Command:7, (term_to_binary(Payload))/binary>>.
handle_message(<<1:1, 1:7, Bin/binary>>) ->
{ok, {Channel, Message}} = zx_lib:b_to_ts(Bin),
zx_daemon:notify(Channel, Message).
connect(Port, State = #s{socket = none}) ->
Options =
[inet6,
{ip, {0,0,0,0,0,0,0,1}},
{active, true},
{mode, binary},
{keepalive, true},
{reuseaddr, true},
{packet, 4}],
case gen_tcp:connect({0,0,0,0,0,0,0,1}, Port, Options) of
{ok, Socket} ->
{ok, State#s{socket = Socket}};
{error, Reason} ->
ok = log(warning, "Connect to local proxy failed with ~tp.", [Reason]),
{error, State}
end.
disconnect(State = #s{socket = none}) ->
State;
disconnect(State = #s{socket = Socket}) ->
ok = zx_net:disconnect(Socket),
State#s{socket = none}.
%%% OTP System Message Handling
-spec system_continue(Parent, Debug, State) -> no_return()
when Parent :: pid(),
Debug :: [sys:dbg_opt()],
State :: state().
system_continue(Parent, Debug, State) ->
loop(Parent, Debug, State).
-spec system_terminate(Reason, Parent, Debug, State) -> no_return()
when Reason :: term(),
Parent :: pid(),
Debug :: [sys:dbg_opt()],
State :: state().
system_terminate(Reason, _Parent, _Debug, _State) ->
exit(Reason).
-spec system_get_state(State) -> {ok, State}
when State :: state().
system_get_state(State) -> {ok, State}.
-spec system_replace_state(StateFun, State) -> {ok, NewState, State}
when StateFun :: fun(),
State :: state(),
NewState :: term().
system_replace_state(StateFun, State) ->
{ok, StateFun(State), State}.

View File

@ -1,10 +1,11 @@
%%% @doc %%% @doc
%%% ZX Daemon Supervisor %%% ZX Daemon Supervisor
%%% %%%
%%% This supervisor maintains the lifecycle of the zxd worker process. %%% This supervisor maintains the lifecycle of the zx_daemon worker process.
%%% @end %%% @end
-module(zx_sup). -module(zx_sup).
-vsn("0.2.0").
-behavior(supervisor). -behavior(supervisor).
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
@ -42,19 +43,32 @@ start_link() ->
init(none) -> init(none) ->
RestartStrategy = {rest_for_one, 1, 60}, RestartStrategy = {rest_for_one, 1, 60},
Daemon = {zx_daemon, Daemon = {zx_daemon,
{zx_daemon, start_link, []}, {zx_daemon, start_link, []},
permanent, permanent,
10000, 10000,
worker, worker,
[zx_daemon]}, [zx_daemon]},
ConnSup = {zx_conn_sup, ConnSup = {zx_conn_sup,
{zx_conn_sup, start_link, []}, {zx_conn_sup, start_link, []},
permanent, permanent,
brutal_kill, brutal_kill,
supervisor, supervisor,
[zx_conn_sup]}, [zx_conn_sup]},
Children = [Daemon, ConnSup], Proxy = {zx_proxy,
{zx_proxy, start_link, []},
permanent,
5000,
worker,
[zx_proxy]},
PeerService = {zx_peers,
{zx_peers, start_link, []},
permanent,
5000,
supervisor,
[zx_peers]},
Children = [Daemon, ConnSup, Proxy, PeerService],
{ok, {RestartStrategy, Children}}. {ok, {RestartStrategy, Children}}.

View File

@ -6,6 +6,7 @@
%%% @end %%% @end
-module(zx_tty). -module(zx_tty).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>"). -author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>"). -copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0"). -license("GPL-3.0").
@ -182,7 +183,8 @@ hurr() -> io:format("That isn't an option.~n").
what_a_quitter() -> what_a_quitter() ->
ok = io:format("User abort: \"QUIT\".~nHalting.~n"), ok = io:format("User abort: \"QUIT\".~nHalting.~n"),
halt(0). ok = init:stop(),
receive Message -> io:format("Death Note: ~tp~n", [Message]) end.
-spec derp() -> ok. -spec derp() -> ok.

View File

@ -0,0 +1,273 @@
%%% @doc
%%% ZX ZSP: The ZSP package interface
%%%
%%% ZSP files are project package files managed by Zomp and ZX. This module provides
%%% a common interface for interfacing with the contents of a ZSP file and a few helper
%%% functions.
%%% @end
-module(zx_zsp).
-vsn("0.2.0").
-author("Craig Everett <zxq9@zxq9.com>").
-copyright("Craig Everett <zxq9@zxq9.com>").
-license("GPL-3.0").
-export([pack/2,
unpack/1, blithely_unpack/1,
extract/2, blithely_extract/2,
verify/1, verify/2,
meta/1, package_id/1,
resign/2, resign/3]).
-export_type([meta/0]).
-include("zx_logger.hrl").
-type meta() :: {PackageID :: zx:package_id(),
KeyName :: zx:key_name(),
Tags :: [string()],
Deps :: [zx:package_id()],
Modules :: [string()]}.
-spec pack(TargetDir, Key) -> Result
when TargetDir :: file:filename(),
Key :: public_key:rsa_public_key(),
Result :: ok
| {error, file:posix()}.
pack(TargetDir, Key) ->
case zx_lib:read_project_meta(TargetDir) of
{ok, Meta} -> pack2(TargetDir, Key, Meta);
Error -> Error
end.
pack2(TargetDir, Key, Meta) ->
PackageID = maps:get(package_id, Meta),
{ok, PackageString} = zx_lib:package_string(PackageID),
ZspFile = PackageString ++ ".zsp",
case filelib:is_regular(ZspFile) of
false -> pack3(TargetDir, PackageID, Meta, Key, ZspFile);
true -> {error, eexists}
end.
pack3(TargetDir, PackageID, Meta, {KeyName, Key}, ZspFile) ->
Beams = filelib:wildcard("**/*.{beam,ez}", TargetDir),
ToDelete = [filename:join(TargetDir, Beam) || Beam <- Beams],
ok = lists:foreach(fun file:delete/1, ToDelete),
ok = zx_lib:rm_rf(filename:join(TargetDir, "erl_crash.dump")),
{ok, Everything} = file:list_dir(TargetDir),
DotFiles = filelib:wildcard(".*", TargetDir),
Targets = lists:subtract(Everything, DotFiles),
{ok, CWD} = file:get_cwd(),
ok = file:set_cwd(TargetDir),
ok = zx_local:update_app_file(),
Name = element(2, PackageID),
AppFile = filename:join("ebin", Name ++ ".app"),
{ok, [{application, _, AppData}]} = file:consult(AppFile),
Modules = lists:map(fun atom_to_list/1, proplists:get_value(modules, AppData)),
TarGzPath = filename:join(zx_lib:path(tmp), ZspFile ++ ".tgz"),
ok = erl_tar:create(TarGzPath, Targets, [compressed]),
{ok, TgzBin} = file:read_file(TarGzPath),
ok = file:delete(TarGzPath),
Tags = maps:get(tags, Meta, []),
Deps = maps:get(deps, Meta, []),
MetaBin = term_to_binary({PackageID, KeyName, Tags, Deps, Modules}),
MetaSize = byte_size(MetaBin),
SignMe = <<MetaSize:24, MetaBin:MetaSize/binary, TgzBin/binary>>,
Sig = public_key:sign(SignMe, sha512, Key),
SigSize = byte_size(Sig),
ZspData = <<SigSize:24, Sig:SigSize/binary, SignMe/binary>>,
ok = file:set_cwd(CWD),
case file:write_file(ZspFile, ZspData) of
ok -> {ok, ZspFile};
Error -> Error
end.
-spec unpack(ZspFile) -> Outcome
when ZspFile :: file:filename(),
Outcome :: ok
| {error, Reason},
Reason :: bad_zsp
| bad_sig
| bad_key
| file:posix().
unpack(ZspFile) ->
case file:read_file(ZspFile) of
{ok, ZspBin} -> extract(ZspBin, cwd);
Error -> Error
end.
-spec blithely_unpack(ZspFile) -> Outcome
when ZspFile :: file:filename(),
Outcome :: ok
| {error, Reason},
Reason :: bad_zsp
| file:posix().
blithely_unpack(ZspFile) ->
case file:read_file(ZspFile) of
{ok, ZspBin} -> blithely_extract(ZspBin, cwd);
Error -> Error
end.
-spec extract(ZspBin, Location) -> Outcome
when ZspBin :: binary(),
Location :: cwd
| lib,
Outcome :: ok
| {error, Reason},
Reason :: bad_zsp
| bad_sig
| bad_key.
extract(ZspBin, Location) ->
case verify(ZspBin) of
ok -> blithely_extract(ZspBin, Location);
Error -> Error
end.
blithely_extract(ZspBin, cwd) ->
{ok, Meta} = meta(ZspBin),
{ok, PackageString} = zx_lib:package_string(element(1, Meta)),
install(ZspBin, PackageString);
blithely_extract(ZspBin, lib) ->
{ok, Meta} = meta(ZspBin),
PackageID = element(1, Meta),
Path = zx_lib:ppath(lib, PackageID),
install(ZspBin, Path).
install(<<SS:24, _:SS/binary, MS:24, _:MS/binary, TarGZ/binary>>, Path) ->
ok = filelib:ensure_dir(Path),
ok = zx_lib:rm_rf(Path),
ok = file:make_dir(Path),
erl_tar:extract({binary, TarGZ}, [{cwd, Path}, compressed]).
-spec verify(ZspBin) -> Outcome
when ZspBin :: binary(),
Outcome :: ok
| {error, Reason},
Reason :: bad_zsp
| bad_sig
| bad_key.
verify(<<Size:24, Sig:Size/binary, Signed/binary>>) ->
verify2(Sig, Signed);
verify(_) ->
{error, bad_zsp}.
verify2(Sig, Signed = <<MetaSize:24, MetaBin:MetaSize/binary, _/binary>>) ->
case zx_lib:b_to_ts(MetaBin) of
{ok, {{Realm, _, _}, SigKeyName, _, _, _}} ->
SigKeyID = {Realm, SigKeyName},
verify3(Sig, Signed, SigKeyID);
error ->
{error, bad_zsp}
end;
verify2(_, _) ->
{error, bad_zsp}.
verify3(Sig, Signed, SigKeyID) ->
case zx_key:load(public, SigKeyID) of
{ok, PubKey} ->
verify4(Signed, Sig, PubKey);
{error, Reason} ->
Message = "zx_key:load(public, ~tp) failed with: ~tp",
ok = log(warning, Message, [SigKeyID, Reason]),
{error, bad_key}
end.
verify4(Signed, Sig, PubKey) ->
case zx_key:verify(Signed, Sig, PubKey) of
true -> ok;
false -> {error, bad_sig}
end.
-spec verify(ZspBin, PubKey) -> boolean()
when ZspBin :: binary(),
PubKey :: public_key:rsa_public_key().
verify(<<Size:24, Sig:Size/binary, Signed/binary>>, PubKey) ->
zx_key:verify(Signed, Sig, PubKey).
-spec meta(binary()) -> {ok, meta()} | {error, bad_zsp}.
meta(<<SS:24, _:SS/binary, MS:24, MetaBin:MS/binary, _/binary>>) ->
case zx_lib:b_to_ts(MetaBin) of
{ok, Meta = {_, _, _, _, _}} -> {ok, Meta};
_ -> {error, bad_zsp}
end.
-spec package_id(binary()) -> {ok, zx:package_id()} | {error, bad_zsp}.
package_id(Bin) ->
case meta(Bin) of
{ok, Meta} -> {ok, element(1, Meta)};
Error -> Error
end.
-spec resign(KeyID, ZspBin) -> Outcome
when KeyID :: zx:key_id(),
ZspBin :: binary(),
Outcome :: {ok, binary()}
| {error, Reason},
Reason :: bad_zsp
| bad_realm
| no_key
| bad_key.
resign(KeyID = {Realm, KeyName},
<<SS:24, _:SS/binary, MS:24, MetaBin:MS/binary, TarGZ/binary>>) ->
case zx_daemon:get_key(private, KeyID) of
{ok, Key} -> resign2(Realm, KeyName, Key, MetaBin, TarGZ);
Error -> Error
end;
resign(_, _) ->
{error, bad_zsp}.
-spec resign(KeyID, Key, ZspBin) -> Outcome
when KeyID :: zx:key_id(),
Key :: public_key:rsa_private_key(),
ZspBin :: binary(),
Outcome :: {ok, binary()}
| {error, Reason},
Reason :: bad_zsp
| bad_realm
| no_key
| bad_key.
resign({Realm, KeyName},
Key,
<<SS:24, _:SS/binary, MS:24, MetaBin:MS/binary, TarGZ/binary>>) ->
resign2(Realm, KeyName, Key, MetaBin, TarGZ);
resign(_, _, _) ->
{error, bad_zsp}.
resign2(Realm, KeyName, Key, MetaBin, TarGZ) ->
case zx_lib:b_to_ts(MetaBin) of
{ok, Meta = {{Realm, _, _}, _, _, _, _}} -> resign3(KeyName, Key, Meta, TarGZ);
{ok, _} -> {error, bad_realm};
error -> {error, bad_zsp}
end.
resign3(KeyName, Key, Meta, TarGZ) ->
MetaBin = term_to_binary(setelement(2, Meta, KeyName)),
MetaSize = byte_size(MetaBin),
SignMe = <<MetaSize:24, MetaBin:MetaSize/binary, TarGZ/binary>>,
Sig = public_key:sign(SignMe, sha512, Key),
SigSize = byte_size(Sig),
ZspBin = <<SigSize:24, Sig:SigSize/binary, SignMe/binary>>,
{ok, ZspBin}.

View File

@ -0,0 +1,5 @@
{deps,[]}.
{package_id,{"otpr","zx",{0,2,0}}}.
{prefix,"zx_"}.
{tags,[]}.
{type,app}.

11
zomp/zx
View File

@ -1,11 +1,12 @@
#!/bin/sh #!/bin/bash
export ZOMP_DIR="${ZOMP_DIR:-$HOME/.zomp}" . "$HOME"/.bash_profile
version=$(cat "$ZOMP_DIR/etc/version.txt") export ZOMP_DIR="${ZOMP_DIR:-$HOME/zomp}"
export ZX_DIR="$ZOMP_DIR/lib/otpr/zx/$version" export ZX_VERSION=$(cat "$ZOMP_DIR/etc/version.txt")
export ZX_DIR="$ZOMP_DIR/lib/otpr/zx/$ZX_VERSION"
start_dir="$PWD" start_dir="$PWD"
cd "$ZX_DIR" cd "$ZX_DIR"
./make_zx ./make_zx
cd "$start_dir" cd "$start_dir"
erl -noshell -pa "$ZX_DIR/ebin" -run zx do $@ erl -noshell -pa "$ZX_DIR/ebin" -run zx do -extra $@

View File

@ -1,11 +1,12 @@
#!/bin/sh #!/bin/sh
export ZOMP_DIR="${ZOMP_DIR:-$HOME/.zomp}" . "$HOME"/.bash_profile
version=$(cat "$ZOMP_DIR/etc/version.txt") export ZOMP_DIR="${ZOMP_DIR:-$HOME/zomp}"
export ZX_DIR="$ZOMP_DIR/lib/otpr/zx/$version" export ZX_VERSION=$(cat "$ZOMP_DIR/etc/version.txt")
export ZX_DIR="$ZOMP_DIR/lib/otpr/zx/$ZX_VERSION"
start_dir="$PWD" start_dir="$PWD"
cd "$ZX_DIR" cd "$ZX_DIR"
./make_zx ./make_zx
cd "$start_dir" cd "$start_dir"
erl -pa "$ZX_DIR/ebin" -run zx do $@ erl -pa "$ZX_DIR/ebin" -run zx do -extra $@