Merge pull request 'First stab at supporting syntax highlighting via wxStyledTextCtrl' (#8) from uw-syntax-highlighting into master
Reviewed-on: #8 Reviewed-by: Craig Everett <craigeverett@qpq.swiss>
This commit is contained in:
commit
509f36c403
@ -652,7 +652,7 @@ 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 := SecKey}} ->
|
||||
Sig = base64:encode(sign_message(list_to_binary(Message), SecKey)),
|
||||
Sig = base64:encode(hz:sign_message(list_to_binary(Message), SecKey)),
|
||||
do_sign_mess2(Request#{"signature" => Sig});
|
||||
false ->
|
||||
gd_gui:trouble({bad_key, ID})
|
||||
@ -675,37 +675,6 @@ do_sign_mess2(Request = #{"url" := URL}) ->
|
||||
end.
|
||||
|
||||
|
||||
% TODO: Should probably be part of Hakuzaru
|
||||
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, SecKey).
|
||||
|
||||
|
||||
vencode(N) when N < 0 ->
|
||||
{error, {negative_N, N}};
|
||||
vencode(N) when N < 16#FD ->
|
||||
{ok, <<N>>};
|
||||
vencode(N) when N =< 16#FFFF ->
|
||||
NBytes = eu(N, 2),
|
||||
{ok, <<16#FD, NBytes/binary>>};
|
||||
vencode(N) when N =< 16#FFFF_FFFF ->
|
||||
NBytes = eu(N, 4),
|
||||
{ok, <<16#FE, NBytes/binary>>};
|
||||
vencode(N) when N < (2 bsl 64) ->
|
||||
NBytes = eu(N, 8),
|
||||
{ok, <<16#FF, NBytes/binary>>}.
|
||||
|
||||
eu(N, Size) ->
|
||||
Bytes = binary:encode_unsigned(N, little),
|
||||
NExtraZeros = Size - byte_size(Bytes),
|
||||
ExtraZeros = << <<0>> || _ <- lists:seq(1, NExtraZeros) >>,
|
||||
<<Bytes/binary, ExtraZeros/binary>>.
|
||||
|
||||
|
||||
do_sign_tx(Request = #{"public_id" := ID, "payload" := CallData, "network_id" := NID},
|
||||
#s{wallet = #wallet{keys = Keys}}) ->
|
||||
BinNID = list_to_binary(NID),
|
||||
@ -862,7 +831,9 @@ do_make_key2(Name, Bin, Transform,
|
||||
#wallet{name = WalletName, poas = POAs, keys = Keys} = Current,
|
||||
T = transform(Transform),
|
||||
Seed = T(Bin),
|
||||
Key = #key{name = KeyName, id = ID} = gd_key_master:make_key(Name, Seed),
|
||||
{ID, Pair} = hz_key_master:make_key(Seed),
|
||||
KeyName = case Name =:= "" of true -> ID; false -> Name end,
|
||||
Key = #key{name = KeyName, id = ID, pair = Pair},
|
||||
POA = #poa{name = KeyName, id = ID},
|
||||
NewKeys = [Key | Keys],
|
||||
NewPOAs = [POA | POAs],
|
||||
@ -901,7 +872,7 @@ t_xor(B, A) ->
|
||||
|
||||
|
||||
do_recover_key(Mnemonic, State) ->
|
||||
case gd_key_master:decode(Mnemonic) of
|
||||
case hz_key_master:decode(Mnemonic) of
|
||||
{ok, Seed} ->
|
||||
do_recover_key2(Seed, State);
|
||||
Error ->
|
||||
@ -911,7 +882,7 @@ do_recover_key(Mnemonic, State) ->
|
||||
|
||||
do_recover_key2(Seed, State = #s{wallet = Current, wallets = Wallets, pass = Pass}) ->
|
||||
#wallet{name = WalletName, keys = Keys, poas = POAs} = Current,
|
||||
Recovered = #key{id = ID, name = AccName} = gd_key_master:make_key("", Seed),
|
||||
Recovered = #key{id = ID, name = AccName} = hz_key_master:make_key("", Seed),
|
||||
case lists:keymember(ID, #key.id, Keys) of
|
||||
false ->
|
||||
NewKeys = [Recovered | Keys],
|
||||
@ -930,7 +901,7 @@ do_recover_key2(Seed, State = #s{wallet = Current, wallets = Wallets, pass = Pas
|
||||
do_mnemonic(ID, #s{wallet = #wallet{keys = Keys}}) ->
|
||||
case lists:keyfind(ID, #key.id, Keys) of
|
||||
#key{pair = #{secret := <<K:32/binary, _/binary>>}} ->
|
||||
Mnemonic = gd_key_master:encode(K),
|
||||
Mnemonic = hz_key_master:encode(K),
|
||||
{ok, Mnemonic};
|
||||
false ->
|
||||
{error, bad_key}
|
||||
|
@ -1,164 +0,0 @@
|
||||
%%% @doc
|
||||
%%% Key functions go here.
|
||||
%%%
|
||||
%%% The main reason this is a module of its own is that in the original architecture
|
||||
%%% it was a process rather than just a library of functions. Now that it exists, though,
|
||||
%%% there is little motivation to cram everything here into the controller process's
|
||||
%%% code.
|
||||
%%% @end
|
||||
|
||||
-module(gd_key_master).
|
||||
-vsn("0.5.4").
|
||||
|
||||
|
||||
-export([make_key/2, encode/1, decode/1]).
|
||||
-export([lcg/1]).
|
||||
-include("gd.hrl").
|
||||
|
||||
|
||||
make_key("", <<>>) ->
|
||||
Pair = #{public := Public} = ecu_eddsa:sign_keypair(),
|
||||
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 = 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 = 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 = gmser_api_encoder:encode(account_pubkey, Public),
|
||||
#key{name = Name, id = ID, pair = Pair}.
|
||||
|
||||
|
||||
-spec encode(Secret) -> Phrase
|
||||
when Secret :: binary(),
|
||||
Phrase :: string().
|
||||
%% @doc
|
||||
%% The encoding and decoding procesures are written to be able to handle any
|
||||
%% width of bitstring or binary and a variable size dictionary. The magic numbers
|
||||
%% 32, 4096 and 12 have been dropped in because currently these are known, but that
|
||||
%% will change in the future if the key size or type changes.
|
||||
|
||||
encode(Bin) ->
|
||||
<<Number:(32 * 8)>> = Bin,
|
||||
DictSize = 4096,
|
||||
Words = read_words(),
|
||||
% Width = chunksize(DictSize - 1, 2),
|
||||
Width = 12,
|
||||
Chunks = chunksize(Number, DictSize),
|
||||
Binary = <<Number:(Chunks * Width)>>,
|
||||
encode(Width, Binary, Words).
|
||||
|
||||
encode(Width, Bits, Words) ->
|
||||
CheckSum = checksum(Width, Bits),
|
||||
encode(Width, <<CheckSum:Width, Bits/bitstring>>, Words, []).
|
||||
|
||||
encode(_, <<>>, _, Acc) ->
|
||||
unicode:characters_to_list(lists:join(" ", lists:reverse(Acc)));
|
||||
encode(Width, Bits, Words, Acc) ->
|
||||
<<I:Width, Rest/bitstring>> = Bits,
|
||||
Word = lists:nth(I + 1, Words),
|
||||
encode(Width, Rest, Words, [Word | Acc]).
|
||||
|
||||
|
||||
-spec decode(Phrase) -> {ok, Secret} | {error, Reason}
|
||||
when Phrase :: string(),
|
||||
Secret :: binary(),
|
||||
Reason :: bad_phrase | bad_word.
|
||||
%% @doc
|
||||
%% Reverses the encoded secret string back into its binary representation.
|
||||
|
||||
decode(Encoded) ->
|
||||
DictSize = 4096,
|
||||
Words = read_words(),
|
||||
Width = chunksize(DictSize - 1, 2),
|
||||
decode(Width, Words, Encoded).
|
||||
|
||||
decode(Width, Words, Encoded) when is_list(Encoded) ->
|
||||
decode(Width, Words, list_to_binary(Encoded));
|
||||
decode(Width, Words, Encoded) ->
|
||||
Split = string:lexemes(Encoded, " "),
|
||||
decode(Width, Words, Split, <<>>).
|
||||
|
||||
decode(Width, Words, [Word | Rest], Acc) ->
|
||||
case find(Word, Words) of
|
||||
{ok, N} -> decode(Width, Words, Rest, <<Acc/bitstring, N:Width>>);
|
||||
Error -> Error
|
||||
end;
|
||||
decode(Width, _, [], Acc) ->
|
||||
sumcheck(Width, Acc).
|
||||
|
||||
|
||||
chunksize(N, C) ->
|
||||
chunksize(N, C, 0).
|
||||
|
||||
chunksize(0, _, A) -> A;
|
||||
chunksize(N, C, A) -> chunksize(N div C, C, A + 1).
|
||||
|
||||
|
||||
read_words() ->
|
||||
Path = filename:join([zx:get_home(), "priv", "words4096.txt"]),
|
||||
{ok, Bin} = file:read_file(Path),
|
||||
string:lexemes(Bin, "\n").
|
||||
|
||||
|
||||
find(Word, Words) ->
|
||||
find(Word, Words, 0).
|
||||
|
||||
find(Word, [Word | _], N) -> {ok, N};
|
||||
find(Word, [_ | Rest], N) -> find(Word, Rest, N + 1);
|
||||
find(Word, [], _) -> {error, {bad_word, Word}}.
|
||||
|
||||
|
||||
checksum(Width, Bits) ->
|
||||
checksum(Width, Bits, 0).
|
||||
|
||||
checksum(_, <<>>, Sum) ->
|
||||
Sum;
|
||||
checksum(Width, Bits, Sum) ->
|
||||
<<N:Width, Rest/bitstring>> = Bits,
|
||||
checksum(Width, Rest, N bxor Sum).
|
||||
|
||||
|
||||
sumcheck(Width, Bits) ->
|
||||
<<CheckSum:Width, Binary/bitstring>> = Bits,
|
||||
case checksum(Width, Binary) =:= CheckSum of
|
||||
true ->
|
||||
<<N:(bit_size(Binary))>> = Binary,
|
||||
{ok, <<N:(32 * 8)>>};
|
||||
false ->
|
||||
{error, bad_phrase}
|
||||
end.
|
||||
|
||||
|
||||
|
||||
-spec lcg(integer()) -> integer().
|
||||
%% A simple PRNG that fits into 32 bits and is easy to implement anywhere (Kotlin).
|
||||
%% Specifically, it is a "linear congruential generator" of the Lehmer variety.
|
||||
%% The constants used are based on recommendations from Park, Miller and Stockmeyer:
|
||||
%% https://www.firstpr.com.au/dsp/rand31/p105-crawford.pdf#page=4
|
||||
%%
|
||||
%% The input value should be between 1 and 2^31-1.
|
||||
%%
|
||||
%% The purpose of this PRNG is for password-based dictionary shuffling.
|
||||
|
||||
lcg(N) ->
|
||||
M = 16#7FFFFFFF,
|
||||
A = 48271,
|
||||
Q = 44488, % M div A
|
||||
R = 3399, % M rem A
|
||||
Div = N div Q,
|
||||
Rem = N rem Q,
|
||||
S = Rem * A,
|
||||
T = Div * R,
|
||||
Result = S - T,
|
||||
case Result < 0 of
|
||||
false -> Result;
|
||||
true -> Result + M
|
||||
end.
|
193
src/gd_sophia_editor.erl
Normal file
193
src/gd_sophia_editor.erl
Normal file
@ -0,0 +1,193 @@
|
||||
-module(gd_sophia_editor).
|
||||
-export([new/1, update/2,
|
||||
get_text/1, set_text/2]).
|
||||
|
||||
-include("$zx_include/zx_logger.hrl").
|
||||
-include_lib("wx/include/wx.hrl").
|
||||
|
||||
|
||||
%%% Formatting Constants
|
||||
|
||||
%% Style labels
|
||||
-define(DEFAULT, 0).
|
||||
-define(KEYWORD, 1).
|
||||
-define(IDENTIFIER, 2).
|
||||
-define(COMMENT, 3).
|
||||
-define(STRING, 4).
|
||||
-define(NUMBER, 5).
|
||||
-define(OPERATOR, 6).
|
||||
|
||||
|
||||
|
||||
%% Color palette
|
||||
|
||||
% Intensities:
|
||||
-define(H, 255). % High
|
||||
-define(M, 192). % Medium
|
||||
-define(L, 128). % Low
|
||||
-define(X, 32). % X-Low
|
||||
-define(Z, 0). % Zilch
|
||||
|
||||
|
||||
% RGB values
|
||||
% R G B
|
||||
-define(black, {?Z, ?Z, ?Z}).
|
||||
-define(light_red, {?H, ?Z, ?Z}).
|
||||
-define(light_green, {?Z, ?H, ?Z}).
|
||||
-define(light_blue, {?Z, ?Z, ?H}).
|
||||
-define(yellow, {?H, ?H, ?Z}).
|
||||
-define(light_magenta, {?H, ?Z, ?H}).
|
||||
-define(light_cyan, {?Z, ?H, ?H}).
|
||||
-define(high_white, {?H, ?H, ?H}).
|
||||
-define(red, {?L, ?Z, ?Z}).
|
||||
-define(green, {?Z, ?L, ?Z}).
|
||||
-define(blue, {?Z, ?Z, ?L}).
|
||||
-define(brown, {?L, ?L, ?Z}).
|
||||
-define(magenta, {?L, ?Z, ?L}).
|
||||
-define(cyan, {?Z, ?L, ?L}).
|
||||
-define(not_black, {?X, ?X, ?X}).
|
||||
-define(grey, {?L, ?L, ?L}).
|
||||
-define(white, {?M, ?M, ?M}).
|
||||
|
||||
styles() ->
|
||||
[?DEFAULT,
|
||||
?KEYWORD,
|
||||
?IDENTIFIER,
|
||||
?COMMENT,
|
||||
?STRING,
|
||||
?NUMBER,
|
||||
?OPERATOR].
|
||||
|
||||
palette(light) ->
|
||||
#{?DEFAULT => ?black,
|
||||
?KEYWORD => ?blue,
|
||||
?IDENTIFIER => ?cyan,
|
||||
?COMMENT => ?grey,
|
||||
?STRING => ?red,
|
||||
?NUMBER => ?magenta,
|
||||
?OPERATOR => ?brown,
|
||||
bg => ?high_white};
|
||||
palette(dark) ->
|
||||
#{?DEFAULT => ?white,
|
||||
?KEYWORD => ?light_cyan,
|
||||
?IDENTIFIER => ?green,
|
||||
?COMMENT => ?grey,
|
||||
?STRING => ?light_red,
|
||||
?NUMBER => ?light_magenta,
|
||||
?OPERATOR => ?yellow,
|
||||
bg => ?not_black}.
|
||||
|
||||
color_mode() ->
|
||||
{R, G, B, _} = wxSystemSettings:getColour(?wxSYS_COLOUR_WINDOW),
|
||||
case (lists:sum([R, G, B]) div 3) > 128 of
|
||||
true -> light;
|
||||
false -> dark
|
||||
end.
|
||||
|
||||
|
||||
new(Parent) ->
|
||||
STC = wxStyledTextCtrl:new(Parent),
|
||||
ok = wxStyledTextCtrl:setLexer(STC, ?wxSTC_LEX_CONTAINER),
|
||||
FontSize = 13,
|
||||
Mono = wxFont:new(FontSize,
|
||||
?wxFONTFAMILY_TELETYPE,
|
||||
?wxFONTSTYLE_NORMAL,
|
||||
?wxFONTWEIGHT_NORMAL,
|
||||
[{face, "Monospace"}]),
|
||||
SetMonospace = fun(Style) -> wxStyledTextCtrl:styleSetFont(STC, Style, Mono) end,
|
||||
ok = lists:foreach(SetMonospace, styles()),
|
||||
ok = wxStyledTextCtrl:styleSetFont(STC, ?wxSTC_STYLE_DEFAULT, Mono),
|
||||
ok = set_colors(STC),
|
||||
STC.
|
||||
|
||||
get_text(STC) ->
|
||||
wxStyledTextCtrl:getText(STC).
|
||||
|
||||
set_text(STC, Text) ->
|
||||
ok = wxStyledTextCtrl:setText(STC, Text),
|
||||
%% Force Scintilla to request styling for the entire text
|
||||
wxStyledTextCtrl:colourise(STC, 0, -1).
|
||||
|
||||
|
||||
set_colors(STC) ->
|
||||
ok = wxStyledTextCtrl:styleClearAll(STC),
|
||||
Palette = #{bg := BGC} = palette(color_mode()),
|
||||
Colorize =
|
||||
fun(Style) ->
|
||||
Color = maps:get(Style, Palette),
|
||||
ok = wxStyledTextCtrl:styleSetForeground(STC, Style, Color),
|
||||
ok = wxStyledTextCtrl:styleSetBackground(STC, Style, BGC)
|
||||
end,
|
||||
ok = wxStyledTextCtrl:styleSetBackground(STC, ?wxSTC_STYLE_DEFAULT, BGC),
|
||||
lists:foreach(Colorize, styles()).
|
||||
|
||||
|
||||
update(_Event, STC) ->
|
||||
Text = wxStyledTextCtrl:getText(STC),
|
||||
case so_scan:scan(Text) of
|
||||
{ok, Tokens} ->
|
||||
ok = wxStyledTextCtrl:startStyling(STC, 0),
|
||||
apply_styles(STC, Tokens);
|
||||
{error, _Reason} ->
|
||||
ok
|
||||
end.
|
||||
|
||||
|
||||
apply_styles(STC, Tokens) ->
|
||||
lists:foreach(fun(Token) -> style_token(STC, Token) end, Tokens).
|
||||
|
||||
|
||||
% FIXME: 'qid' is not properly handled. If there are multi-dot qids, they will break
|
||||
style_token(STC, Token) ->
|
||||
{Type, Value} = type_and_value(Token),
|
||||
{StartOffset, LengthOffset} = offset(Type),
|
||||
{Line, Col} = element(2, Token),
|
||||
Length = byte_size(to_binary(Value)) + LengthOffset,
|
||||
Style = classify_style(Type, Value),
|
||||
Start = wxStyledTextCtrl:positionFromLine(STC, Line - 1) + Col + StartOffset,
|
||||
wxStyledTextCtrl:startStyling(STC, Start),
|
||||
wxStyledTextCtrl:setStyling(STC, Length, Style).
|
||||
|
||||
offset(string) -> { 0, 0};
|
||||
offset(qid) -> {-1, 1};
|
||||
offset(_) -> {-1, 0}.
|
||||
|
||||
to_binary(S) when is_list(S) ->
|
||||
unicode:characters_to_binary(S);
|
||||
to_binary(S) when is_binary(S) ->
|
||||
S;
|
||||
to_binary(I) when is_integer(I) ->
|
||||
integer_to_binary(I).
|
||||
|
||||
|
||||
classify_style(Type, Value) ->
|
||||
case Type of
|
||||
symbol ->
|
||||
case lists:member(Value, keywords()) of
|
||||
true -> ?KEYWORD;
|
||||
false -> ?OPERATOR
|
||||
end;
|
||||
id -> ?IDENTIFIER;
|
||||
qid -> ?IDENTIFIER;
|
||||
con -> ?IDENTIFIER;
|
||||
qcon -> ?IDENTIFIER;
|
||||
tvar -> ?IDENTIFIER;
|
||||
string -> ?STRING;
|
||||
char -> ?STRING;
|
||||
int -> ?NUMBER;
|
||||
hex -> ?NUMBER;
|
||||
bytes -> ?NUMBER;
|
||||
skip -> ?COMMENT;
|
||||
_ -> ?DEFAULT
|
||||
end.
|
||||
|
||||
|
||||
type_and_value({Type, _Line, Value}) -> {Type, Value};
|
||||
type_and_value({Type, _}) -> {Type, atom_to_list(Type)}.
|
||||
|
||||
|
||||
keywords() ->
|
||||
["contract", "include", "let", "switch", "type", "record", "datatype", "if",
|
||||
"elif", "else", "function", "stateful", "payable", "true", "false", "mod",
|
||||
"public", "entrypoint", "private", "indexed", "namespace", "interface",
|
||||
"main", "using", "as", "for", "hiding", "band", "bor", "bxor", "bnot"].
|
@ -15,6 +15,8 @@
|
||||
-include("$zx_include/zx_logger.hrl").
|
||||
-include("gd.hrl").
|
||||
|
||||
-define(editorMode, sophia).
|
||||
|
||||
% Widgets
|
||||
-record(w,
|
||||
{name = none :: atom() | {FunName :: binary(), call | dryr},
|
||||
@ -256,6 +258,9 @@ handle_event(E = #wx{event = #wxCommand{type = command_button_clicked},
|
||||
State
|
||||
end,
|
||||
{noreply, NewState};
|
||||
handle_event(#wx{event = Event = #wxStyledText{type = stc_styleneeded}, obj = Win}, State) ->
|
||||
ok = style(State, Win, Event),
|
||||
{noreply, State};
|
||||
handle_event(#wx{event = #wxClose{}}, State = #s{frame = Frame, prefs = Prefs}) ->
|
||||
Geometry =
|
||||
case wxTopLevelWindow:isMaximized(Frame) of
|
||||
@ -291,6 +296,14 @@ terminate(Reason, State) ->
|
||||
|
||||
%%% Doers
|
||||
|
||||
style(#s{code = {_, Pages}}, Win, Event) ->
|
||||
case lists:keyfind(Win, #p.win, Pages) of
|
||||
#p{code = STC} ->
|
||||
gd_sophia_editor:update(Event, STC);
|
||||
false ->
|
||||
tell("Received bogus style event.~nWin: ~p~nEvent: ~p", [Win, Event])
|
||||
end.
|
||||
|
||||
clicked(State = #s{cons = {Consbook, Contracts}}, Name) ->
|
||||
case wxNotebook:getSelection(Consbook) of
|
||||
?wxNOT_FOUND ->
|
||||
@ -504,22 +517,13 @@ add_code_page2(State, {hash, Address}) ->
|
||||
open_hash2(State, Address).
|
||||
|
||||
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.
|
||||
% The call below returns a wx_color4() type (not that we need alpha...).
|
||||
% Color = wxSystemSettings:getColour(?wxSYS_COLOUR_WINDOW),
|
||||
% tell("Color: ~p", [Color]),
|
||||
Color = wxSystemSettings:getColour(?wxSYS_COLOUR_WINDOW),
|
||||
tell("Color: ~p", [Color]),
|
||||
Window = wxWindow:new(Codebook, ?wxID_ANY),
|
||||
PageSz = wxBoxSizer:new(?wxHORIZONTAL),
|
||||
|
||||
CodeTxStyle = {style, ?wxTE_MULTILINE bor ?wxTE_PROCESS_TAB bor ?wxTE_DONTWRAP},
|
||||
CodeTx = wxTextCtrl:new(Window, ?wxID_ANY, [CodeTxStyle]),
|
||||
TextAt = wxTextAttr:new(),
|
||||
Mono = wxFont:new(10, ?wxMODERN, ?wxNORMAL, ?wxNORMAL, [{face, "Monospace"}]),
|
||||
ok = wxTextAttr:setFont(TextAt, Mono),
|
||||
true = wxTextCtrl:setDefaultStyle(CodeTx, TextAt),
|
||||
ok = wxTextCtrl:setValue(CodeTx, Code),
|
||||
CodeTx = gd_sophia_editor:new(Window),
|
||||
ok = gd_sophia_editor:set_text(CodeTx, Code),
|
||||
|
||||
_ = wxSizer:add(PageSz, CodeTx, zxw:flags(wide)),
|
||||
|
||||
@ -531,6 +535,7 @@ add_code_page(State = #s{tabs = TopBook, code = {Codebook, Pages}}, Location, Co
|
||||
{file, Path} -> filename:basename(Path);
|
||||
{hash, Addr} -> Addr
|
||||
end,
|
||||
ok = wxStyledTextCtrl:connect(Window, stc_styleneeded),
|
||||
true = wxNotebook:addPage(Codebook, Window, FileName, [{bSelect, true}]),
|
||||
Page = #p{path = Location, win = Window, code = CodeTx},
|
||||
NewPages = Pages ++ [Page],
|
||||
@ -910,7 +915,7 @@ save(State = #s{frame = Frame, j = J, prefs = Prefs, code = {Codebook, Pages}})
|
||||
_ -> Name ++ ".aes"
|
||||
end,
|
||||
Path = filename:join(Dir, File),
|
||||
Source = wxTextCtrl:getValue(Widget),
|
||||
Source = get_source(Widget),
|
||||
case filelib:ensure_dir(Path) of
|
||||
ok ->
|
||||
case file:write_file(Path, Source) of
|
||||
@ -938,6 +943,19 @@ save(State = #s{frame = Frame, j = J, prefs = Prefs, code = {Codebook, Pages}})
|
||||
end
|
||||
end.
|
||||
|
||||
get_source(Widget) ->
|
||||
case ?editorMode of
|
||||
plain -> wxTextCtrl:getValue(Widget);
|
||||
sophia -> gd_sophia_editor:get_text(Widget)
|
||||
end.
|
||||
|
||||
set_source(Widget, Src) ->
|
||||
case ?editorMode of
|
||||
plain -> wxTextCtrl:setValue(Widget, Src);
|
||||
sophia -> gd_sophia_editor:set_text(Widget, Src)
|
||||
end.
|
||||
|
||||
|
||||
% TODO: Break this down -- tons of things in here recur.
|
||||
rename(State = #s{frame = Frame, j = J, prefs = Prefs, code = {Codebook, Pages}}) ->
|
||||
case wxNotebook:getSelection(Codebook) of
|
||||
@ -968,7 +986,7 @@ rename(State = #s{frame = Frame, j = J, prefs = Prefs, code = {Codebook, Pages}}
|
||||
_ -> Name ++ ".aes"
|
||||
end,
|
||||
NewPath = filename:join(Dir, File),
|
||||
Source = wxTextCtrl:getValue(Widget),
|
||||
Source = get_source(Widget),
|
||||
case filelib:ensure_dir(NewPath) of
|
||||
ok ->
|
||||
case file:write_file(NewPath, Source) of
|
||||
@ -1084,7 +1102,7 @@ load3(State = #s{tabs = TopBook, cons = {Consbook, Pages}, buttons = Buttons, j
|
||||
TextAt = wxTextAttr:new(),
|
||||
ok = wxTextAttr:setFont(TextAt, Mono),
|
||||
true = wxTextCtrl:setDefaultStyle(CodeTx, TextAt),
|
||||
ok = wxTextCtrl:setValue(CodeTx, Source),
|
||||
ok = set_source(CodeTx, Source),
|
||||
_ = wxSizer:add(CodeSz, CodeTx, zxw:flags(wide)),
|
||||
ScrollWin = wxScrolledWindow:new(Window),
|
||||
FunSz = wxStaticBoxSizer:new(?wxVERTICAL, ScrollWin, [{label, J("Function Interfaces")}]),
|
||||
|
@ -5,7 +5,7 @@
|
||||
{author,"Craig Everett"}.
|
||||
{desc,"A desktop client for the Gajumaru network of blockchain networks"}.
|
||||
{package_id,{"otpr","gajudesk",{0,5,4}}}.
|
||||
{deps,[{"otpr","hakuzaru",{0,5,1}},
|
||||
{deps,[{"otpr","hakuzaru",{0,6,0}},
|
||||
{"otpr","gmserialization",{0,1,3}},
|
||||
{"otpr","sophia",{9,0,0}},
|
||||
{"otpr","gmbytecode",{3,4,1}},
|
||||
|
Loading…
x
Reference in New Issue
Block a user