Shaky, but working-ish contract deployment and calls

This commit is contained in:
Craig Everett 2025-02-25 16:32:11 +09:00
parent 0b02d6dd29
commit eac630168c
7 changed files with 1525 additions and 232 deletions

1029
src/: Normal file

File diff suppressed because it is too large Load Diff

View File

@ -59,6 +59,7 @@ start(normal, _Args) ->
end,
ok = application:ensure_started(hakuzaru),
ok = application:ensure_started(zxwidgets),
ok = application:ensure_started(sophia),
gmc_sup:start_link().

View File

@ -14,9 +14,9 @@
selected/1,
password/2,
refresh/0,
nonce/1, spend/2, chain/1, grids/1, sign_mess/1, sign_tx/1,
deploy/2,
make_key/6, recover_key/1, mnemonic/1, rename_key/2, drop_key/1,
nonce/1, spend/2, chain/1, grids/1, sign_mess/1, sign_tx/1, sign_call/3, dry_run/2,
deploy/3,
make_key/6, recover_key/1, mnemonic/1, rename_key/2, drop_key/1, list_keys/0,
add_node/1, set_sole_node/1]).
-export([encrypt/2, decrypt/2]).
-export([save/2]).
@ -170,15 +170,33 @@ sign_tx(Request) ->
gen_server:cast(?MODULE, {sign_tx, Request}).
-spec deploy(Build, InitArgs) -> Result
when Build :: map(),
-spec sign_call(ConID, PubKey, TX) -> ok
when ConID :: clutch:id(),
PubKey :: clutch:id(),
TX :: binary().
sign_call(ConID, PubKey, TX) ->
gen_server:cast(?MODULE, {sign_call, ConID, PubKey, TX}).
-spec dry_run(ConID, TX) -> ok
when ConID :: clutch:id(),
TX :: binary().
dry_run(ConID, TX) ->
gen_server:cast(?MODULE, {dry_run, ConID, TX}).
-spec deploy(CreatorID, Build, InitArgs) -> Result
when CreatorID :: clutch:id(),
Build :: map(),
InitArgs :: [Arg :: string()],
Result :: {ok, TX_Hash :: clutch:id()}
| {error, Reason},
Reason :: term(). % FIXME
deploy(Build, InitArgs) ->
gen_server:call(?MODULE, {deploy, Build, InitArgs}).
deploy(CreatorID, Build, InitArgs) ->
gen_server:cast(?MODULE, {deploy, CreatorID, Build, InitArgs}).
-spec make_key(Type, Size, Name, Seed, Encoding, Transform) -> ok
@ -230,6 +248,14 @@ drop_key(ID) ->
gen_server:cast(?MODULE, {drop_key, ID}).
-spec list_keys() -> Result
when Result :: {ok, Selected :: non_neg_integer(), Keys :: [clutch:id()]}
| error.
list_keys() ->
gen_server:call(?MODULE, list_keys).
-spec add_node(New) -> ok
when New :: #node{}.
@ -315,6 +341,9 @@ read_prefs() ->
%% The gen_server:handle_call/3 callback.
%% See: http://erlang.org/doc/man/gen_server.html#Module:handle_call-3
handle_call(list_keys, _, State) ->
Response = do_list_keys(State),
{reply, Response, State};
handle_call({nonce, ID}, _, State) ->
Response = do_nonce(ID),
{reply, Response, State};
@ -324,9 +353,6 @@ handle_call({save, Module, Prefs}, _, State) ->
handle_call({mnemonic, ID}, _, State) ->
Response = do_mnemonic(ID, State),
{reply, Response, State};
handle_call({deploy, Build, InitArgs}, _, State) ->
Result = do_deploy(Build, InitArgs, State),
{reply, Result, State};
handle_call(Unexpected, From, State) ->
ok = log(warning, "Unexpected call from ~tp: ~tp~n", [From, Unexpected]),
{noreply, State}.
@ -384,6 +410,15 @@ handle_cast({sign_mess, Request}, State) ->
handle_cast({sign_tx, Request}, State) ->
ok = do_sign_tx(Request, State),
{noreply, State};
handle_cast({sign_call, ConID, PubKey, TX}, State) ->
ok = do_sign_call(State, ConID, PubKey, TX),
{noreply, State};
handle_cast({dry_run, ConID, TX}, State) ->
ok = do_dry_run(ConID, TX),
{noreply, State};
handle_cast({deploy, CreatorID, Build, InitArgs}, State) ->
ok = do_deploy(CreatorID, Build, InitArgs, State),
{noreply, State};
handle_cast({make_key, Name, Seed, Encoding, Transform}, State) ->
NewState = do_make_key(Name, Seed, Encoding, Transform, State),
{noreply, NewState};
@ -613,8 +648,8 @@ do_grids_sig2(WTF) ->
do_sign_mess(Request = #{"public_id" := ID, "payload" := Message},
#s{wallet = #wallet{keys = Keys}}) ->
case lists:keyfind(ID, #key.id, Keys) of
#key{pair = #{secret := PrivKey}} ->
Sig = base64:encode(sign_message(list_to_binary(Message), PrivKey)),
#key{pair = #{secret := SecKey}} ->
Sig = base64:encode(sign_message(list_to_binary(Message), SecKey)),
do_sign_mess2(Request#{"signature" => Sig});
false ->
gmc_gui:trouble({bad_key, ID})
@ -638,13 +673,13 @@ do_sign_mess2(Request = #{"url" := URL}) ->
% TODO: Should probably be part of Hakuzaru
sign_message(Message, PrivKey) ->
sign_message(Message, SecKey) ->
Prefix = <<"Gajumaru Signed Message:\n">>,
{ok, PSize} = vencode(byte_size(Prefix)),
{ok, MSize} = vencode(byte_size(Message)),
Smashed = iolist_to_binary([PSize, Prefix, MSize, Message]),
{ok, Hashed} = eblake2:blake2b(32, Smashed),
ecu_eddsa:sign_detached(Hashed, PrivKey).
ecu_eddsa:sign_detached(Hashed, SecKey).
vencode(N) when N < 0 ->
@ -672,9 +707,9 @@ do_sign_tx(Request = #{"public_id" := ID, "payload" := CallData, "network_id" :=
#s{wallet = #wallet{keys = Keys}}) ->
BinNID = list_to_binary(NID),
case lists:keyfind(ID, #key.id, Keys) of
#key{pair = #{secret := PrivKey}} ->
#key{pair = #{secret := SecKey}} ->
BinaryTX = list_to_binary(CallData),
SignedTX = sign_tx_hash(BinaryTX, PrivKey, BinNID),
SignedTX = sign_tx_hash(BinaryTX, SecKey, BinNID),
do_sign_tx2(Request#{"signed" => true, "payload" := SignedTX});
false ->
gmc_gui:trouble({bad_key, ID})
@ -696,11 +731,11 @@ do_sign_tx2(Request = #{"url" := URL}) ->
Error -> gmc_gui:trouble(Error)
end.
sign_tx_hash(Unsigned, PrivKey, NetworkID) ->
{ok, TX_Data} = aeser_api_encoder:safe_decode(transaction, Unsigned),
sign_tx_hash(Unsigned, SecKey, NetworkID) ->
{ok, TX_Data} = gmser_api_encoder:safe_decode(transaction, Unsigned),
{ok, Hash} = eblake2:blake2b(32, TX_Data),
NetworkHash = <<NetworkID/binary, Hash/binary>>,
Signature = ecu_eddsa:sign_detached(NetworkHash, PrivKey),
Signature = ecu_eddsa:sign_detached(NetworkHash, SecKey),
SigTxType = signed_tx,
SigTxVsn = 1,
SigTemplate =
@ -709,19 +744,57 @@ sign_tx_hash(Unsigned, PrivKey, NetworkID) ->
TX =
[{signatures, [Signature]},
{transaction, TX_Data}],
SignedTX = aeser_chain_objects:serialize(SigTxType, SigTxVsn, SigTemplate, TX),
aeser_api_encoder:encode(transaction, SignedTX).
SignedTX = gmser_chain_objects:serialize(SigTxType, SigTxVsn, SigTemplate, TX),
gmser_api_encoder:encode(transaction, SignedTX).
do_sign_call(#s{wallet = #wallet{keys = Keys, chain_id = ChainID}},
ConID,
PubKey,
TX) ->
#key{pair = #{secret := SecKey}} = lists:keyfind(PubKey, #key.id, Keys),
SignedTX = sign_tx_hash(TX, SecKey, ChainID),
case hz:post_tx(SignedTX) of
{ok, Data = #{"tx_hash" := TXHash}} ->
ok = tell("Contract deploy TX succeded with: ~p", [TXHash]),
do_sign_call2(ConID, Data);
{ok, WTF} ->
gmc_v_devman:trouble({error, WTF});
Error ->
gmc_v_devman:trouble(Error)
end;
do_sign_call(_, _, _, _) ->
gmc_v_devman:trouble({error, no_chain}).
do_sign_call2(ConID, #{"tx_hash" := TXHash}) ->
case hz:tx_info(TXHash) of
{ok, CallInfo = #{"call_info" := #{"return_type" := "ok"}}} ->
gmc_v_devman:call_result(ConID, CallInfo);
{error, "Tx not mined"} ->
gmc_v_devman:trouble({tx_hash, TXHash});
{ok, Reason = #{"call_info" := #{"return_type" := "revert"}}} ->
gmc_v_devman:trouble({error, Reason});
Error ->
gmc_v_devman:trouble(Error)
end.
do_dry_run(ConID, TX) ->
case hz:dry_run(TX) of
{ok, Result} -> gmc_v_devman:dryrun_result(ConID, Result);
Other -> gmc_v_devmam:trouble({error, ConID, Other})
end.
do_spend(KeyID, TX, State = #s{wallet = #wallet{keys = Keys}}) ->
case lists:keyfind(KeyID, #key.id, Keys) of
#key{pair = #{secret := PrivKey}} ->
do_spend2(PrivKey, TX, State);
#key{pair = #{secret := SecKey}} ->
do_spend2(SecKey, TX, State);
false ->
log(warning, "Tried do_spend with a bad key: ~p", [KeyID])
end.
do_spend2(PrivKey,
do_spend2(SecKey,
#spend_tx{sender_id = SenderID,
recipient_id = RecipientID,
amount = Amount,
@ -751,9 +824,9 @@ do_spend2(PrivKey,
{ttl, int},
{nonce, int},
{payload, binary}],
BinaryTX = aeser_chain_objects:serialize(Type, Vsn, Template, Fields),
BinaryTX = gmser_chain_objects:serialize(Type, Vsn, Template, Fields),
NetworkTX = <<ChainID/binary, BinaryTX/binary>>,
Signature = ecu_eddsa:sign_detached(NetworkTX, PrivKey),
Signature = ecu_eddsa:sign_detached(NetworkTX, SecKey),
SigTxType = signed_tx,
SigTxVsn = 1,
SigTemplate =
@ -762,12 +835,18 @@ do_spend2(PrivKey,
TX_Data =
[{signatures, [Signature]},
{transaction, BinaryTX}],
SignedTX = aeser_chain_objects:serialize(SigTxType, SigTxVsn, SigTemplate, TX_Data),
Encoded = aeser_api_encoder:encode(transaction, SignedTX),
SignedTX = gmser_chain_objects:serialize(SigTxType, SigTxVsn, SigTemplate, TX_Data),
Encoded = gmser_api_encoder:encode(transaction, SignedTX),
Outcome = hz:post_tx(Encoded),
tell("Outcome: ~p", [Outcome]).
do_list_keys(#s{selected = Selected, wallet = #wallet{poas = POAs}}) ->
{ok, Selected, [ID || #poa{id = ID} <- POAs]};
do_list_keys(#s{wallet = none}) ->
error.
do_nonce(ID) ->
hz:next_nonce(ID).
@ -899,37 +978,39 @@ do_mnemonic(ID, #s{wallet = #wallet{keys = Keys}}) ->
end.
do_deploy(Build,
do_deploy(CreatorID,
Build,
InitArgs,
#s{selected = Index, wallet = #wallet{keys = Keys, chain_id = ChainID}}) ->
#key{pair = #{public := PubKey, secret := SecKey}} = lists:nth(Index, Keys),
case hz:contract_create_built(PubKey, Build, InitArgs) of
#s{wallet = #wallet{keys = Keys, chain_id = ChainID}}) ->
#key{pair = #{secret := SecKey}} = lists:keyfind(CreatorID, #key.id, Keys),
case hz:contract_create_built(CreatorID, Build, InitArgs) of
{ok, CreateTX} -> do_deploy2(SecKey, CreateTX, ChainID);
Error -> Error
Error -> gmc_v_devman:trouble(Error)
end.
do_deploy2(SecKey, CreateTX, ChainID) ->
SignedTX = sign_tx_hash(CreateTX, SecKey, ChainID),
tell(info, "SignedTX: ~p", [SignedTX]),
case hz:post_tx(SignedTX) of
{ok, Data = #{"tx_hash" := TXHash}} ->
ok = tell("Contract deploy TX succeded with: ~p", [TXHash]),
do_deploy3(Data);
{ok, WTF} ->
{error, WTF};
gmc_v_devman:trouble({error, WTF});
Error ->
Error
gmc_v_devman:trouble(Error)
end.
do_deploy3(#{"tx_hash" := TXHash}) ->
case hz:tx_info(TXHash) of
{ok, #{"call_info" := #{"return_type" := "ok", "contract_id" := ConID}}} ->
{contract_id, ConID};
gmc_v_devman:open_contract(ConID);
{error, "Tx not mined"} ->
{tx_hash, TXHash};
gmc_v_devman:trouble({tx_hash, TXHash});
{ok, Reason = #{"call_info" := #{"return_type" := "revert"}}} ->
{error, Reason};
gmc_v_devman:trouble({error, Reason});
Error ->
Error
gmc_v_devman:trouble(Error)
end.
@ -1136,7 +1217,7 @@ do_close_wallet(State = #s{wallet = Current, wallets = Wallets, pass = Pass}) ->
#wallet{name = Name} = Current,
RW = lists:keyfind(Name, #wr.name, Wallets),
ok = save_wallet(RW, Pass, Current),
State#s{pass = none, wallet = none}.
State#s{selected = 0, pass = none, wallet = none}.
save_wallet(#wr{path = Path, pass = false}, none, Wallet) ->

View File

@ -765,7 +765,7 @@ spend2(#poa{id = ID, name = Name}, Nonce, Height, State = #s{frame = Frame, j =
?wxID_OK ->
{ok, PK} = decode_account_id(ID),
TX =
#spend_tx{sender_id = aeser_id:create(account, PK),
#spend_tx{sender_id = gmser_id:create(account, PK),
recipient_id = wxTextCtrl:getValue(ToTx),
amount = wxTextCtrl:getValue(AmtTx),
gas_price = wxSlider:getValue(GasSl),
@ -784,7 +784,7 @@ clean_spend(_, #spend_tx{recipient_id = ""}) ->
ok;
clean_spend(ID, TX = #spend_tx{recipient_id = S}) when is_list(S) ->
case decode_account_id(S) of
{ok, PK} -> clean_spend(ID, TX#spend_tx{recipient_id = aeser_id:create(account, PK)});
{ok, PK} -> clean_spend(ID, TX#spend_tx{recipient_id = gmser_id:create(account, PK)});
Error -> tell("Decode recipient_id failed with: ~tp", [Error])
end;
clean_spend(ID, TX = #spend_tx{amount = S}) when is_list(S) ->
@ -811,7 +811,7 @@ decode_account_id(S) when is_list(S) ->
decode_account_id(list_to_binary(S));
decode_account_id(B) ->
try
{account_pubkey, PK} = aeser_api_encoder:decode(B),
{account_pubkey, PK} = gmser_api_encoder:decode(B),
{ok, PK}
catch
E:R -> {E, R}

View File

@ -18,21 +18,21 @@
make_key("", <<>>) ->
Pair = #{public := Public} = ecu_eddsa:sign_keypair(),
ID = aeser_api_encoder:encode(account_pubkey, Public),
ID = gmser_api_encoder:encode(account_pubkey, Public),
Name = binary_to_list(ID),
#key{name = Name, id = ID, pair = Pair};
make_key("", Seed) ->
Pair = #{public := Public} = ecu_eddsa:sign_seed_keypair(Seed),
ID = aeser_api_encoder:encode(account_pubkey, Public),
ID = gmser_api_encoder:encode(account_pubkey, Public),
Name = binary_to_list(ID),
#key{name = Name, id = ID, pair = Pair};
make_key(Name, <<>>) ->
Pair = #{public := Public} = ecu_eddsa:sign_keypair(),
ID = aeser_api_encoder:encode(account_pubkey, Public),
ID = gmser_api_encoder:encode(account_pubkey, Public),
#key{name = Name, id = ID, pair = Pair};
make_key(Name, Seed) ->
Pair = #{public := Public} = ecu_eddsa:sign_seed_keypair(Seed),
ID = aeser_api_encoder:encode(account_pubkey, Public),
ID = gmser_api_encoder:encode(account_pubkey, Public),
#key{name = Name, id = ID, pair = Pair}.

View File

@ -8,7 +8,7 @@
%-behavior(gmc_v).
-include_lib("wx/include/wx.hrl").
-export([to_front/1]).
-export([set_manifest/1, trouble/1]).
-export([set_manifest/1, open_contract/1, call_result/2, dryrun_result/2, trouble/1]).
-export([start_link/1]).
-export([init/1, terminate/2, code_change/3,
handle_call/3, handle_cast/2, handle_info/2, handle_event/2]).
@ -32,14 +32,15 @@
-record(p,
{path = {file, ""} :: {file, file:filename()} | {hash, binary()},
win = none :: none | wx:wx_object(),
code = none :: none | wxStyledTextCtrl:wxStyledTextCtrl()}).
code = none :: none | wxTextCtrl:wxTextCtrl()}).
% Contract pages
-record(c,
{id = "" :: string(),
{id = <<"">> :: binary(),
win = none :: none | wx:wx_object(),
code = none :: none | wxStyledTextCtrl:wxStyledTextCtrl(),
cons = none :: none | wxStyledTextCtrl:wxStyledTextCtrl(),
code = none :: none | wxTextCtrl:wxTextCtrl(),
cons = none :: none | wxTextCtrl:wxTextCtrl(),
build = none :: none | map(),
funs = {#w{}, []} :: {#w{}, [#f{}]}}).
% State
@ -65,8 +66,9 @@ to_front(Win) ->
wx_object:cast(Win, to_front).
% TODO: Probably kill this
-spec set_manifest(Entries) -> ok
when Entries :: [ael:conf_meta()].
when Entries :: list().
set_manifest(Entries) ->
case is_pid(whereis(?MODULE)) of
@ -75,6 +77,29 @@ set_manifest(Entries) ->
end.
-spec open_contract(Address) -> ok
when Address :: string().
open_contract(Address) ->
wx_object:cast(?MODULE, {open_contract, Address}).
-spec call_result(ConID, CallInfo) -> ok
when ConID :: clutch:id(),
CallInfo :: map().
call_result(ConID, CallInfo) ->
wx_object:cast(?MODULE, {call_result, ConID, CallInfo}).
-spec dryrun_result(ConID, CallInfo) -> ok
when ConID :: clutch:id(),
CallInfo :: map().
dryrun_result(ConID, CallInfo) ->
wx_object:cast(?MODULE, {dryrun_result, ConID, CallInfo}).
-spec trouble(Info) -> ok
when Info :: term().
@ -189,6 +214,15 @@ handle_call(Unexpected, From, State) ->
handle_cast(to_front, State = #s{frame = Frame}) ->
ok = wxFrame:raise(Frame),
{noreply, State};
handle_cast({open_contract, Address}, State) ->
NewState = load2(State, Address),
{noreply, NewState};
handle_cast({call_result, ConID, CallInfo}, State) ->
ok = do_call_result(State, ConID, CallInfo),
{noreply, State};
handle_cast({dryrun_result, ConID, CallInfo}, State) ->
ok = do_dryrun_result(State, ConID, CallInfo),
{noreply, State};
handle_cast({trouble, Info}, State) ->
ok = handle_troubling(State, Info),
{noreply, State};
@ -216,7 +250,7 @@ handle_event(E = #wx{event = #wxCommand{type = command_button_clicked},
#w{name = load} -> load(State);
#w{name = edit} -> edit(State);
#w{name = close_instance} -> close_instance(State);
#w{name = Name, wx = Button} -> clicked(State, Name, Button);
#w{name = Name} -> clicked(State, Name);
undefined ->
tell("Received message: ~w", [E]),
State
@ -257,22 +291,124 @@ terminate(Reason, State) ->
%%% Doers
clicked(State = #s{cons = {Consbook, Contracts}}, Name, Button) ->
clicked(State = #s{cons = {Consbook, Contracts}}, Name) ->
case wxNotebook:getSelection(Consbook) of
?wxNOT_FOUND ->
ok = tell(warning, "Inconcievable! No notebook page is selected!"),
State;
Index ->
Contract = lists:nth(Index + 1, Contracts),
clicked(State, Contract, Name, Button)
clicked2(State, Contract, Name)
end.
clicked(State, Contract, Name, Button) ->
ok = tell("Button: ~p ~p~nContract: ~p", [Button, Name, Contract]),
clicked2(State, Contract, Name) ->
case gmc_con:list_keys() of
{ok, 0, []} ->
handle_troubling(State, "No keys exist in the current wallet.");
{ok, Selected, Keys} ->
clicked3(State, Contract, Name, Selected, Keys);
error ->
handle_troubling(State, "No wallet is selected!")
end.
clicked3(State = #s{frame = Frame, j = J}, Contract, Name, Selected, Keys) ->
Dialog = wxDialog:new(Frame, ?wxID_ANY, J("Deploy Contract")),
Sizer = wxBoxSizer:new(?wxVERTICAL),
KeySz = wxStaticBoxSizer:new(?wxVERTICAL, Dialog, [{label, J("Signature Key")}]),
KeyPicker = wxChoice:new(Dialog, ?wxID_ANY, [{choices, Keys}]),
_ = wxStaticBoxSizer:add(KeySz, KeyPicker, zxw:flags(wide)),
ok = wxChoice:setSelection(KeyPicker, Selected - 1),
ButtSz = wxBoxSizer:new(?wxHORIZONTAL),
Affirm = wxButton:new(Dialog, ?wxID_OK),
Cancel = wxButton:new(Dialog, ?wxID_CANCEL),
_ = wxBoxSizer:add(ButtSz, Affirm, zxw:flags(wide)),
_ = wxBoxSizer:add(ButtSz, Cancel, zxw:flags(wide)),
_ = wxSizer:add(Sizer, KeySz, [{proportion, 0}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(Sizer, ButtSz, [{proportion, 1}, {flag, ?wxEXPAND}]),
ok = wxDialog:setSizer(Dialog, Sizer),
ok = wxBoxSizer:layout(Sizer),
ok = wxDialog:center(Dialog),
Outcome =
case wxDialog:showModal(Dialog) of
?wxID_OK ->
ID = wxChoice:getString(KeyPicker, wxChoice:getSelection(KeyPicker)),
BinID = unicode:characters_to_binary(ID),
{ok, BinID};
?wxID_CANCEL ->
cancel
end,
ok = wxDialog:destroy(Dialog),
case Outcome of
{ok, CallerID} -> clicked4(State, Contract, Name, CallerID);
cancel -> State
end.
clicked4(State,
#c{id = ConID, build = #{aci := ACI}, funs = {_, Funs}},
{Name, Type},
PK) ->
AACI = hz:prepare_aaci(ACI),
#f{args = ArgFields} = lists:keyfind(Name, #f.name, Funs),
Args = lists:map(fun get_arg/1, ArgFields),
FunName = binary_to_list(Name),
{ok, Nonce} = hz:next_nonce(PK),
{ok, Height} = hz:top_height(),
TTL = Height + 10000,
GasP = hz:min_gas_price(),
Gas = 5000000,
Amount = 0,
case hz:contract_call(PK, Nonce, Gas, GasP, Amount, TTL, AACI, ConID, FunName, Args) of
{ok, UnsignedTX} ->
case Type of
call -> do_call(State, ConID, PK, UnsignedTX);
dryr -> do_dry_run(State, ConID, UnsignedTX)
end;
Error ->
handle_troubling(State, Error),
State
end.
do_call(State, ConID, CallerID, UnsignedTX) ->
ok = gmc_con:sign_call(ConID, CallerID, UnsignedTX),
State.
get_arg({_, TextCtrl, _}) ->
wxTextCtrl:getValue(TextCtrl).
do_dry_run(State, ConID, TX) ->
ok = gmc_con:dry_run(ConID, TX),
State.
do_call_result(#s{tabs = TopBook, cons = {Consbook, Contracts}}, ConID, CallInfo) ->
case lookup_contract(ConID, Contracts) of
{#c{cons = Console}, ZeroIndex} ->
_ = wxNotebook:changeSelection(TopBook, 1),
_ = wxNotebook:changeSelection(Consbook, ZeroIndex),
Out = io_lib:format("Call Result:~n~p~n~n", [CallInfo]),
wxTextCtrl:appendText(Console, Out);
error ->
tell(info, "Received result for ~p:~n~p ", [ConID, CallInfo])
end.
do_dryrun_result(#s{tabs = TopBook, cons = {Consbook, Contracts}}, ConID, CallInfo) ->
case lookup_contract(ConID, Contracts) of
{#c{cons = Console}, ZeroIndex} ->
_ = wxNotebook:changeSelection(TopBook, 1),
_ = wxNotebook:changeSelection(Consbook, ZeroIndex),
Out = io_lib:format("Call Result:~n~p~n~n", [CallInfo]),
wxTextCtrl:appendText(Console, Out);
error ->
tell(info, "Received result for ~p:~n~p ", [ConID, CallInfo])
end.
lookup_contract(ConID, Contracts) ->
lookup_contract(ConID, Contracts, 0).
lookup_contract(ConID, [Contract = #c{id = ConID} | _], I) ->
{Contract, I};
lookup_contract(ConID, [#c{} | T], I) ->
lookup_contract(ConID, T, I + 1);
lookup_contract(_, [], _) ->
error.
add_code_page(State = #s{code = {Codebook, Pages}}, File) ->
@ -303,7 +439,7 @@ add_code_page2(State = #s{j = J}, {file, File}) ->
add_code_page2(State, {hash, Address}) ->
open_hash2(State, Address).
add_code_page(State = #s{j = J, tabs = TopBook, code = {Codebook, Pages}}, Location, Code) ->
add_code_page(State = #s{tabs = TopBook, code = {Codebook, Pages}}, Location, Code) ->
% FIXME: One of these days we need to define the text area as a wxStyledTextCtrl and will
% have to contend with system theme issues (light/dark themese, namely)
% Leaving this little thing here to remind myself how any of that works later.
@ -385,24 +521,35 @@ deploy(State = #s{code = {Codebook, Pages}}) ->
?wxNOT_FOUND ->
State;
Index ->
Page = #p{code = CodeTx} = lists:nth(Index + 1, Pages),
#p{code = CodeTx} = lists:nth(Index + 1, Pages),
Source = wxTextCtrl:getValue(CodeTx),
deploy2(State, Source)
end.
deploy2(State, Source) ->
case aeso_compiler:from_string(Source, [{aci, json}]) of
{ok, Build = #{aci := ACI}} ->
FunDefs = {#{functions := Funs}, _} = find_main(ACI),
Init = lom:find(name, <<"init">>, Funs),
ok = tell(info, "Compilation Succeeded!~n~tp~n~n~tp", [Build, FunDefs]),
deploy3(State, Init);
case compile(Source) of
% Options = sophia_options(),
% case so_compiler:from_string(Source, Options) of
{ok, Build} ->
deploy3(State, Build);
Other ->
ok = tell(info, "Compilation Failed!~n~tp", [Other]),
State
end.
deploy3(State = #s{frame = Frame, j = J}, #{arguments := As}) ->
deploy3(State, Build) ->
case gmc_con:list_keys() of
{ok, 0, []} ->
handle_troubling(State, "No keys exist in the current wallet.");
{ok, Selected, Keys} ->
deploy4(State, Build, Selected, Keys);
error ->
handle_troubling(State, "No wallet is selected!")
end.
deploy4(State = #s{frame = Frame, j = J}, Build = #{aci := ACI}, Selected, Keys) ->
{#{functions := Funs}, _} = find_main(ACI),
#{arguments := As} = lom:find(name, <<"init">>, Funs),
Dialog = wxDialog:new(Frame, ?wxID_ANY, J("Deploy Contract")),
Sizer = wxBoxSizer:new(?wxVERTICAL),
ScrollWin = wxScrolledWindow:new(Dialog),
@ -410,7 +557,15 @@ deploy3(State = #s{frame = Frame, j = J}, #{arguments := As}) ->
FunSizer = wxStaticBoxSizer:new(?wxVERTICAL, ScrollWin, [{label, FunName}]),
ok = wxScrolledWindow:setSizerAndFit(ScrollWin, FunSizer),
ok = wxScrolledWindow:setScrollRate(ScrollWin, 5, 5),
ButtSz = wxDialog:createButtonSizer(Dialog, ?wxOK bor ?wxCANCEL),
KeySz = wxStaticBoxSizer:new(?wxVERTICAL, Dialog, [{label, J("Signature Key")}]),
KeyPicker = wxChoice:new(Dialog, ?wxID_ANY, [{choices, Keys}]),
_ = wxStaticBoxSizer:add(KeySz, KeyPicker, zxw:flags(wide)),
ok = wxChoice:setSelection(KeyPicker, Selected - 1),
ButtSz = wxBoxSizer:new(?wxHORIZONTAL),
Affirm = wxButton:new(Dialog, ?wxID_OK),
Cancel = wxButton:new(Dialog, ?wxID_CANCEL),
_ = wxBoxSizer:add(ButtSz, Affirm, zxw:flags(wide)),
_ = wxBoxSizer:add(ButtSz, Cancel, zxw:flags(wide)),
GridSz = wxFlexGridSizer:new(2, 4, 4),
ok = wxFlexGridSizer:setFlexibleDirection(GridSz, ?wxHORIZONTAL),
ok = wxFlexGridSizer:addGrowableCol(GridSz, 1),
@ -433,117 +588,34 @@ deploy3(State = #s{frame = Frame, j = J}, #{arguments := As}) ->
end,
ArgFields = lists:map(MakeArgField, As),
_ = wxStaticBoxSizer:add(FunSizer, GridSz, zxw:flags(wide)),
_ = wxSizer:add(Sizer, ScrollWin, zxw:flags(wide)),
_ = wxSizer:add(Sizer, ButtSz),
_ = wxSizer:add(Sizer, ScrollWin, [{proportion, 5}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(Sizer, KeySz, [{proportion, 0}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(Sizer, ButtSz, [{proportion, 1}, {flag, ?wxEXPAND}]),
ok = wxDialog:setSizer(Dialog, Sizer),
ok = wxBoxSizer:layout(Sizer),
ok = wxDialog:setSize(Dialog, {500, 300}),
ok = wxDialog:center(Dialog),
ok =
Outcome =
case wxDialog:showModal(Dialog) of
?wxID_OK ->
tell(info, "DEPLOYING!");
ID = wxChoice:getString(KeyPicker, wxChoice:getSelection(KeyPicker)),
BinID = unicode:characters_to_binary(ID),
Inputs = lists:map(fun get_arg/1, ArgFields),
{ok, BinID, Inputs};
?wxID_CANCEL ->
ok
cancel
end,
ok = wxDialog:destroy(Dialog),
case Outcome of
{ok, SigID, Args} -> deploy5(State, SigID, Build, Args);
cancel -> State
end.
deploy5(State, SigID, Build, Args) ->
tell(info, "Build: ~p", [Build]),
ok = gmc_con:deploy(SigID, Build, Args),
State.
find_main(ACI) ->
find_main(ACI, none, []).
find_main([#{contract := I = #{kind := contract_interface}} | T], M, Is) ->
find_main(T, M, [I | Is]);
find_main([#{contract := M = #{kind := contract_main}} | T], _, Is) ->
find_main(T, M, Is);
find_main([#{namespace := _} | T], M, Is) ->
find_main(T, M, Is);
find_main([C | T], M, Is) ->
ok = tell("Surprising ACI element: ~p", [C]),
find_main(T, M, Is);
find_main([], M, Is) ->
{M, Is}.
fun_interfaces(Window,
Buttons,
{OldScrollWin, OldIfaces},
{#{name := Name, functions := Funs}, _ConIfaces},
J) ->
ok = wxScrolledWindow:destroy(OldScrollWin),
OldButtonIDs = button_key_list(OldIfaces),
NextButtons = maps:without(OldButtonIDs, Buttons),
ScrollWin = wxScrolledWindow:new(Window),
FSOpts = [{label, J("Function Interfaces")}],
FunSizer = wxStaticBoxSizer:new(?wxVERTICAL, ScrollWin, FSOpts),
ok = wxScrolledWindow:setSizerAndFit(ScrollWin, FunSizer),
ok = wxScrolledWindow:setScrollRate(ScrollWin, 5, 5),
ConName = wxStaticText:new(ScrollWin, ?wxID_ANY, Name),
_ = wxSizer:add(FunSizer, ConName),
MakeIface =
fun(#{name := N, arguments := As}) ->
FunName = unicode:characters_to_list([N, "/", integer_to_list(length(As))]),
FN = wxStaticBoxSizer:new(?wxVERTICAL, ScrollWin, [{label, FunName}]),
GridSz = wxFlexGridSizer:new(2, 4, 4),
ok = wxFlexGridSizer:setFlexibleDirection(GridSz, ?wxHORIZONTAL),
ok = wxFlexGridSizer:addGrowableCol(GridSz, 1),
MakeArgField =
fun(#{name := AN, type := T}) ->
Type =
case T of
<<"address">> -> address;
<<"int">> -> integer;
<<"bool">> -> boolean;
L when is_list(L) -> list; % FIXME
% I when is_binary(I) -> iface % FIXME
I when is_binary(I) -> address % FIXME
end,
ANT = wxStaticText:new(ScrollWin, ?wxID_ANY, AN),
TCT = wxTextCtrl:new(ScrollWin, ?wxID_ANY),
_ = wxFlexGridSizer:add(GridSz, ANT, zxw:flags(base)),
_ = wxFlexGridSizer:add(GridSz, TCT, zxw:flags(wide)),
{ANT, TCT, Type}
end,
ArgFields = lists:map(MakeArgField, As),
ButtSz = wxBoxSizer:new(?wxHORIZONTAL),
{CallButton, DryRunButton} =
case N =:= <<"init">> of
false ->
CallBn = wxButton:new(ScrollWin, ?wxID_ANY, [{label, J("Call")}]),
DryRBn = wxButton:new(ScrollWin, ?wxID_ANY, [{label, J("Dry Run")}]),
true = wxButton:disable(CallBn),
true = wxButton:disable(DryRBn),
_ = wxBoxSizer:add(ButtSz, CallBn, zxw:flags(wide)),
_ = wxBoxSizer:add(ButtSz, DryRBn, zxw:flags(wide)),
{#w{name = {N, call}, id = wxButton:getId(CallBn), wx = CallBn},
#w{name = {N, dryr}, id = wxButton:getId(DryRBn), wx = DryRBn}};
true ->
Deploy = wxButton:new(ScrollWin, ?wxID_ANY, [{label, J("Deploy")}]),
_ = wxBoxSizer:add(ButtSz, Deploy, zxw:flags(wide)),
{#w{name = {N, call}, id = wxButton:getId(Deploy), wx = Deploy},
none}
end,
_ = wxStaticBoxSizer:add(FN, GridSz, zxw:flags(wide)),
_ = wxStaticBoxSizer:add(FN, ButtSz, zxw:flags(base)),
_ = wxSizer:add(FunSizer, FN, zxw:flags(base)),
#f{name = N, call = CallButton, dryrun = DryRunButton, args = ArgFields}
end,
Ifaces = lists:map(MakeIface, Funs),
NewButtons = lists:foldl(fun map_iface_buttons/2, NextButtons, Ifaces),
ok = wxSizer:layout(FunSizer),
{NewButtons, {ScrollWin, Ifaces}}.
button_key_list([#f{call = #w{id = C}, dryrun = #w{id = D}} | T]) ->
[C, D | button_key_list(T)];
button_key_list([#f{call = #w{id = C}, dryrun = none} | T]) ->
[C | button_key_list(T)];
button_key_list([]) ->
[].
map_iface_buttons(#f{call = C = #w{id = CID}, dryrun = D = #w{id = DID}}, A) ->
maps:put(DID, D, maps:put(CID, C, A));
map_iface_buttons(#f{call = C = #w{id = CID}, dryrun = none}, A) ->
maps:put(CID, C, A).
open(State = #s{frame = Frame, j = J}) ->
Dialog = wxDialog:new(Frame, ?wxID_ANY, J("Open Contract Source")),
@ -649,7 +721,7 @@ open_hash(State = #s{frame = Frame, j = J}) ->
ok = wxBoxSizer:layout(Sizer),
ok = wxDialog:setSize(Dialog, {500, 200}),
ok = wxDialog:center(Dialog),
ok = wxStyledTextCtrl:setFocus(AddressTx),
ok = wxTextCtrl:setFocus(AddressTx),
Choice =
case wxDialog:showModal(Dialog) of
?wxID_OK ->
@ -677,7 +749,8 @@ open_hash2(State, Address) ->
open_hash3(State, Address, Source) ->
% TODO: Compile on load and verify the deployed hash for validity.
case aeso_compiler:from_string(Source, [{aci, json}]) of
Options = sophia_options(),
case so_compiler:from_string(Source, Options) of
{ok, Build = #{aci := ACI}} ->
{Defs = #{functions := Funs}, ConIfaces} = find_main(ACI),
Callable = lom:delete(name, <<"init">>, Funs),
@ -698,7 +771,7 @@ save(State = #s{frame = Frame, j = J, prefs = Prefs, code = {Codebook, Pages}})
Index ->
case lists:nth(Index + 1, Pages) of
#p{path = {file, Path}, code = Widget} ->
Source = wxStyledTextCtrl:getText(Widget),
Source = wxTextCtrl:getValue(Widget),
case filelib:ensure_dir(Path) of
ok ->
case file:write_file(Path, Source) of
@ -864,7 +937,7 @@ load(State = #s{frame = Frame, j = J}) ->
ok = wxBoxSizer:layout(Sizer),
ok = wxDialog:setSize(Dialog, {500, 200}),
ok = wxDialog:center(Dialog),
ok = wxStyledTextCtrl:setFocus(AddressTx),
ok = wxTextCtrl:setFocus(AddressTx),
Choice =
case wxDialog:showModal(Dialog) of
?wxID_OK ->
@ -890,26 +963,12 @@ load2(State, Address) ->
State
end.
load3(State, Address, Source) ->
% TODO: Compile on load and verify the deployed hash for validity.
case aeso_compiler:from_string(Source, [{aci, json}]) of
{ok, Build = #{aci := ACI}} ->
{Defs = #{functions := Funs}, ConIfaces} = find_main(ACI),
Callable = lom:delete(name, <<"init">>, Funs),
FunDefs = {maps:put(functions, Callable, Defs), ConIfaces},
ok = tell(info, "Compilation Succeeded!~n~tp~n~n~tp", [Build, FunDefs]),
add_instance_page(State, Address, Source);
Other ->
ok = tell(info, "Compilation Failed!~n~tp", [Other]),
State
end.
add_instance_page(State = #s{cons = {Consbook, Pages}, j = J}, Address, Source) ->
load3(State = #s{tabs = TopBook, cons = {Consbook, Pages}, buttons = Buttons, j = J},
Address,
Source) ->
Window = wxWindow:new(Consbook, ?wxID_ANY),
PageSz = wxBoxSizer:new(?wxVERTICAL),
ProgSz = wxBoxSizer:new(?wxHORIZONTAL),
CodeSz = wxStaticBoxSizer:new(?wxVERTICAL, Window, [{label, J("Contract Source")}]),
CodeTxStyle = {style, ?wxTE_MULTILINE
bor ?wxTE_PROCESS_TAB
@ -922,52 +981,175 @@ add_instance_page(State = #s{cons = {Consbook, Pages}, j = J}, Address, Source)
true = wxTextCtrl:setDefaultStyle(CodeTx, TextAt),
ok = wxTextCtrl:setValue(CodeTx, Source),
_ = wxSizer:add(CodeSz, CodeTx, zxw:flags(wide)),
ScrollWin = wxScrolledWindow:new(Window),
FunSz = wxStaticBoxSizer:new(?wxVERTICAL, ScrollWin, [{label, J("Function Interfaces")}]),
ok = wxWindow:setSizer(ScrollWin, FunSz),
ok = wxScrolledWindow:setSizerAndFit(ScrollWin, FunSz),
ok = wxScrolledWindow:setScrollRate(ScrollWin, 5, 5),
ConsSz = wxStaticBoxSizer:new(?wxVERTICAL, Window, [{label, J("Console")}]),
ConsTxStyle = {style, ?wxTE_MULTILINE bor ?wxTE_READONLY},
ConsTx = wxTextCtrl:new(Window, ?wxID_ANY, [ConsTxStyle]),
_ = wxSizer:add(ConsSz, ConsTx, zxw:flags(wide)),
_ = wxSizer:add(ProgSz, CodeSz, [{proportion, 3}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(ProgSz, CodeSz, [{proportion, 2}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(ProgSz, ScrollWin, [{proportion, 1}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(PageSz, ProgSz, [{proportion, 3}, {flag, ?wxEXPAND}]),
_ = wxSizer:add(PageSz, ConsSz, [{proportion, 1}, {flag, ?wxEXPAND}]),
{Out, IFaces, Build, NewButtons} =
case compile(Source) of
{ok, B = #{aci := ACI}} ->
{#{functions := Fs}, _} = find_main(ACI),
Callable = lom:delete(name, <<"init">>, Fs),
{NB, IFs} = fun_interfaces(ScrollWin, FunSz, Buttons, Callable, J),
O = io_lib:format("Compilation Succeeded!~n~tp~n~nDone!~n", [B]),
{O, IFs, B, NB};
Other ->
O = io_llib:format("Compilation Failed!~n~tp~n", [Other]),
{O, [], none, Buttons}
end,
ok = wxWindow:setSizer(Window, PageSz),
ok = wxSizer:layout(PageSz),
true = wxNotebook:addPage(Consbook, Window, Address, [{bSelect, true}]),
Page = #c{id = Address, win = Window,
code = CodeTx, cons = ConsTx,
funs = {ScrollWin, []}},
build = Build, funs = {ScrollWin, IFaces}},
NewPages = Pages ++ [Page],
State#s{cons = {Consbook, NewPages}}.
ok = wxTextCtrl:appendText(ConsTx, Out),
_ = wxNotebook:changeSelection(TopBook, 1),
% TODO: Verify the deployed hash for validity.
State#s{cons = {Consbook, NewPages}, buttons = NewButtons}.
edit(State) ->
ok = tell(info, "EDIT clicked"),
State.
get_arg({_, TextCtrl, _}) ->
wxTextCtrl:getValue(TextCtrl).
find_main(ACI) ->
find_main(ACI, none, []).
find_main([#{contract := I = #{kind := contract_interface}} | T], M, Is) ->
find_main(T, M, [I | Is]);
find_main([#{contract := M = #{kind := contract_main}} | T], _, Is) ->
find_main(T, M, Is);
find_main([#{namespace := _} | T], M, Is) ->
find_main(T, M, Is);
find_main([C | T], M, Is) ->
ok = tell("Surprising ACI element: ~p", [C]),
find_main(T, M, Is);
find_main([], M, Is) ->
{M, Is}.
fun_interfaces(ScrollWin, FunSz, Buttons, Funs, J) ->
MakeIface =
fun(#{name := N, arguments := As}) ->
FunName = unicode:characters_to_list([N, "/", integer_to_list(length(As))]),
FN = wxStaticBoxSizer:new(?wxVERTICAL, ScrollWin, [{label, FunName}]),
GridSz = wxFlexGridSizer:new(2, 4, 4),
ok = wxFlexGridSizer:setFlexibleDirection(GridSz, ?wxHORIZONTAL),
ok = wxFlexGridSizer:addGrowableCol(GridSz, 1),
MakeArgField =
fun(#{name := AN, type := T}) ->
Type =
case T of
<<"address">> -> address;
<<"int">> -> integer;
<<"bool">> -> boolean;
L when is_list(L) -> list; % FIXME
% I when is_binary(I) -> iface % FIXME
I when is_binary(I) -> address % FIXME
end,
ANT = wxStaticText:new(ScrollWin, ?wxID_ANY, AN),
TCT = wxTextCtrl:new(ScrollWin, ?wxID_ANY),
_ = wxFlexGridSizer:add(GridSz, ANT, zxw:flags(base)),
_ = wxFlexGridSizer:add(GridSz, TCT, zxw:flags(wide)),
{ANT, TCT, Type}
end,
ArgFields = lists:map(MakeArgField, As),
ButtSz = wxBoxSizer:new(?wxHORIZONTAL),
{CallButton, DryRunButton} =
case N =:= <<"init">> of
false ->
CallBn = wxButton:new(ScrollWin, ?wxID_ANY, [{label, J("Call")}]),
DryRBn = wxButton:new(ScrollWin, ?wxID_ANY, [{label, J("Dry Run")}]),
_ = wxBoxSizer:add(ButtSz, CallBn, zxw:flags(wide)),
_ = wxBoxSizer:add(ButtSz, DryRBn, zxw:flags(wide)),
{#w{name = {N, call}, id = wxButton:getId(CallBn), wx = CallBn},
#w{name = {N, dryr}, id = wxButton:getId(DryRBn), wx = DryRBn}};
true ->
Deploy = wxButton:new(ScrollWin, ?wxID_ANY, [{label, J("Deploy")}]),
_ = wxBoxSizer:add(ButtSz, Deploy, zxw:flags(wide)),
{#w{name = {N, call}, id = wxButton:getId(Deploy), wx = Deploy},
none}
end,
_ = wxStaticBoxSizer:add(FN, GridSz, zxw:flags(wide)),
_ = wxStaticBoxSizer:add(FN, ButtSz, zxw:flags(base)),
_ = wxSizer:add(FunSz, FN, zxw:flags(base)),
#f{name = N, call = CallButton, dryrun = DryRunButton, args = ArgFields}
end,
IFaces = lists:map(MakeIface, Funs),
NewButtons = lists:foldl(fun map_iface_buttons/2, Buttons, IFaces),
{NewButtons, IFaces}.
map_iface_buttons(#f{call = C = #w{id = CID}, dryrun = D = #w{id = DID}}, A) ->
maps:put(DID, D, maps:put(CID, C, A));
map_iface_buttons(#f{call = C = #w{id = CID}, dryrun = none}, A) ->
maps:put(CID, C, A).
close_instance(State) ->
ok = tell(info, "CLOSE_INSTANCE clicked"),
State.
edit(State = #s{cons = {Consbook, Pages}}) ->
case wxNotebook:getSelection(Consbook) of
?wxNOT_FOUND ->
State;
Index ->
#c{code = CodeTx} = lists:nth(Index + 1, Pages),
Address = wxNotebook:getPageText(Consbook, Index),
Source = wxTextCtrl:getValue(CodeTx),
add_code_page(State, {hash, Address}, Source)
end.
close_instance(State = #s{cons = {Consbook, Pages}, buttons = Buttons}) ->
case wxNotebook:getSelection(Consbook) of
?wxNOT_FOUND ->
State;
Index ->
{#c{funs = {_, IFaces}}, NewPages} = take_nth(Index + 1, Pages),
IDs = list_iface_buttons(IFaces),
NewButtons = maps:without(IDs, Buttons),
true = wxNotebook:deletePage(Consbook, Index),
State#s{cons = {Consbook, NewPages}, buttons = NewButtons}
end.
list_iface_buttons(IFaces) ->
lists:foldl(fun list_iface_buttons/2, [], IFaces).
list_iface_buttons(#f{call = #w{id = CID}, dryrun = #w{id = DID}}, A) ->
[CID, DID | A].
%% Incomplete compiler wrangling
compile(Source) ->
Options = sophia_options(),
so_compiler:from_string(Source, Options).
sophia_options() ->
[{aci, json}].
%% (Somewhat silly) Data operations
store_nth(1, E, [_ | T]) -> [E | T];
store_nth(N, E, [H | T]) -> [H | store_nth(N - 1, T, E)].
store_nth(N, E, [H | T]) -> [H | store_nth(N - 1, E, T)].
drop_nth(1, [_ | T]) -> T;
drop_nth(N, [H | T]) -> [H | drop_nth(N - 1, T)].
take_nth(N, L) ->
take_nth(N, L, []).
take_nth(1, [E | T], A) -> {E, lists:reverse(A) ++ T};
take_nth(N, [H | T], A) -> take_nth(N - 1, T, [H | A]).
keyfind_index(K, E, L) ->
keyfind_index(K, E, 1, L).

View File

@ -2,15 +2,15 @@
{type,gui}.
{modules,[]}.
{prefix,"gmc"}.
{desc,"A desktop client for the Gajumaru network of blockchain networks"}.
{author,"Craig Everett"}.
{desc,"A desktop client for the Gajumaru network of blockchain networks"}.
{package_id,{"otpr","clutch",{0,2,0}}}.
{deps,[{"otpr","lom",{1,0,0}},
{"otpr","hakuzaru",{0,2,0}},
{"otpr","aesophia",{8,0,1}},
{"otpr","aeserialization",{0,1,2}},
{deps,[{"otpr","sophia",{9,0,0}},
{"otpr","hakuzaru",{0,3,0}},
{"otpr","gmbytecode",{3,4,1}},
{"otpr","lom",{1,0,0}},
{"otpr","gmserialization",{0,1,2}},
{"otpr","zj",{1,1,0}},
{"otpr","aebytecode",{3,2,1}},
{"otpr","erl_base58",{0,1,0}},
{"otpr","eblake2",{1,0,0}},
{"otpr","ec_utils",{1,0,0}},