Skip to content

Commit b1f2974

Browse files
committed
gl: Fix glDebugMessage functionality
gl:getDebugMessageLog returned one list instead of several, and gl:debugMessageInsert had an unused lenght parameter.
1 parent cec0a67 commit b1f2974

File tree

8 files changed

+117
-64
lines changed

8 files changed

+117
-64
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: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -382,6 +382,8 @@ spec_arg_type2(T=#type{single={list, _Max}}) ->
382382
"[" ++ spec_arg_type3(T) ++ "]";
383383
spec_arg_type2(T=#type{single={list,_,_}}) ->
384384
"[" ++ spec_arg_type3(T) ++ "]";
385+
spec_arg_type2(T=#type{single={list,_,_,_}}) ->
386+
"[" ++ spec_arg_type3(T) ++ "]";
385387
spec_arg_type2(T=#type{single={tuple_list,Sz}}) ->
386388
"[{" ++ args(fun spec_arg_type3/1, ",", lists:duplicate(Sz,T)) ++ "}]".
387389

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/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[])

lib/wx/doc/src/gl.xml

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@
77
<erlref>
88
<header>
99
<copyright>
10-
<year>2020</year><year>2021</year>
10+
<year>2020</year>
1111
<holder>Ericsson AB. All Rights Reserved.</holder></copyright>
1212
<legalnotice>
1313
Licensed under the Apache License, Version 2.0 (the "License");
@@ -928,10 +928,10 @@
928928
<p><url href="https://www.khronos.org/registry/OpenGL-Refpages/gl4/html/glDebugMessageControl.xhtml">External documentation.</url></p></desc>
929929
</func>
930930
<func>
931-
<name name="debugMessageInsert" arity="6" clause_i="1" since=""/>
931+
<name name="debugMessageInsert" arity="5" clause_i="1" since=""/>
932932
<fsummary>inject an application-supplied message into the debug message queue</fsummary>
933933
<desc>
934-
<p><seemfa marker="gl#debugMessageInsert/6"><c>gl:debugMessageInsert/6</c></seemfa> inserts a user-supplied message into the debug output queue. <c>Source</c> specifies the source that will be used to classify the message and must be <c>?GL_DEBUG_SOURCE_APPLICATION</c> or <c>?GL_DEBUG_SOURCE_THIRD_PARTY</c>. All other sources are reserved for use by the GL implementation. <c>Type</c> indicates the type of the message to be inserted and may be one of <c>?GL_DEBUG_TYPE_ERROR</c>, <c>?GL_DEBUG_TYPE_DEPRECATED_BEHAVIOR</c>, <c>?GL_DEBUG_TYPE_UNDEFINED_BEHAVIOR</c>, <c>?GL_DEBUG_TYPE_PORTABILITY</c>, <c>?GL_DEBUG_TYPE_PERFORMANCE</c>, <c>?GL_DEBUG_TYPE_MARKER</c>, <c>?GL_DEBUG_TYPE_PUSH_GROUP</c>, <c>?GL_DEBUG_TYPE_POP_GROUP</c>, or <c>?GL_DEBUG_TYPE_OTHER</c>. <c>Severity</c> indicates the severity of the message and may be <c>?GL_DEBUG_SEVERITY_LOW</c>, <c>?GL_DEBUG_SEVERITY_MEDIUM</c>, <c>?GL_DEBUG_SEVERITY_HIGH</c> or <c>?GL_DEBUG_SEVERITY_NOTIFICATION</c>. <c>Id</c> is available for application defined use and may be any value. This value will be recorded and used to identify the message. </p>
934+
<p><seemfa marker="gl#debugMessageInsert/5"><c>gl:debugMessageInsert/5</c></seemfa> inserts a user-supplied message into the debug output queue. <c>Source</c> specifies the source that will be used to classify the message and must be <c>?GL_DEBUG_SOURCE_APPLICATION</c> or <c>?GL_DEBUG_SOURCE_THIRD_PARTY</c>. All other sources are reserved for use by the GL implementation. <c>Type</c> indicates the type of the message to be inserted and may be one of <c>?GL_DEBUG_TYPE_ERROR</c>, <c>?GL_DEBUG_TYPE_DEPRECATED_BEHAVIOR</c>, <c>?GL_DEBUG_TYPE_UNDEFINED_BEHAVIOR</c>, <c>?GL_DEBUG_TYPE_PORTABILITY</c>, <c>?GL_DEBUG_TYPE_PERFORMANCE</c>, <c>?GL_DEBUG_TYPE_MARKER</c>, <c>?GL_DEBUG_TYPE_PUSH_GROUP</c>, <c>?GL_DEBUG_TYPE_POP_GROUP</c>, or <c>?GL_DEBUG_TYPE_OTHER</c>. <c>Severity</c> indicates the severity of the message and may be <c>?GL_DEBUG_SEVERITY_LOW</c>, <c>?GL_DEBUG_SEVERITY_MEDIUM</c>, <c>?GL_DEBUG_SEVERITY_HIGH</c> or <c>?GL_DEBUG_SEVERITY_NOTIFICATION</c>. <c>Id</c> is available for application defined use and may be any value. This value will be recorded and used to identify the message. </p>
935935

936936
<p><url href="https://www.khronos.org/registry/OpenGL-Refpages/gl4/html/glDebugMessageInsert.xhtml">External documentation.</url></p></desc>
937937
</func>
@@ -1798,11 +1798,8 @@
17981798
<func>
17991799
<name name="getInternalformati64v" arity="4" clause_i="1" since=""/>
18001800
<name name="getInternalformativ" arity="4" clause_i="1" since=""/>
1801-
<fsummary>retrieve information about implementation-dependent support for internal formats</fsummary>
1802-
<desc>
1803-
<p><seemfa marker="gl#getInternalformativ/4"><c>gl:getInternalformativ/4</c></seemfa> and <seemfa marker="gl#getInternalformativ/4"><c>gl:getInternalformati64v/4</c></seemfa> retrieve information about implementation-dependent support for internal formats. <c>Target</c> indicates the target with which the internal format will be used and must be one of <c>?GL_RENDERBUFFER</c>, <c>?GL_TEXTURE_2D_MULTISAMPLE</c>, or <c>?GL_TEXTURE_2D_MULTISAMPLE_ARRAY</c>, corresponding to usage as a renderbuffer, two-dimensional multisample texture or two-dimensional multisample array texture, respectively. </p>
1804-
1805-
<p><url href="https://www.khronos.org/registry/OpenGL-Refpages/gl4/html/glGetInternalFormat.xhtml">External documentation.</url></p></desc>
1801+
<fsummary/>
1802+
<desc><p>No documentation available.</p></desc>
18061803
</func>
18071804
<func>
18081805
<name name="getLightfv" arity="2" clause_i="1" since=""/>

lib/wx/src/gen/gl.erl

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -238,7 +238,7 @@
238238
texStorage2DMultisample/6,texStorage3DMultisample/7,textureView/8,
239239
bindVertexBuffer/4,vertexAttribFormat/5,vertexAttribIFormat/4,vertexAttribLFormat/4,
240240
vertexAttribBinding/2,vertexBindingDivisor/2,debugMessageControl/5,
241-
debugMessageInsert/6,getDebugMessageLog/2,pushDebugGroup/4,popDebugGroup/0,
241+
debugMessageInsert/5,getDebugMessageLog/2,pushDebugGroup/4,popDebugGroup/0,
242242
objectPtrLabel/3,bufferStorage/4,clearTexImage/5,clearTexSubImage/11,
243243
bindBuffersBase/3,bindBuffersRange/5,bindTextures/2,bindSamplers/2,
244244
bindImageTextures/2,bindVertexBuffers/4,clipControl/2,createTransformFeedbacks/1,
@@ -5119,15 +5119,14 @@ debugMessageControl(Source,Type,Severity,Ids,Enabled) when is_integer(Source),is
51195119
IF:queue_cmd(Source,Type,Severity,Count,Ids,Enabled,5802),
51205120
ok.
51215121

5122-
-spec debugMessageInsert(Source, Type, Id, Severity, Length, Buf) -> 'ok'
5123-
when Source::enum(), Type::enum(), Id::i(), Severity::enum(), Length::i(), Buf::string().
5124-
debugMessageInsert(Source,Type,Id,Severity,Length,Buf) when is_integer(Source),is_integer(Type),is_integer(Id),is_integer(Severity),is_integer(Length),is_list(Buf) ->
5122+
-spec debugMessageInsert(Source::enum(), Type::enum(), Id::i(), Severity::enum(), Buf::string()) -> 'ok'.
5123+
debugMessageInsert(Source,Type,Id,Severity,Buf) when is_integer(Source),is_integer(Type),is_integer(Id),is_integer(Severity),is_list(Buf) ->
51255124
IF = get_interface(),
51265125
BufBin = unicode:characters_to_binary([Buf|[0]]),
5127-
IF:queue_cmd(Source,Type,Id,Severity,Length,BufBin,5803),
5126+
IF:queue_cmd(Source,Type,Id,Severity,BufBin,5803),
51285127
ok.
51295128

5130-
-spec getDebugMessageLog(Count::i(), BufSize::i()) -> {i(),Sources::[enum()],Types::[enum()],Ids::[i()],Severities::[enum()],MessageLog::string()}.
5129+
-spec getDebugMessageLog(Count::i(), BufSize::i()) -> {i(),Sources::[enum()],Types::[enum()],Ids::[i()],Severities::[enum()],MessageLog::[string()]}.
51315130
getDebugMessageLog(Count,BufSize) when is_integer(Count),is_integer(BufSize) ->
51325131
IF = get_interface(),
51335132
IF:queue_cmd(Count,BufSize,5804),

lib/wx/test/wx_opengl_SUITE.erl

Lines changed: 59 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@
2727
init_per_suite/1, end_per_suite/1,
2828
init_per_testcase/2, end_per_testcase/2]).
2929

30-
-export([canvas/1, glu_tesselation/1]).
30+
-export([canvas/1, glu_tesselation/1, debugMessage/1]).
3131

3232
-include("wx_test_lib.hrl").
3333
-include_lib("wx/include/gl.hrl").
@@ -55,7 +55,7 @@ end_per_testcase(Func,Config) ->
5555
suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,2}}].
5656

