Skip to content

Commit

Permalink
fix text conversions: expect unicode
Browse files Browse the repository at this point in the history
  • Loading branch information
vladdu committed Jun 21, 2017
1 parent f2a4559 commit eb066cf
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 6 deletions.
2 changes: 1 addition & 1 deletion common/apps/erlide_builder/src/erlide_builder.erl
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ compile_options(F, Options, OutputDir) ->
format_compile_msg(L, Marker) when is_list(L) ->
lists:flatten([format_compile_msg(X, Marker) || X <- L]);
format_compile_msg({File, L}, Marker) ->
[{Ln, File, iolist_to_binary(M:format_error(D)), Marker} || {Ln, M, D} <- L].
[{Ln, File, unicode:characters_to_binary(lists:flatten(M:format_error(D))), Marker} || {Ln, M, D} <- L].

mk_includes(L) ->
[{i, X} || X <- L].
Expand Down
2 changes: 1 addition & 1 deletion ide/apps/erlide_ide_core/src/erlide_scanner.erl
Original file line number Diff line number Diff line change
Expand Up @@ -135,5 +135,5 @@ convert_tokens(Tokens) ->
G = case is_list(Txt) of true -> length(Txt); _ -> byte_size(Txt) end,
<<(kind_small(Kind)), L:24, O:24, G:24>>
end,
erlang:iolist_to_binary([Fun(X) || X <- Tokens]).
unicode:characters_to_binary(lists:flatten([Fun(X) || X <- Tokens])).

8 changes: 4 additions & 4 deletions server/apps/erlide_server/src/erlide_lsp_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,7 @@ handle_cast({'textDocument/rename', Id, #{textDocument:=#{uri:=URI}, position:=P
handle_cast({show_message, Type, Msg}, State = #state{proxy = Proxy}) ->
Proxy ! {notify, 'window/showMessage',
#{type => Type,
message => iolist_to_binary(Msg)}},
message => unicode:characters_to_binary(Msg)}},
{noreply, State};
handle_cast({show_message_request, Type, Msg, Actions, Pid}, State = #state{proxy = Proxy}) ->
Id = State#state.crt_id,
Expand All @@ -178,14 +178,14 @@ handle_cast({show_message_request, Type, Msg, Actions, Pid}, State = #state{prox
},
Proxy ! {request, Id, 'window/showMessageRequest',
#{type => Type,
message => iolist_to_binary(Msg),
message => unicode:characters_to_binary(Msg),
actions => Actions}
},
{noreply, NewState};
handle_cast({log_message, Type, Msg}, State = #state{proxy = Proxy}) ->
Proxy ! {notify, 'window/logMessage',
#{type => Type,
message => iolist_to_binary(Msg)}},
message => unicode:characters_to_binary(Msg)}},
{noreply, State};
handle_cast({telemetry_event, Msg}, State = #state{proxy = Proxy}) ->
Proxy ! {notify, 'telemetry/event', Msg},
Expand All @@ -209,7 +209,7 @@ handle_cast({_F, _A}=Other, State) ->
{noreply, State};
handle_cast({F, Id, A}, State) ->
FN = atom_to_binary(F, latin1),
AN = iolist_to_binary(io_lib:format("~p~n", [A])),
AN = unicode:characters_to_binary(lists:flatten(io_lib:format("~p~n", [A]))),
io:format("Unrecognized operation ~p~n", [{FN, AN}]),
reply(State, Id, #{error => #{code => method_not_found,
message => <<"Unrecognized method ", FN/binary,
Expand Down

0 comments on commit eb066cf

Please sign in to comment.