Skip to content

Commit e7a74b3

Browse files
author
Erlang/OTP
committed
Merge branch 'dgud/wx/fix-debug/OTP-18512' into maint-25
* dgud/wx/fix-debug/OTP-18512: wx: Use temp env for send_msg gl: Fix glDebugMessage functionality Fix tests Fix wx-3.2 macros and OpenGL support wx: Add debug printouts for OpenGL wx: Improve debug printouts
2 parents 7419d0c + 448b7ab commit e7a74b3

31 files changed

+2911
-2625
lines changed

lib/wx/api_gen/gl_gen.erl

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -358,7 +358,10 @@ handle_arg_opt({c_only,Opt},P) -> P#arg{where=c, alt=Opt};
358358
handle_arg_opt(list_binary, P) -> P#arg{alt=list_binary};
359359
handle_arg_opt(string, P=#arg{type=T}) -> P#arg{type=T#type{base=string}};
360360
handle_arg_opt({string,Max,Sz}, P=#arg{type=T}) ->
361-
P#arg{type=T#type{base=string, size={Max,Sz}}}.
361+
P#arg{type=T#type{base=string, size={Max,Sz}}};
362+
handle_arg_opt({size, Sz}, P=#arg{type=T}) ->
363+
P#arg{type=T#type{size={Sz,Sz}}}.
364+
362365

363366
parse_type([], _Os) -> void;
364367
parse_type(C, Os) ->

lib/wx/api_gen/gl_gen_erl.erl

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -88,8 +88,8 @@ gl_api(Fs, _GluNifs) ->
8888

8989
w("-on_load(init_nif/0).~n",[]),
9090
w("~n-export([~s]).~n~n", [args(fun(EF) -> EF end, ",", ExportList, 60)]),
91-
w("-export([get_interface/0, rec/1, lookup_func/0]).\n",[]),
92-
w("-nifs([lookup_func/0]).\n",[]),
91+
w("-export([get_interface/0, rec/1, lookup_func/1]).\n",[]),
92+
w("-nifs([lookup_func_nif/1]).\n",[]),
9393
w("-define(nif_stub,nif_stub_error(?LINE)).~n", []),
9494
w("%% @hidden~n", []),
9595
w("nif_stub_error(Line) ->~n"
@@ -118,7 +118,9 @@ gl_api(Fs, _GluNifs) ->
118118
w(" error_logger:error_report([{gl, error}, {message, lists:flatten(Err)}]),~n", []),
119119
w(" rec(Op)~n", []),
120120
w(" end.~n~n", []),
121-
w("lookup_func() -> ?nif_stub.\n\n",[]),
121+
w("lookup_func(functions) -> lookup_func_nif(1);\n",[]),
122+
w("lookup_func(function_names) -> lookup_func_nif(2).\n\n",[]),
123+
w("lookup_func_nif(_Func) -> ?nif_stub.\n\n",[]),
122124
w("~n", []),
123125
w("~n", []),
124126

@@ -380,6 +382,8 @@ spec_arg_type2(T=#type{single={list, _Max}}) ->
380382
"[" ++ spec_arg_type3(T) ++ "]";
381383
spec_arg_type2(T=#type{single={list,_,_}}) ->
382384
"[" ++ spec_arg_type3(T) ++ "]";
385+
spec_arg_type2(T=#type{single={list,_,_,_}}) ->
386+
"[" ++ spec_arg_type3(T) ++ "]";
383387
spec_arg_type2(T=#type{single={tuple_list,Sz}}) ->
384388
"[{" ++ args(fun spec_arg_type3/1, ",", lists:duplicate(Sz,T)) ++ "}]".
385389

lib/wx/api_gen/gl_gen_nif.erl

Lines changed: 27 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -422,8 +422,8 @@ decode_var(P=#arg{name=Name, in=true, alt=Alt,
422422

423423

424424
decode_var(P=#arg{name=Name, in=false,
425-
type=#type{name=T, base=Base, size=Szs}}, Argc)
426-
when Base =:= binary; Base =:= string ->
425+
type=#type{name=T, base=Base, size=Szs, single=Single}}, Argc)
426+
when not is_tuple(Single), (Base =:= binary orelse Base =:= string) ->
427427
Sz = case Szs of
428428
{Max,_} when is_integer(Max) -> integer_to_list(Max);
429429
{Max,_} -> Max;
@@ -454,6 +454,19 @@ decode_var(P=#arg{name=Name, in=false, type=#type{name=T,single={list,Sz,_}}}, A
454454
w(" std::vector <~s> ~s (~s);\n", [T, Name, Sz]),
455455
w(" std::vector <ERL_NIF_TERM> ~s_ts (~s);\n", [Name, Sz]),
456456
{P,Argc};
457+
decode_var(P=#arg{name=Name, in=false,
458+
type=#type{base=Base, name=T,single={list,Sz,_,_}, size=Size}}, Argc) ->
459+
case Base of
460+
string ->
461+
{BinSize, _} = Size,
462+
w(" ~s = (unsigned char *) enif_alloc((int) ~s*sizeof(~s));\n", [Name,BinSize,T]),
463+
w(" unsigned char *~s_ptr = ~s;\n", [Name,Name]),
464+
store_free(Name ++ "_ptr");
465+
_ ->
466+
exit({?LINE, Base, P})
467+
end,
468+
w(" std::vector <ERL_NIF_TERM> ~s_ts (~s);\n", [Name, Sz]),
469+
{P,Argc};
457470
decode_var(P=#arg{name=Name, in=true, type=#type{name="GLUquadric"}}, Argc) ->
458471
w(" if(!egl_get_ptr(env, argv[~w], (void **) &~s)) Badarg(~w,\"~s\");~n",
459472
[Argc, Name,?OP,Name]),
@@ -576,10 +589,6 @@ build_ret(Name,_Q,#type{name=T,base=Base,size=Sz,single=true})
576589
Ptr -> io_lib:format(" enif_make_uint64(env, (egl_uint64_t) ~s)", [Name]);
577590
true -> io_lib:format(" enif_make_int64(env, (egl_int64_t) ~s)", [Name])
578591
end;
579-
build_ret(Name,_Q,#type{base=string,single=true}) ->
580-
io_lib:format(" enif_make_string(env, (const char *) ~s, ERL_NIF_LATIN1)",[Name]);
581-
build_ret(Name,_Q,#type{base=string,size={_,_OutSz}}) ->
582-
io_lib:format(" enif_make_string(env, (const char *) ~s, ERL_NIF_LATIN1)",[Name]);
583592
build_ret(Name,_Q,#type{name=_T,base=float,size=Sz,single=true}) ->
584593
if Sz =< 4 -> io_lib:format(" enif_make_double(env, (double) ~s)", [Name]);
585594
true -> io_lib:format(" enif_make_double(env, ~s)", [Name])
@@ -602,6 +611,12 @@ build_ret(Name,false,#type{single={list,Sz}}) when Sz >= 10, is_integer(Sz) ->
602611
io_lib:format(" enif_make_list_from_array(env, ~s_ts, ~w)",[Name, Sz]);
603612
build_ret(Name,false,#type{single={list,_,Sz}}) ->
604613
io_lib:format(" enif_make_list_from_array(env, ~s_ts.data(), ~s)",[Name, Sz]);
614+
build_ret(Name,false,#type{single={list,_,Sz,_}}) ->
615+
io_lib:format(" enif_make_list_from_array(env, ~s_ts.data(), ~s)",[Name, Sz]);
616+
build_ret(Name,_Q,#type{base=string,single=true}) ->
617+
io_lib:format(" enif_make_string(env, (const char *) ~s, ERL_NIF_LATIN1)",[Name]);
618+
build_ret(Name,_Q,#type{base=string,size={_,_OutSz}}) ->
619+
io_lib:format(" enif_make_string(env, (const char *) ~s, ERL_NIF_LATIN1)",[Name]);
605620
build_ret(Name,_Q,T=#type{}) ->
606621
io:format("{~p, {~p, {single,{tuple,X}}}}.~n", [get(current_func),Name]),
607622
io:format(" ~p~n",[T]).
@@ -615,6 +630,12 @@ prepare_ret(#arg{name=Name, type=#type{single={list,_,Sz}}=T}) ->
615630
Fetch = build_ret(Name ++ "[ri]", false, T#type{single=true}),
616631
w(" for(int ri=0; ri < (int) ~s; ri++)\n"
617632
" ~s_ts[ri] = ~s;\n",[Sz, Name, Fetch]);
633+
prepare_ret(#arg{name=Name, type=#type{single={list,_,Sz,Lengths}}=T}) ->
634+
Fetch = build_ret(Name, false, T#type{single=true}),
635+
w(" for(int ri=0; ri < (int) ~s; ri++) {\n"
636+
" ~s_ts[ri] = ~s;\n",[Sz, Name, Fetch]),
637+
w(" ~s += ~s[ri];\n"
638+
" }\n", [Name, Lengths]);
618639
prepare_ret(_) ->
619640
ok.
620641

lib/wx/api_gen/glapi.conf

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -483,24 +483,16 @@
483483

484484
{"glDebugMessageControl", [{"count", {c_only, {length, "ids"}}},
485485
{"ids", {single, list}}]}.
486-
{"glDebugMessageInsertARB", {"length", {c_only, {size, "buf"}}}}.
487-
488-
{"glGetDebugMessageLogARB", [{"sources", {single, {list, "count", "result"}}},
489-
{"types", {single, {list, "count", "result"}}},
490-
{"ids", {single, {list, "count", "result"}}},
491-
{"severities", {single, {list, "count", "result"}}},
492-
{"lengths", [{c_only, undefined}, {single, {list, "count", "result"}}]},
493-
{"messageLog", [{string, "bufSize", "result"}
494-
%%,{single, {list, "bufsize", "result"}}
495-
]}]}.
486+
{"glDebugMessageInsert", {"length", {c_only, {size, "buf"}}}}.
496487

497488
{"glGetDebugMessageLog", [{"sources", {single, {list, "count", "result"}}},
498489
{"types", {single, {list, "count", "result"}}},
499490
{"ids", {single, {list, "count", "result"}}},
500491
{"severities", {single, {list, "count", "result"}}},
501492
{"lengths", [{c_only, undefined}, {single, {list, "count", "result"}}]},
502-
{"messageLog", [{string, "bufSize", "result"}
503-
%%,{single, {list, "bufsize", "result"}}
493+
{"messageLog", [
494+
{single, {list, "count", "result", "lengths"}},
495+
{size, "bufSize"}
504496
]}]}.
505497

506498

lib/wx/api_gen/wx_extra/added_func.h

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -95,3 +95,9 @@ class wxAuiNotebookEvent : public wxBookCtrlEvent {
9595
void SetDragSource(wxAuiNotebook* s) { m_dragSource = s; }
9696
wxAuiNotebook* GetDragSource() const { return m_dragSource; }
9797
};
98+
99+
class wxGLCanvas : public wxWindow
100+
{
101+
public:
102+
bool CreateSurface();
103+
};

lib/wx/api_gen/wx_gen_nif.erl

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1460,7 +1460,9 @@ gen_macros() ->
14601460
w("#if wxUSE_WEBVIEW && wxUSE_WEBVIEW_IE~n"),
14611461
w("#include <wx/msw/webview_ie.h>~n"),
14621462
w("#endif~n"),
1463-
1463+
w("#if wxUSE_GLCANVAS_EGL && !wxCHECK_VERSION(3,2,3)~n"),
1464+
w("#include <EGL/egl.h>~n"),
1465+
w("#endif~n"),
14641466

14651467
w("~n~n", []),
14661468
w("#ifndef wxICON_DEFAULT_BITMAP_TYPE~n",[]),

lib/wx/api_gen/wxapi.conf

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,10 @@
109109
{'WXK_BROWSER', {test_if, "wxCHECK_VERSION(3,1,0)"}},
110110
{'WXK_VOLUME', {test_if, "wxCHECK_VERSION(3,1,0)"}},
111111
{'WXK_MEDIA', {test_if, "wxCHECK_VERSION(3,1,0)"}},
112-
{'WXK_LAUNCH', {test_if, "wxCHECK_VERSION(3,1,0)"}},
112+
{'WXK_LAUNCH', {test_if, "wxCHECK_VERSION(3,2,0)"}},
113+
114+
%% Varies in 3.1 and 3.2
115+
wxDF_MAX,
113116

114117
{wxTOUCH, {test_if, "wxCHECK_VERSION(3,1,1)"}},
115118

@@ -1439,11 +1442,23 @@
14391442
{pre_hook, [{erl, "{ok, _} = wxe_master:init_opengl(),"}]}
14401443
]},
14411444
{'SetCurrent', [{post_hook,[{c, "setActiveGL(memenv, Ecmd.caller, This, context)"}]}]},
1445+
{'CreateSurface', [{test_if, "wxUSE_GLCANVAS_EGL"},
1446+
{pre_hook,
1447+
[{c, %% Workaround for EGL and 3.2.* crashes
1448+
"\n#if !wxCHECK_VERSION(3,2,3)\n"
1449+
" if(!This) throw wxe_badarg(0);\n"
1450+
" if(This->GetEGLSurface() != EGL_NO_SURFACE)\n"
1451+
" eglDestroySurface(This->GetEGLDisplay(), This->GetEGLSurface());\n"
1452+
"#endif\n"
1453+
}]}
1454+
]},
1455+
'IsDisplaySupported',
14421456
'SwapBuffers']}.
14431457

14441458
{class, wxGLContext, object, [{ifdef, wxUSE_GLCANVAS}],
14451459
[{'wxGLContext', [{"ctxAttrs", nowhere}]},
1446-
{'SetCurrent', [{post_hook,[{c, "setActiveGL(memenv, Ecmd.caller, win, This)"}]}]}
1460+
{'SetCurrent', [{post_hook,[{c, "setActiveGL(memenv, Ecmd.caller, win, This)"}]}]},
1461+
{'IsOK', [{test_if, "wxCHECK_VERSION(3,1,0)"}]}
14471462
]}.
14481463

14491464
{class, wxAuiManager, wxEvtHandler, [{ifdef, wxUSE_AUI}],

lib/wx/c_src/egl_impl.c

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ ERL_NIF_TERM EGL_ATOM_BADARG;
5151

5252
static ErlNifFunc egl_funcs[] =
5353
{
54-
{"lookup_func", 0, egl_lookup_func_func}
54+
{"lookup_func_nif", 1, egl_lookup_func_func}
5555
};
5656
static int egl_init(ErlNifEnv *env, void **priv_data, ERL_NIF_TERM arg)
5757
{
@@ -142,9 +142,22 @@ void * egl_lookup_func(int op)
142142
return gl_fns[op-GLE_LIB_START].nif_cb;
143143
}
144144

145+
const char * egl_lookup_func_desc(int op)
146+
{
147+
return gl_fns[op-GLE_LIB_START].name;
148+
}
149+
150+
145151
ERL_NIF_TERM egl_lookup_func_func(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
146152
{
147-
egl_uword func = (egl_uword) egl_lookup_func;
153+
egl_uword func = 0;
154+
unsigned int which;
155+
if(!(enif_get_uint(env, argv[0], &which)) && !(which == 1 || which == 2))
156+
return enif_make_badarg(env);
157+
if(which == 1)
158+
func = (egl_uword) egl_lookup_func;
159+
if(which == 2)
160+
func = (egl_uword) egl_lookup_func_desc;
148161
if(sizeof(void *) == sizeof(unsigned int))
149162
return enif_make_uint(env, (unsigned int) func);
150163
else

lib/wx/c_src/gen/gl_nif.cpp

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
/*
22
* %CopyrightBegin%
33
*
4-
* Copyright Ericsson AB 2008-2021. All Rights Reserved.
4+
* Copyright Ericsson AB 2008-2023. All Rights Reserved.
55
*
66
* Licensed under the Apache License, Version 2.0 (the "License");
77
* you may not use this file except in compliance with the License.
@@ -11518,15 +11518,13 @@ void ecb_glDebugMessageInsert(ErlNifEnv* env, ErlNifPid *self, ERL_NIF_TERM argv
1151811518
GLenum type;
1151911519
GLuint id;
1152011520
GLenum severity;
11521-
GLsizei length;
1152211521
ErlNifBinary buf;
1152311522
if(!enif_get_uint(env, argv[0], &source)) Badarg(5803,"source");
1152411523
if(!enif_get_uint(env, argv[1], &type)) Badarg(5803,"type");
1152511524
if(!enif_get_uint(env, argv[2], &id)) Badarg(5803,"id");
1152611525
if(!enif_get_uint(env, argv[3], &severity)) Badarg(5803,"severity");
11527-
if(!enif_get_int(env, argv[4], &length)) Badarg(5803,"length");
11528-
if(!enif_inspect_binary(env, argv[5], &buf)) Badarg(5803,"buf");
11529-
weglDebugMessageInsert(source,type,id,severity,length,(GLchar *) buf.data);
11526+
if(!enif_inspect_binary(env, argv[4], &buf)) Badarg(5803,"buf");
11527+
weglDebugMessageInsert(source,type,id,severity,(GLsizei) buf.size,(GLchar *) buf.data);
1153011528
}
1153111529

1153211530
void ecb_glGetDebugMessageLog(ErlNifEnv* env, ErlNifPid *self, ERL_NIF_TERM argv[])
@@ -11549,6 +11547,8 @@ void ecb_glGetDebugMessageLog(ErlNifEnv* env, ErlNifPid *self, ERL_NIF_TERM argv
1154911547
std::vector <GLsizei> lengths (count);
1155011548
std::vector <ERL_NIF_TERM> lengths_ts (count);
1155111549
messageLog = (unsigned char *) enif_alloc((int) bufSize*sizeof(GLchar));
11550+
unsigned char *messageLog_ptr = messageLog;
11551+
std::vector <ERL_NIF_TERM> messageLog_ts (count);
1155211552
result = weglGetDebugMessageLog(count,bufSize,sources.data(),types.data(),ids.data(),severities.data(),lengths.data(),(GLchar *) messageLog);
1155311553
for(int ri=0; ri < (int) result; ri++)
1155411554
sources_ts[ri] = enif_make_int(env, sources[ri]);
@@ -11558,16 +11558,20 @@ void ecb_glGetDebugMessageLog(ErlNifEnv* env, ErlNifPid *self, ERL_NIF_TERM argv
1155811558
ids_ts[ri] = enif_make_int(env, ids[ri]);
1155911559
for(int ri=0; ri < (int) result; ri++)
1156011560
severities_ts[ri] = enif_make_int(env, severities[ri]);
11561+
for(int ri=0; ri < (int) result; ri++) {
11562+
messageLog_ts[ri] = enif_make_string(env, (const char *) messageLog, ERL_NIF_LATIN1);
11563+
messageLog += lengths[ri];
11564+
}
1156111565
reply = enif_make_tuple6(env,
1156211566
enif_make_int(env, result),
1156311567
enif_make_list_from_array(env, sources_ts.data(), result),
1156411568
enif_make_list_from_array(env, types_ts.data(), result),
1156511569
enif_make_list_from_array(env, ids_ts.data(), result),
1156611570
enif_make_list_from_array(env, severities_ts.data(), result),
11567-
enif_make_string(env, (const char *) messageLog, ERL_NIF_LATIN1) );
11571+
enif_make_list_from_array(env, messageLog_ts.data(), result) );
1156811572
enif_send(NULL, self, env,
1156911573
enif_make_tuple2(env, EGL_ATOM_REPLY, reply));
11570-
enif_free(messageLog);
11574+
enif_free(messageLog_ptr);
1157111575
}
1157211576

1157311577
void ecb_glPushDebugGroup(ErlNifEnv* env, ErlNifPid *self, ERL_NIF_TERM argv[])

0 commit comments

Comments
 (0)