1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2011-2016. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 
21 #include <stdio.h>
22 #include <string.h>
23 
24 #ifdef _WIN32
25 #include <windows.h>
26 #endif
27 
28 #include "egl_impl.h"
29 
30 #define WX_DEF_EXTS
31 #include "gen/gl_fdefs.h"
32 
33 void init_tess();
34 void exit_tess();
35 int load_gl_functions();
36 
37 /* ****************************************************************************
38  * OPENGL INITIALIZATION
39  *
40  * Function initializer and loader, part of erl_gl dynamic library.
41  * Also supports gl_nif files
42  *
43  * NOTE: Must function loading must be done after the context is set and in
44  *       the gui thread
45  *****************************************************************************/
46 
47 ERL_NIF_TERM EGL_ATOM_OK;
48 ERL_NIF_TERM EGL_ATOM_REPLY;
49 ERL_NIF_TERM EGL_ATOM_ERROR;
50 ERL_NIF_TERM EGL_ATOM_BADARG;
51 
52 static ErlNifFunc egl_funcs[] =
53 {
54     {"lookup_func", 0, egl_lookup_func_func}
55 };
egl_init(ErlNifEnv * env,void ** priv_data,ERL_NIF_TERM arg)56 static int egl_init(ErlNifEnv *env, void **priv_data, ERL_NIF_TERM arg)
57 {
58     EGL_ATOM_OK = enif_make_atom(env, "ok");
59     EGL_ATOM_BADARG = enif_make_atom(env, "badarg");
60     EGL_ATOM_REPLY = enif_make_atom(env, "_egl_result_");
61     EGL_ATOM_ERROR = enif_make_atom(env, "_egl_error_");
62 
63     return 0;
64 }
65 
ERL_NIF_INIT(gl,egl_funcs,egl_init,NULL,NULL,NULL)66 ERL_NIF_INIT(gl, egl_funcs, egl_init, NULL, NULL, NULL)
67 
68 int egl_get_float(ErlNifEnv* env, ERL_NIF_TERM term, GLfloat* dp)
69 {
70     double temp;
71     if(enif_get_double(env, term, &temp)) {
72         *dp = (GLfloat) temp;
73         return 1;
74     } else return 0;
75 }
76 
egl_get_short(ErlNifEnv * env,ERL_NIF_TERM term,GLshort * dp)77 int egl_get_short(ErlNifEnv* env, ERL_NIF_TERM term, GLshort* dp)
78 {
79     int temp;
80     if(enif_get_int(env, term, &temp)) {
81         *dp = (GLshort) temp;
82         return 1;
83     } else return 0;
84 }
85 
egl_get_ushort(ErlNifEnv * env,ERL_NIF_TERM term,GLushort * dp)86 int egl_get_ushort(ErlNifEnv* env, ERL_NIF_TERM term, GLushort* dp)
87 {
88     unsigned int temp;
89     if(enif_get_uint(env, term, &temp)) {
90         *dp = (GLushort) temp;
91         return 1;
92     } else return 0;
93 }
94 
egl_get_byte(ErlNifEnv * env,ERL_NIF_TERM term,GLbyte * dp)95 int egl_get_byte(ErlNifEnv* env, ERL_NIF_TERM term, GLbyte* dp)
96 {
97     int temp;
98     if(enif_get_int(env, term, &temp)) {
99         *dp = (GLbyte) temp;
100         return 1;
101     } else return 0;
102 }
103 
egl_get_ubyte(ErlNifEnv * env,ERL_NIF_TERM term,GLubyte * dp)104 int egl_get_ubyte(ErlNifEnv* env, ERL_NIF_TERM term, GLubyte* dp)
105 {
106     unsigned int temp;
107     if(enif_get_uint(env, term, &temp)) {
108         *dp = (GLubyte) temp;
109         return 1;
110     } else return 0;
111 }
112 
egl_get_word(ErlNifEnv * env,ERL_NIF_TERM term,egl_word * dp)113 int egl_get_word(ErlNifEnv* env, ERL_NIF_TERM term, egl_word* dp)
114 {
115     if(sizeof(egl_word) == sizeof(int))
116         return enif_get_int(env, term, (signed int *) dp);
117     else
118         return enif_get_int64(env, term, (ErlNifSInt64 *) dp);
119 }
120 
egl_get_ptr(ErlNifEnv * env,ERL_NIF_TERM term,void ** dp)121 int egl_get_ptr(ErlNifEnv* env, ERL_NIF_TERM term, void** dp)
122 {
123     if(sizeof(void *) == sizeof(int))
124         return enif_get_uint(env, term, (unsigned int *) dp);
125     else
126         return enif_get_uint64(env, term, (ErlNifUInt64 *) dp);
127 }
128 
egl_badarg(ErlNifEnv * env,ErlNifPid * self,int op,const char * argc)129 void egl_badarg(ErlNifEnv* env, ErlNifPid *self, int op, const char * argc) {
130     const char * func;
131     func = gl_fns[op-GLE_LIB_START].name;
132     enif_send(NULL, self, env,
133               enif_make_tuple3(env, EGL_ATOM_ERROR,
134                                enif_make_tuple2(env, enif_make_int(env, op),
135                                                 enif_make_string(env, func, ERL_NIF_LATIN1)),
136                                enif_make_tuple2(env, EGL_ATOM_BADARG,
137                                                 enif_make_string(env, argc, ERL_NIF_LATIN1))));
138 }
139 
egl_lookup_func(int op)140 void * egl_lookup_func(int op)
141 {
142     return gl_fns[op-GLE_LIB_START].nif_cb;
143 }
144 
egl_lookup_func_func(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])145 ERL_NIF_TERM egl_lookup_func_func(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
146 {
147     egl_uword func = (egl_uword) egl_lookup_func;
148     if(sizeof(void *) == sizeof(unsigned int))
149         return enif_make_uint(env, (unsigned int) func);
150     else
151         return enif_make_uint64(env, (ErlNifUInt64) func);
152 }
153 
154 #ifdef _WIN32
155 #define RTLD_LAZY 0
156 #define OPENGL_LIB L"opengl32.dll"
157 #define OPENGLU_LIB L"glu32.dll"
158 typedef HMODULE DL_LIB_P;
159 typedef WCHAR DL_CHAR;
dlsym(HMODULE Lib,const char * func)160 void * dlsym(HMODULE Lib, const char *func) {
161   void * p;
162   p = (void *) wglGetProcAddress(func);
163   if(p == 0 || (p == (void *) 0x1) || (p == (void *) 0x2)
164      || (p == (void *) 0x3) || (p == (void *) -1) ) {
165       p = (void *) GetProcAddress(Lib, func);
166   }
167   return p;
168 }
169 
dlopen(const WCHAR * DLL,int unused)170 HMODULE dlopen(const WCHAR *DLL, int unused) {
171   return LoadLibrary(DLL);
172 }
173 
dlclose(HMODULE Lib)174 void dlclose(HMODULE Lib) {
175   FreeLibrary(Lib);
176 }
177 
178 #else
179 typedef void * DL_LIB_P;
180 typedef char DL_CHAR;
181 # ifdef _MACOSX
182 #  define OPENGL_LIB "/System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGL.dylib"
183 #  define OPENGLU_LIB "/System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGLU.dylib"
184 # else
185 #  define OPENGL_LIB "libGL.so.1"
186 #  define OPENGLU_LIB "libGLU.so.1"
187 # endif
188 #endif
189 
190 /* NOTE: Must be done after the context is set and in the gui thread */
egl_load_functions()191 int egl_load_functions() {
192     DL_CHAR * DLName;
193     DL_LIB_P LIBhandle;
194     void * func = NULL;
195     int i;
196 
197 #ifdef _WIN32
198     if(!wglGetCurrentContext())
199         enif_fprintf(stderr, "wglGetCurrentContext is not set this will not work\r\n");
200 #endif
201 
202     /* Load GLU functions */
203     DLName = (DL_CHAR *) OPENGLU_LIB;
204     LIBhandle = dlopen(DLName, RTLD_LAZY);
205     // fprintf(stderr, "Loading GLU: %s\r\n", (const char*)DLName);
206     func = NULL;
207 
208     if(LIBhandle) {
209         for(i=0; i < (GLE_GL_FUNC_START-GLE_LIB_START); i++) {
210             if(gl_fns[i].func) {
211                 if((func = dlsym(LIBhandle, gl_fns[i].name))) {
212                     * (void **) (gl_fns[i].func) = func;
213                 } else {
214                     if(gl_fns[i].alt != NULL) {
215                         if((func = dlsym(LIBhandle, gl_fns[i].alt))) {
216                             * (void **) (gl_fns[i].func) = func;
217                         } else {
218                             * (void **) (gl_fns[i].func) = NULL;
219                             gl_fns[i].nif_cb = NULL;
220                             // fprintf(stderr, "GLU Skipped %s\r\n", glu_fns[i].alt);
221                         };
222                     } else {
223                         * (void **) (gl_fns[i].func) = NULL;
224                         gl_fns[i].nif_cb = NULL;
225                         // fprintf(stderr, "GLU Skipped %s\r\n", glu_fns[i].name);
226                     }
227                 }
228             }
229         }
230         // dlclose(LIBhandle);
231         // fprintf(stderr, "GLU library is loaded\r\n");
232     } else {
233         for(i=0; i < GLE_GL_FUNC_START; i++) {
234             gl_fns[i].nif_cb = NULL;
235         }
236         fprintf(stderr, "Could NOT load OpenGL GLU library: %s\r\n", (char *) DLName);
237     };
238 
239     /* Load GL functions */
240 
241     DLName = (DL_CHAR *) OPENGL_LIB;
242     LIBhandle = dlopen(DLName, RTLD_LAZY);
243     func = NULL;
244 
245     if(LIBhandle) {
246         for(; i <= (GLE_GL_FUNC_LAST-GLE_LIB_START); i++) {
247             if(gl_fns[i].func) {
248                 if((func = dlsym(LIBhandle, gl_fns[i].name))) {
249                     * (void **) (gl_fns[i].func) = func;
250                     // fprintf(stderr, "GL LOADED %s \r\n", gl_fns[i].name);
251                 } else {
252                     if(gl_fns[i].alt != NULL) {
253                         if((func = dlsym(LIBhandle, gl_fns[i].alt))) {
254                             * (void **) (gl_fns[i].func) = func;
255                             // fprintf(stderr, "GL LOADED %s \r\n", gl_fns[i].alt);
256                         } else {
257                             * (void **) (gl_fns[i].func) = NULL;
258                             gl_fns[i].nif_cb = NULL;
259                             // fprintf(stderr, "GL Skipped %s and %s \r\n", gl_fns[i].name, gl_fns[i].alt);
260                         };
261                     } else {
262                         * (void **) (gl_fns[i].func) = NULL;
263                         gl_fns[i].nif_cb = NULL;
264                         // fprintf(stderr, "GL Skipped %s \r\n", gl_fns[i].name);
265                     }
266                 }
267             }
268         }
269         // dlclose(LIBhandle);
270         // fprintf(stderr, "OPENGL library is loaded\r\n");
271     } else {
272         for(i=0; i <= (GLE_GL_FUNC_LAST-GLE_LIB_START); i++) {
273             gl_fns[i].nif_cb = NULL;
274         }
275         fprintf(stderr, "Could NOT load OpenGL library: %s\r\n", (char *) DLName);
276     };
277 
278     return 0;
279 }
280 
281 /* *******************************************************************************
282  * GLU Tesselation special
283  * ******************************************************************************/
284 
285 static GLUtesselator* tess;
286 
287 typedef struct {
288     GLdouble * tess_coords;
289     int alloc_n;
290     int alloc_max;
291 
292     int * tess_index_list;
293     int index_n;
294     int index_max;
295 
296     int error;
297 } egl_tess_data;
298 
299 #define NEED_MORE_ALLOC 1
300 #define NEED_MORE_INDEX 2
301 
302 static egl_tess_data egl_tess;
303 
304 void CALLBACK
egl_ogla_vertex(GLdouble * coords)305 egl_ogla_vertex(GLdouble* coords)
306 {
307     /* fprintf(stderr, "%d\r\n", (int) (coords - tess_coords) / 3); */
308     if(egl_tess.index_n < egl_tess.index_max) {
309         egl_tess.tess_index_list[egl_tess.index_n] = (int) (coords - egl_tess.tess_coords) / 3;
310         egl_tess.index_n++;
311     }
312     else
313         egl_tess.error = NEED_MORE_INDEX;
314 }
315 
316 void CALLBACK
egl_ogla_combine(GLdouble coords[3],void * vertex_data[4],GLfloat w[4],void ** dataOut)317 egl_ogla_combine(GLdouble coords[3],
318                  void* vertex_data[4],
319                  GLfloat w[4],
320                  void **dataOut)
321 {
322     GLdouble* vertex = &egl_tess.tess_coords[egl_tess.alloc_n];
323     if(egl_tess.alloc_n < egl_tess.alloc_max) {
324         egl_tess.alloc_n += 3;
325         vertex[0] = coords[0];
326         vertex[1] = coords[1];
327         vertex[2] = coords[2];
328         *dataOut = vertex;
329 
330 #if 0
331         fprintf(stderr, "combine: ");
332         int i;
333         for (i = 0; i < 4; i++) {
334             if (w[i] > 0.0) {
335                 fprintf(stderr, "%d(%g) ", (int) vertex_data[i], w[i]);
336             }
337         }
338         fprintf(stderr, "\r\n");
339         fprintf(stderr, "%g %g %g\r\n", vertex[0], vertex[1], vertex[2]);
340 #endif
341 
342     } else {
343         egl_tess.error = NEED_MORE_ALLOC;
344         *dataOut = NULL;
345     }
346 }
347 
348 void CALLBACK
egl_ogla_edge_flag(GLboolean flag)349 egl_ogla_edge_flag(GLboolean flag)
350 {
351 }
352 
353 void CALLBACK
egl_ogla_error(GLenum errorCode)354 egl_ogla_error(GLenum errorCode)
355 {
356     // const GLubyte *err;
357     // err = gluErrorString(errorCode);
358     // fprintf(stderr, "Tesselation error: %d: %s\r\n", (int) errorCode, err);
359 }
360 
init_tess()361 void init_tess()
362 {
363     tess = gluNewTess();
364 
365     gluTessCallback(tess, GLU_TESS_VERTEX,     (GLUfuncptr) egl_ogla_vertex);
366     gluTessCallback(tess, GLU_TESS_EDGE_FLAG,  (GLUfuncptr) egl_ogla_edge_flag);
367     gluTessCallback(tess, GLU_TESS_COMBINE,    (GLUfuncptr) egl_ogla_combine);
368     gluTessCallback(tess, GLU_TESS_ERROR,      (GLUfuncptr) egl_ogla_error);
369 
370 }
371 
exit_tess()372 void exit_tess()
373 {
374     gluDeleteTess(tess);
375 }
376 
erl_tess_impl(ErlNifEnv * env,ErlNifPid * self,ERL_NIF_TERM argv[])377 void erl_tess_impl(ErlNifEnv* env, ErlNifPid *self, ERL_NIF_TERM argv[])
378 {
379     int i, a;
380     unsigned int num_vertices;
381     GLdouble n[3], *vs;
382     ErlNifBinary bin;
383     const ERL_NIF_TERM *tuple;
384     ERL_NIF_TERM vs_l, vs_h, vs_t, reply;
385 
386     int a_max = 2;
387     int i_max = 6;
388 
389     if(!enif_get_tuple(env, argv[0], &a, &tuple) && a != 3) Badarg(5009, "Normal");
390     if(!enif_get_double(env, tuple[0], &n[0])) Badarg(5009,"Normal");
391     if(!enif_get_double(env, tuple[1], &n[1])) Badarg(5009,"Normal");
392     if(!enif_get_double(env, tuple[2], &n[2])) Badarg(5009,"Normal");
393 
394     if(!enif_get_list_length(env, argv[1], &num_vertices)) Badarg(5009,"Vs");
395     egl_tess.alloc_max = a_max*num_vertices*3;
396     egl_tess.error = 0;
397     enif_alloc_binary(egl_tess.alloc_max*sizeof(GLdouble), &bin);
398     vs = (GLdouble *) bin.data;
399     egl_tess.tess_coords = vs;
400 
401     vs_l = argv[1];
402     while(enif_get_list_cell(env,  vs_l, &vs_h, &vs_t)) {
403         if(!enif_get_tuple(env, vs_h, &a, &tuple) && a != 3) Badarg(5009,"Vs");
404         if(!enif_get_double(env, tuple[0], vs++)) Badarg(5009,"Normal");
405         if(!enif_get_double(env, tuple[1], vs++)) Badarg(5009,"Normal");
406         if(!enif_get_double(env, tuple[2], vs++)) Badarg(5009,"Normal");
407         vs_l = vs_t;
408     }
409     egl_tess.index_max = i_max*3*num_vertices;
410     egl_tess.tess_index_list = (int *) enif_alloc(sizeof(int) * egl_tess.index_max);
411 
412     egl_tess.index_n = 0;
413     egl_tess.alloc_n = num_vertices*3;
414 
415     gluTessNormal(tess, n[0], n[1], n[2]);
416     gluTessBeginPolygon(tess, 0);
417     gluTessBeginContour(tess);
418     for (i = 0; i < num_vertices; i++) {
419         gluTessVertex(tess, egl_tess.tess_coords+3*i, egl_tess.tess_coords+3*i);
420     }
421     gluTessEndContour(tess);
422     gluTessEndPolygon(tess);
423 
424     vs_t = enif_make_list(env, 0);
425     i=egl_tess.index_n;
426     while(i > 0) {
427         i--;
428         vs_t = enif_make_list_cell(env, enif_make_int(env, egl_tess.tess_index_list[i]), vs_t);
429     };
430 
431     enif_realloc_binary(&bin, egl_tess.alloc_n*sizeof(GLdouble));
432     reply = enif_make_tuple2(env, vs_t, enif_make_binary(env, &bin));
433     enif_send(NULL, self, env, enif_make_tuple2(env, EGL_ATOM_REPLY, reply));
434     /* fprintf(stderr, "List %d: %d %d %d \r\n",  */
435     /* 	  res, */
436     /* 	  n_pos,  */
437     /* 	  (tess_alloc_vertex-new_vertices)*sizeof(GLdouble),  */
438     /* 	  num_vertices*6*sizeof(GLdouble)); */
439     enif_free(egl_tess.tess_index_list);
440 }
441