5757
all() ->
58-
[canvas, glu_tesselation].
58+
[canvas, glu_tesselation, debugMessage].
5959

6060
groups() ->
6161
[].
@@ -93,19 +93,14 @@ canvas(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
9393
canvas(Config) ->
9494
WX = ?mr(wx_ref, wx:new()),
9595
Frame = wxFrame:new(WX,1,"Hello 3D-World",[]),
96-
Attrs = [?WX_GL_RGBA,
97-
?WX_GL_DOUBLEBUFFER,
98-
?WX_GL_MIN_RED,8,
99-
?WX_GL_MIN_GREEN,8,
100-
?WX_GL_MIN_BLUE,8,
101-
%% ?WX_GL_CORE_PROFILE,
102-
?WX_GL_DEPTH_SIZE,24,0],
103-
104-
105-
true = wxGLCanvas:isDisplaySupported(Attrs),
106-
107-
Canvas = ?mt(wxGLCanvas, wxGLCanvas:new(Frame, [{style,?wxFULL_REPAINT_ON_RESIZE},
108-
{attribList, Attrs}])),
96+
Attrs = [{attribList, [?WX_GL_RGBA,
97+
?WX_GL_DOUBLEBUFFER,
98+
?WX_GL_MIN_RED,8,
99+
?WX_GL_MIN_GREEN,8,
100+
?WX_GL_MIN_BLUE,8,
101+
%% ?WX_GL_CORE_PROFILE,
102+
?WX_GL_DEPTH_SIZE,24,0]}],
103+
Canvas = ?mt(wxGLCanvas, wxGLCanvas:new(Frame, [{style,?wxFULL_REPAINT_ON_RESIZE}|Attrs])),
109104
Context = wxGLContext:new(Canvas),
110105
SetContext = fun() -> ?m(true, wxGLCanvas:setCurrent(Canvas, Context)) end,
111106

@@ -239,14 +234,8 @@ glu_tesselation(Config) ->
239234
after 1000 -> exit(show_timeout)
240235
end,
241236

242-
try %% 3.0 API
243-
Context = wxGLContext:new(Canvas),
244-
wxGLCanvas:setCurrent(Canvas, Context)
245-
catch _:Reason:ST -> %% 2.8 API
246-
io:format("Using old api: ~p~n ~p~n",[Reason, ST]),
247-
?m(false, wx:is_null(wxGLCanvas:getContext(Canvas))),
248-
?m(ok, wxGLCanvas:setCurrent(Canvas))
249-
end,
237+
Context = wxGLContext:new(Canvas),
238+
wxGLCanvas:setCurrent(Canvas, Context),
250239

251240
Simple = ?m({_,_}, glu:tesselate({0.0,0.0,1.0}, [{-1.0,0.0,0.0},{1.0,0.0,0.0},{0.0,1.0,0.0}])),
252241
io:format("Simple ~p~n",[Simple]),
@@ -266,4 +255,50 @@ glu_tesselation(Config) ->
266255

267256
wx_test_lib:wx_destroy(Frame, Config).
268257

269-
258+
debugMessage(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
259+
debugMessage(Config) ->
260+
WX = ?mr(wx_ref, wx:new()),
261+
Frame = wxFrame:new(WX,1,"Hello 3D-World",[]),
262+
case {?wxMAJOR_VERSION, ?wxMINOR_VERSION} of
263+
{WxMajor,WxMinor} when WxMajor >= 3, WxMinor >= 2 ->
264+
Attrs = [{attribList, [?WX_GL_RGBA,?WX_GL_DOUBLEBUFFER,?WX_GL_DEBUG,0]}],
265+
Canvas = ?mt(wxGLCanvas, wxGLCanvas:new(Frame, Attrs)),
266+
wxFrame:connect(Frame, show),
267+
?m(true, wxWindow:show(Frame)),
268+
269+
receive #wx{event=#wxShow{}} -> ok
270+
after 1000 -> exit(show_timeout)
271+
end,
272+
273+
Context = wxGLContext:new(Canvas),
274+
wxGLCanvas:setCurrent(Canvas, Context),
275+
276+
case {gl:getIntegerv(?GL_MAJOR_VERSION),gl:getIntegerv(?GL_MINOR_VERSION)} of
277+
{[Major|_], [Minor|_]} when Major >= 4, Minor >= 3 ->
278+
io:format("~nVersion: ~p~n", [{Major,Minor}]),
279+
ByteCount = 5000,
280+
Count = 10,
281+
%% Before any log insertion:
282+
A = gl:getDebugMessageLog(Count, ByteCount),
283+
io:format( "A = ~p~n", [ A ] ),
284+
285+
Msg1 = "Hello!",
286+
gl:debugMessageInsert(?GL_DEBUG_SOURCE_APPLICATION, ?GL_DEBUG_TYPE_ERROR,
287+
10, ?GL_DEBUG_SEVERITY_HIGH, Msg1),
288+
Msg2 = "Goodbye...",
289+
gl:debugMessageInsert(?GL_DEBUG_SOURCE_APPLICATION, ?GL_DEBUG_TYPE_ERROR,
290+
11, ?GL_DEBUG_SEVERITY_HIGH, Msg2),
291+
292+
B = gl:getDebugMessageLog(Count, ByteCount),
293+
io:format("B = ~p~n", [B]),
294+
295+
C = gl:getDebugMessageLog(Count, ByteCount),
296+
io:format("C = ~p~n", [C]);
297+
Versions ->
298+
io:format("Not supported version: ~p~n", [Versions])
299+
end;
300+
_ -> ok
301+
end,
302+
wx_test_lib:wx_destroy(Frame, Config).
303+
304+

0 commit comments

Comments
 (0)