1 'From TeaSqueak3.2 of 19 September 2002 [latest update: #362] on 5 February 2003 at 10:43:22 am'!
2 GLX subclass: #GLXUnixQuartz
3 	instanceVariableNames: ''
4 	classVariableNames: ''
5 	poolDictionaries: ''
6 	category: 'Tea-GLX'!
7 GLX subclass: #GLXUnixX11BE
8 	instanceVariableNames: ''
9 	classVariableNames: ''
10 	poolDictionaries: ''
11 	category: 'Tea-GLX'!
12 GLXUnixX11BE subclass: #GLXUnixX11LE
13 	instanceVariableNames: ''
14 	classVariableNames: ''
15 	poolDictionaries: ''
16 	category: 'Tea-GLX'!
17 
18 !GLX class methodsFor: 'instance creation' stamp: 'ikp 2/3/2003 17:06'!
19 new
20 	Smalltalk platformName = 'Win32' ifTrue:[^GLXWin32 basicNew initialize].
21 	Smalltalk platformName = 'unix'
22 		ifTrue:
23 			[(Smalltalk windowSystemName = 'X11')
24 				ifTrue: [Smalltalk isLittleEndian
25 					ifTrue: [^GLXUnixX11LE basicNew initialize]
26 					ifFalse: [^GLXUnixX11BE basicNew initialize]].
27 			 (Smalltalk windowSystemName = 'Quartz')
28 				"implicitly big endian"
29 				ifTrue: [^GLXUnixQuartz basicNew initialize].
30 			 self error: 'I cannot create a GLX for this window system'].
31 	Smalltalk platformName = 'Mac OS' ifTrue:[
32 		Smalltalk osVersion asNumber < 1000
33 			ifTrue: [^GLXMacOS9 basicNew initialize]
34 			ifFalse:[^GLXMacOSX basicNew initialize].
35 	].
36 	^self error:'Cannot identify platform'! !
37 
38 
39 !GLXUnixQuartz methodsFor: 'accessing' stamp: 'ikp 1/7/2003 21:14'!
40 imagePixelFormat32
41 	^GLBgra! !
42 
43 !GLXUnixQuartz methodsFor: 'accessing' stamp: 'ikp 1/7/2003 21:14'!
44 imagePixelType32
45 	^GLUnsignedInt8888Rev! !
46 
47 !GLXUnixQuartz methodsFor: 'accessing' stamp: 'ikp 1/7/2003 21:14'!
48 textureInternalFormat
49 	^GLRgba! !
50 
51 !GLXUnixQuartz methodsFor: 'accessing' stamp: 'ikp 1/7/2003 21:14'!
52 texturePixelFormat
53 	^GLBgra! !
54 
55 !GLXUnixQuartz methodsFor: 'accessing' stamp: 'ikp 1/7/2003 21:14'!
56 texturePixelType
57 	^GLUnsignedInt8888Rev! !
58 
59 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
60 glAccum: op with: value
61 	"This method was automatically generated."
62 	"void glAccum(GLenum op, GLfloat value);"
63 	<cdecl: void 'glAccum' (ulong float) module: 'OpenGL'>
64 	^self externalCallFailed! !
65 
66 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
67 glActiveTextureARB: texture
68 	"This method was automatically generated."
69 	"void glActiveTextureARB(GLenum texture);"
70 	<cdecl: void 'glActiveTextureARB' (ulong) module: 'OpenGL'>
71 	^self externalCallFailed! !
72 
73 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
74 glAlphaFunc: func with: ref
75 	"This method was automatically generated."
76 	"void glAlphaFunc(GLenum func, GLclampf ref);"
77 	<cdecl: void 'glAlphaFunc' (ulong float) module: 'OpenGL'>
78 	^self externalCallFailed! !
79 
80 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
81 glAreTexturesResident: n with: texturez with: residences
82 	"This method was automatically generated."
83 	"GLboolean glAreTexturesResident(GLsizei n, GLuint* textures, GLboolean* residences);"
84 	<cdecl: bool 'glAreTexturesResident' (long ulong* ulong*) module: 'OpenGL'>
85 	^self externalCallFailed! !
86 
87 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
88 glAreTexturesResidentEXT: n with: texturez with: residences
89 	"This method was automatically generated."
90 	"GLboolean glAreTexturesResidentEXT(GLsizei n, GLuint* textures, GLboolean* residences);"
91 	<cdecl: bool 'glAreTexturesResidentEXT' (long ulong* ulong*) module: 'OpenGL'>
92 	^self externalCallFailed! !
93 
94 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
95 glArrayElement: i
96 	"This method was automatically generated."
97 	"void glArrayElement(GLint i);"
98 	<cdecl: void 'glArrayElement' (long) module: 'OpenGL'>
99 	^self externalCallFailed! !
100 
101 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
102 glArrayElementEXT: i
103 	"This method was automatically generated."
104 	"void glArrayElementEXT(GLint i);"
105 	<cdecl: void 'glArrayElementEXT' (long) module: 'OpenGL'>
106 	^self externalCallFailed! !
107 
108 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
109 glBegin: mode
110 	"This method was automatically generated."
111 	"void glBegin(GLenum mode);"
112 	<cdecl: void 'glBegin' (ulong) module: 'OpenGL'>
113 	^self externalCallFailed! !
114 
115 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
116 glBindTexture: targt with: texture
117 	"This method was automatically generated."
118 	"void glBindTexture(GLenum target, GLuint texture);"
119 	<cdecl: void 'glBindTexture' (ulong ulong) module: 'OpenGL'>
120 	^self externalCallFailed! !
121 
122 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
123 glBitmap: width with: height with: xorig with: yorig with: xmove with: ymove with: bitmap
124 	"This method was automatically generated."
125 	"void glBitmap(GLsizei width, GLsizei height, GLfloat xorig, GLfloat yorig, GLfloat xmove, GLfloat ymove, GLubyte* bitmap);"
126 	<cdecl: void 'glBitmap' (long long float float float float void*) module: 'OpenGL'>
127 	^self externalCallFailed! !
128 
129 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
130 glBlendColor: red with: green with: blue with: alpha
131 	"This method was automatically generated."
132 	"void glBlendColor(GLclampf red, GLclampf green, GLclampf blue, GLclampf alpha);"
133 	<cdecl: void 'glBlendColor' (float float float float) module: 'OpenGL'>
134 	^self externalCallFailed! !
135 
136 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
137 glBlendEquation: mode
138 	"This method was automatically generated."
139 	"void glBlendEquation(GLenum mode);"
140 	<cdecl: void 'glBlendEquation' (ulong) module: 'OpenGL'>
141 	^self externalCallFailed! !
142 
143 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
144 glBlendFunc: sfactor with: dfactor
145 	"This method was automatically generated."
146 	"void glBlendFunc(GLenum sfactor, GLenum dfactor);"
147 	<cdecl: void 'glBlendFunc' (ulong ulong) module: 'OpenGL'>
148 	^self externalCallFailed! !
149 
150 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
151 glCallList: list
152 	"This method was automatically generated."
153 	"void glCallList(GLuint list);"
154 	<cdecl: void 'glCallList' (ulong) module: 'OpenGL'>
155 	^self externalCallFailed! !
156 
157 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
158 glCallLists: n with: type with: lists
159 	"This method was automatically generated."
160 	"void glCallLists(GLsizei n, GLenum type, GLvoid* lists);"
161 	<cdecl: void 'glCallLists' (long ulong void*) module: 'OpenGL'>
162 	^self externalCallFailed! !
163 
164 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
165 glClear: mask
166 	"This method was automatically generated."
167 	"void glClear(GLbitfield mask);"
168 	<cdecl: void 'glClear' (ulong) module: 'OpenGL'>
169 	^self externalCallFailed! !
170 
171 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
172 glClearAccum: red with: green with: blue with: alpha
173 	"This method was automatically generated."
174 	"void glClearAccum(GLfloat red, GLfloat green, GLfloat blue, GLfloat alpha);"
175 	<cdecl: void 'glClearAccum' (float float float float) module: 'OpenGL'>
176 	^self externalCallFailed! !
177 
178 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
179 glClearColor: red with: green with: blue with: alpha
180 	"This method was automatically generated."
181 	"void glClearColor(GLclampf red, GLclampf green, GLclampf blue, GLclampf alpha);"
182 	<cdecl: void 'glClearColor' (float float float float) module: 'OpenGL'>
183 	^self externalCallFailed! !
184 
185 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
186 glClearDepth: depth
187 	"This method was automatically generated."
188 	"void glClearDepth(GLclampd depth);"
189 	<cdecl: void 'glClearDepth' (double) module: 'OpenGL'>
190 	^self externalCallFailed! !
191 
192 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
193 glClearIndex: c
194 	"This method was automatically generated."
195 	"void glClearIndex(GLfloat c);"
196 	<cdecl: void 'glClearIndex' (float) module: 'OpenGL'>
197 	^self externalCallFailed! !
198 
199 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
200 glClearStencil: s
201 	"This method was automatically generated."
202 	"void glClearStencil(GLint s);"
203 	<cdecl: void 'glClearStencil' (long) module: 'OpenGL'>
204 	^self externalCallFailed! !
205 
206 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
207 glClientActiveTextureARB: texture
208 	"This method was automatically generated."
209 	"void glClientActiveTextureARB(GLenum texture);"
210 	<cdecl: void 'glClientActiveTextureARB' (ulong) module: 'OpenGL'>
211 	^self externalCallFailed! !
212 
213 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
214 glClipPlane: plane with: equation
215 	"This method was automatically generated."
216 	"void glClipPlane(GLenum plane, GLdouble* equation);"
217 	<cdecl: void 'glClipPlane' (ulong double*) module: 'OpenGL'>
218 	^self externalCallFailed! !
219 
220 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
221 glColor3b: red with: green with: blue
222 	"This method was automatically generated."
223 	"void glColor3b(GLbyte red, GLbyte green, GLbyte blue);"
224 	<cdecl: void 'glColor3b' (byte byte byte) module: 'OpenGL'>
225 	^self externalCallFailed! !
226 
227 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
228 glColor3bv: v
229 	"This method was automatically generated."
230 	"void glColor3bv(GLbyte* v);"
231 	<cdecl: void 'glColor3bv' (byte*) module: 'OpenGL'>
232 	^self externalCallFailed! !
233 
234 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
235 glColor3d: red with: green with: blue
236 	"This method was automatically generated."
237 	"void glColor3d(GLdouble red, GLdouble green, GLdouble blue);"
238 	<cdecl: void 'glColor3d' (double double double) module: 'OpenGL'>
239 	^self externalCallFailed! !
240 
241 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
242 glColor3dv: v
243 	"This method was automatically generated."
244 	"void glColor3dv(GLdouble* v);"
245 	<cdecl: void 'glColor3dv' (double*) module: 'OpenGL'>
246 	^self externalCallFailed! !
247 
248 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
249 glColor3f: red with: green with: blue
250 	"This method was automatically generated."
251 	"void glColor3f(GLfloat red, GLfloat green, GLfloat blue);"
252 	<cdecl: void 'glColor3f' (float float float) module: 'OpenGL'>
253 	^self externalCallFailed! !
254 
255 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
256 glColor3fv: v
257 	"This method was automatically generated."
258 	"void glColor3fv(GLfloat* v);"
259 	<cdecl: void 'glColor3fv' (float*) module: 'OpenGL'>
260 	^self externalCallFailed! !
261 
262 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
263 glColor3i: red with: green with: blue
264 	"This method was automatically generated."
265 	"void glColor3i(GLint red, GLint green, GLint blue);"
266 	<cdecl: void 'glColor3i' (long long long) module: 'OpenGL'>
267 	^self externalCallFailed! !
268 
269 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
270 glColor3iv: v
271 	"This method was automatically generated."
272 	"void glColor3iv(GLint* v);"
273 	<cdecl: void 'glColor3iv' (long*) module: 'OpenGL'>
274 	^self externalCallFailed! !
275 
276 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
277 glColor3s: red with: green with: blue
278 	"This method was automatically generated."
279 	"void glColor3s(GLshort red, GLshort green, GLshort blue);"
280 	<cdecl: void 'glColor3s' (short short short) module: 'OpenGL'>
281 	^self externalCallFailed! !
282 
283 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
284 glColor3sv: v
285 	"This method was automatically generated."
286 	"void glColor3sv(GLshort* v);"
287 	<cdecl: void 'glColor3sv' (short*) module: 'OpenGL'>
288 	^self externalCallFailed! !
289 
290 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
291 glColor3ub: red with: green with: blue
292 	"This method was automatically generated."
293 	"void glColor3ub(GLubyte red, GLubyte green, GLubyte blue);"
294 	<cdecl: void 'glColor3ub' (byte byte byte) module: 'OpenGL'>
295 	^self externalCallFailed! !
296 
297 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
298 glColor3ubv: v
299 	"This method was automatically generated."
300 	"void glColor3ubv(GLubyte* v);"
301 	<cdecl: void 'glColor3ubv' (byte*) module: 'OpenGL'>
302 	^self externalCallFailed! !
303 
304 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
305 glColor3ui: red with: green with: blue
306 	"This method was automatically generated."
307 	"void glColor3ui(GLuint red, GLuint green, GLuint blue);"
308 	<cdecl: void 'glColor3ui' (ulong ulong ulong) module: 'OpenGL'>
309 	^self externalCallFailed! !
310 
311 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
312 glColor3uiv: v
313 	"This method was automatically generated."
314 	"void glColor3uiv(GLuint* v);"
315 	<cdecl: void 'glColor3uiv' (ulong*) module: 'OpenGL'>
316 	^self externalCallFailed! !
317 
318 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
319 glColor3us: red with: green with: blue
320 	"This method was automatically generated."
321 	"void glColor3us(GLushort red, GLushort green, GLushort blue);"
322 	<cdecl: void 'glColor3us' (ushort ushort ushort) module: 'OpenGL'>
323 	^self externalCallFailed! !
324 
325 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
326 glColor3usv: v
327 	"This method was automatically generated."
328 	"void glColor3usv(GLushort* v);"
329 	<cdecl: void 'glColor3usv' (ushort*) module: 'OpenGL'>
330 	^self externalCallFailed! !
331 
332 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
333 glColor4b: red with: green with: blue with: alpha
334 	"This method was automatically generated."
335 	"void glColor4b(GLbyte red, GLbyte green, GLbyte blue, GLbyte alpha);"
336 	<cdecl: void 'glColor4b' (byte byte byte byte) module: 'OpenGL'>
337 	^self externalCallFailed! !
338 
339 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
340 glColor4bv: v
341 	"This method was automatically generated."
342 	"void glColor4bv(GLbyte* v);"
343 	<cdecl: void 'glColor4bv' (byte*) module: 'OpenGL'>
344 	^self externalCallFailed! !
345 
346 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
347 glColor4d: red with: green with: blue with: alpha
348 	"This method was automatically generated."
349 	"void glColor4d(GLdouble red, GLdouble green, GLdouble blue, GLdouble alpha);"
350 	<cdecl: void 'glColor4d' (double double double double) module: 'OpenGL'>
351 	^self externalCallFailed! !
352 
353 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
354 glColor4dv: v
355 	"This method was automatically generated."
356 	"void glColor4dv(GLdouble* v);"
357 	<cdecl: void 'glColor4dv' (double*) module: 'OpenGL'>
358 	^self externalCallFailed! !
359 
360 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
361 glColor4f: red with: green with: blue with: alpha
362 	"This method was automatically generated."
363 	"void glColor4f(GLfloat red, GLfloat green, GLfloat blue, GLfloat alpha);"
364 	<cdecl: void 'glColor4f' (float float float float) module: 'OpenGL'>
365 	^self externalCallFailed! !
366 
367 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
368 glColor4fv: v
369 	"This method was automatically generated."
370 	"void glColor4fv(GLfloat* v);"
371 	<cdecl: void 'glColor4fv' (float*) module: 'OpenGL'>
372 	^self externalCallFailed! !
373 
374 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
375 glColor4i: red with: green with: blue with: alpha
376 	"This method was automatically generated."
377 	"void glColor4i(GLint red, GLint green, GLint blue, GLint alpha);"
378 	<cdecl: void 'glColor4i' (long long long long) module: 'OpenGL'>
379 	^self externalCallFailed! !
380 
381 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
382 glColor4iv: v
383 	"This method was automatically generated."
384 	"void glColor4iv(GLint* v);"
385 	<cdecl: void 'glColor4iv' (long*) module: 'OpenGL'>
386 	^self externalCallFailed! !
387 
388 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
389 glColor4s: red with: green with: blue with: alpha
390 	"This method was automatically generated."
391 	"void glColor4s(GLshort red, GLshort green, GLshort blue, GLshort alpha);"
392 	<cdecl: void 'glColor4s' (short short short short) module: 'OpenGL'>
393 	^self externalCallFailed! !
394 
395 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
396 glColor4sv: v
397 	"This method was automatically generated."
398 	"void glColor4sv(GLshort* v);"
399 	<cdecl: void 'glColor4sv' (short*) module: 'OpenGL'>
400 	^self externalCallFailed! !
401 
402 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
403 glColor4ub: red with: green with: blue with: alpha
404 	"This method was automatically generated."
405 	"void glColor4ub(GLubyte red, GLubyte green, GLubyte blue, GLubyte alpha);"
406 	<cdecl: void 'glColor4ub' (byte byte byte byte) module: 'OpenGL'>
407 	^self externalCallFailed! !
408 
409 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
410 glColor4ubv: v
411 	"This method was automatically generated."
412 	"void glColor4ubv(GLubyte* v);"
413 	<cdecl: void 'glColor4ubv' (byte*) module: 'OpenGL'>
414 	^self externalCallFailed! !
415 
416 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
417 glColor4ui: red with: green with: blue with: alpha
418 	"This method was automatically generated."
419 	"void glColor4ui(GLuint red, GLuint green, GLuint blue, GLuint alpha);"
420 	<cdecl: void 'glColor4ui' (ulong ulong ulong ulong) module: 'OpenGL'>
421 	^self externalCallFailed! !
422 
423 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
424 glColor4uiv: v
425 	"This method was automatically generated."
426 	"void glColor4uiv(GLuint* v);"
427 	<cdecl: void 'glColor4uiv' (ulong*) module: 'OpenGL'>
428 	^self externalCallFailed! !
429 
430 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
431 glColor4us: red with: green with: blue with: alpha
432 	"This method was automatically generated."
433 	"void glColor4us(GLushort red, GLushort green, GLushort blue, GLushort alpha);"
434 	<cdecl: void 'glColor4us' (ushort ushort ushort ushort) module: 'OpenGL'>
435 	^self externalCallFailed! !
436 
437 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
438 glColor4usv: v
439 	"This method was automatically generated."
440 	"void glColor4usv(GLushort* v);"
441 	<cdecl: void 'glColor4usv' (ushort*) module: 'OpenGL'>
442 	^self externalCallFailed! !
443 
444 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
445 glColorMask: red with: green with: blue with: alpha
446 	"This method was automatically generated."
447 	"void glColorMask(GLboolean red, GLboolean green, GLboolean blue, GLboolean alpha);"
448 	<cdecl: void 'glColorMask' (bool bool bool bool) module: 'OpenGL'>
449 	^self externalCallFailed! !
450 
451 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
452 glColorMaterial: face with: mode
453 	"This method was automatically generated."
454 	"void glColorMaterial(GLenum face, GLenum mode);"
455 	<cdecl: void 'glColorMaterial' (ulong ulong) module: 'OpenGL'>
456 	^self externalCallFailed! !
457 
458 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
459 glColorPointer: size with: type with: stride with: pointer
460 	"This method was automatically generated."
461 	"void glColorPointer(GLint size, GLenum type, GLsizei stride, GLvoid* pointer);"
462 	<cdecl: void 'glColorPointer' (long ulong long void*) module: 'OpenGL'>
463 	^self externalCallFailed! !
464 
465 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
466 glColorPointerEXT: size with: type with: stride with: count with: pointer
467 	"This method was automatically generated."
468 	"void glColorPointerEXT(GLint size, GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
469 	<cdecl: void 'glColorPointerEXT' (long ulong long long void*) module: 'OpenGL'>
470 	^self externalCallFailed! !
471 
472 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
473 glColorSubTable: targt with: start with: count with: format with: type with: data
474 	"This method was automatically generated."
475 	"void glColorSubTable(GLenum target, GLsizei start, GLsizei count, GLenum format, GLenum type, GLvoid* data);"
476 	<cdecl: void 'glColorSubTable' (ulong long long ulong ulong void*) module: 'OpenGL'>
477 	^self externalCallFailed! !
478 
479 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
480 glColorTable: targt with: internalformat with: width with: format with: type with: table
481 	"This method was automatically generated."
482 	"void glColorTable(GLenum target, GLenum internalformat, GLsizei width, GLenum format, GLenum type, GLvoid* table);"
483 	<cdecl: void 'glColorTable' (ulong ulong long ulong ulong void*) module: 'OpenGL'>
484 	^self externalCallFailed! !
485 
486 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
487 glColorTableParameterfv: targt with: pname with: params
488 	"This method was automatically generated."
489 	"void glColorTableParameterfv(GLenum target, GLenum pname, GLfloat* params);"
490 	<cdecl: void 'glColorTableParameterfv' (ulong ulong float*) module: 'OpenGL'>
491 	^self externalCallFailed! !
492 
493 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
494 glColorTableParameteriv: targt with: pname with: params
495 	"This method was automatically generated."
496 	"void glColorTableParameteriv(GLenum target, GLenum pname, GLint* params);"
497 	<cdecl: void 'glColorTableParameteriv' (ulong ulong long*) module: 'OpenGL'>
498 	^self externalCallFailed! !
499 
500 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
501 glConvolutionFilter1D: targt with: internalformat with: width with: format with: type with: image
502 	"This method was automatically generated."
503 	"void glConvolutionFilter1D(GLenum target, GLenum internalformat, GLsizei width, GLenum format, GLenum type, GLvoid* image);"
504 	<cdecl: void 'glConvolutionFilter1D' (ulong ulong long ulong ulong void*) module: 'OpenGL'>
505 	^self externalCallFailed! !
506 
507 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
508 glConvolutionFilter2D: targt with: internalformat with: width with: height with: format with: type with: image
509 	"This method was automatically generated."
510 	"void glConvolutionFilter2D(GLenum target, GLenum internalformat, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* image);"
511 	<cdecl: void 'glConvolutionFilter2D' (ulong ulong long long ulong ulong void*) module: 'OpenGL'>
512 	^self externalCallFailed! !
513 
514 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
515 glConvolutionParameterf: targt with: pname with: params
516 	"This method was automatically generated."
517 	"void glConvolutionParameterf(GLenum target, GLenum pname, GLfloat params);"
518 	<cdecl: void 'glConvolutionParameterf' (ulong ulong float) module: 'OpenGL'>
519 	^self externalCallFailed! !
520 
521 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
522 glConvolutionParameterfv: targt with: pname with: params
523 	"This method was automatically generated."
524 	"void glConvolutionParameterfv(GLenum target, GLenum pname, GLfloat* params);"
525 	<cdecl: void 'glConvolutionParameterfv' (ulong ulong float*) module: 'OpenGL'>
526 	^self externalCallFailed! !
527 
528 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
529 glConvolutionParameteri: targt with: pname with: params
530 	"This method was automatically generated."
531 	"void glConvolutionParameteri(GLenum target, GLenum pname, GLint params);"
532 	<cdecl: void 'glConvolutionParameteri' (ulong ulong long) module: 'OpenGL'>
533 	^self externalCallFailed! !
534 
535 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
536 glConvolutionParameteriv: targt with: pname with: params
537 	"This method was automatically generated."
538 	"void glConvolutionParameteriv(GLenum target, GLenum pname, GLint* params);"
539 	<cdecl: void 'glConvolutionParameteriv' (ulong ulong long*) module: 'OpenGL'>
540 	^self externalCallFailed! !
541 
542 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
543 glCopyColorSubTable: targt with: start with: x with: y with: width
544 	"This method was automatically generated."
545 	"void glCopyColorSubTable(GLenum target, GLsizei start, GLint x, GLint y, GLsizei width);"
546 	<cdecl: void 'glCopyColorSubTable' (ulong long long long long) module: 'OpenGL'>
547 	^self externalCallFailed! !
548 
549 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
550 glCopyColorTable: targt with: internalformat with: x with: y with: width
551 	"This method was automatically generated."
552 	"void glCopyColorTable(GLenum target, GLenum internalformat, GLint x, GLint y, GLsizei width);"
553 	<cdecl: void 'glCopyColorTable' (ulong ulong long long long) module: 'OpenGL'>
554 	^self externalCallFailed! !
555 
556 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
557 glCopyConvolutionFilter1D: targt with: internalformat with: x with: y with: width
558 	"This method was automatically generated."
559 	"void glCopyConvolutionFilter1D(GLenum target, GLenum internalformat, GLint x, GLint y, GLsizei width);"
560 	<cdecl: void 'glCopyConvolutionFilter1D' (ulong ulong long long long) module: 'OpenGL'>
561 	^self externalCallFailed! !
562 
563 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
564 glCopyConvolutionFilter2D: targt with: internalformat with: x with: y with: width with: height
565 	"This method was automatically generated."
566 	"void glCopyConvolutionFilter2D(GLenum target, GLenum internalformat, GLint x, GLint y, GLsizei width, GLsizei height);"
567 	<cdecl: void 'glCopyConvolutionFilter2D' (ulong ulong long long long long) module: 'OpenGL'>
568 	^self externalCallFailed! !
569 
570 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
571 glCopyPixels: x with: y with: width with: height with: type
572 	"This method was automatically generated."
573 	"void glCopyPixels(GLint x, GLint y, GLsizei width, GLsizei height, GLenum type);"
574 	<cdecl: void 'glCopyPixels' (long long long long ulong) module: 'OpenGL'>
575 	^self externalCallFailed! !
576 
577 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
578 glCopyTexImage1D: targt with: level with: internalformat with: x with: y with: width with: border
579 	"This method was automatically generated."
580 	"void glCopyTexImage1D(GLenum target, GLint level, GLenum internalformat, GLint x, GLint y, GLsizei width, GLint border);"
581 	<cdecl: void 'glCopyTexImage1D' (ulong long ulong long long long long) module: 'OpenGL'>
582 	^self externalCallFailed! !
583 
584 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
585 glCopyTexImage2D: targt with: level with: internalformat with: x with: y with: width with: height with: border
586 	"This method was automatically generated."
587 	"void glCopyTexImage2D(GLenum target, GLint level, GLenum internalformat, GLint x, GLint y, GLsizei width, GLsizei height, GLint border);"
588 	<cdecl: void 'glCopyTexImage2D' (ulong long ulong long long long long long) module: 'OpenGL'>
589 	^self externalCallFailed! !
590 
591 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
592 glCopyTexSubImage1D: targt with: level with: xoffset with: x with: y with: width
593 	"This method was automatically generated."
594 	"void glCopyTexSubImage1D(GLenum target, GLint level, GLint xoffset, GLint x, GLint y, GLsizei width);"
595 	<cdecl: void 'glCopyTexSubImage1D' (ulong long long long long long) module: 'OpenGL'>
596 	^self externalCallFailed! !
597 
598 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
599 glCopyTexSubImage2D: targt with: level with: xoffset with: yoffset with: x with: y with: width with: height
600 	"This method was automatically generated."
601 	"void glCopyTexSubImage2D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLint x, GLint y, GLsizei width, GLsizei height);"
602 	<cdecl: void 'glCopyTexSubImage2D' (ulong long long long long long long long) module: 'OpenGL'>
603 	^self externalCallFailed! !
604 
605 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
606 glCopyTexSubImage3D: targt with: level with: xoffset with: yoffset with: zoffset with: x with: y with: width with: height
607 	"This method was automatically generated."
608 	"void glCopyTexSubImage3D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLint zoffset, GLint x, GLint y, GLsizei width, GLsizei height);"
609 	<cdecl: void 'glCopyTexSubImage3D' (ulong long long long long long long long long) module: 'OpenGL'>
610 	^self externalCallFailed! !
611 
612 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
613 glCullFace: mode
614 	"This method was automatically generated."
615 	"void glCullFace(GLenum mode);"
616 	<cdecl: void 'glCullFace' (ulong) module: 'OpenGL'>
617 	^self externalCallFailed! !
618 
619 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
620 glDeleteLists: list with: range
621 	"This method was automatically generated."
622 	"void glDeleteLists(GLuint list, GLsizei range);"
623 	<cdecl: void 'glDeleteLists' (ulong long) module: 'OpenGL'>
624 	^self externalCallFailed! !
625 
626 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
627 glDeleteTextures: n with: textures
628 	"This method was automatically generated."
629 	"void glDeleteTextures(GLsizei n, GLuint* textures);"
630 	<cdecl: void 'glDeleteTextures' (long ulong*) module: 'OpenGL'>
631 	^self externalCallFailed! !
632 
633 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
634 glDeleteTexturesEXT: n with: textures
635 	"This method was automatically generated."
636 	"void glDeleteTexturesEXT(GLsizei n, GLuint* textures);"
637 	<cdecl: void 'glDeleteTexturesEXT' (long ulong*) module: 'OpenGL'>
638 	^self externalCallFailed! !
639 
640 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
641 glDepthFunc: func
642 	"This method was automatically generated."
643 	"void glDepthFunc(GLenum func);"
644 	<cdecl: void 'glDepthFunc' (ulong) module: 'OpenGL'>
645 	^self externalCallFailed! !
646 
647 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
648 glDepthMask: flag
649 	"This method was automatically generated."
650 	"void glDepthMask(GLboolean flag);"
651 	<cdecl: void 'glDepthMask' (bool) module: 'OpenGL'>
652 	^self externalCallFailed! !
653 
654 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
655 glDepthRange: zNear with: zFar
656 	"This method was automatically generated."
657 	"void glDepthRange(GLclampd zNear, GLclampd zFar);"
658 	<cdecl: void 'glDepthRange' (double double) module: 'OpenGL'>
659 	^self externalCallFailed! !
660 
661 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
662 glDisable: cap
663 	"This method was automatically generated."
664 	"void glDisable(GLenum cap);"
665 	<cdecl: void 'glDisable' (ulong) module: 'OpenGL'>
666 	^self externalCallFailed! !
667 
668 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
669 glDisableClientState: array
670 	"This method was automatically generated."
671 	"void glDisableClientState(GLenum array);"
672 	<cdecl: void 'glDisableClientState' (ulong) module: 'OpenGL'>
673 	^self externalCallFailed! !
674 
675 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
676 glDrawArrays: mode with: first with: count
677 	"This method was automatically generated."
678 	"void glDrawArrays(GLenum mode, GLint first, GLsizei count);"
679 	<cdecl: void 'glDrawArrays' (ulong long long) module: 'OpenGL'>
680 	^self externalCallFailed! !
681 
682 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
683 glDrawArraysEXT: mode with: first with: count
684 	"This method was automatically generated."
685 	"void glDrawArraysEXT(GLenum mode, GLint first, GLsizei count);"
686 	<cdecl: void 'glDrawArraysEXT' (ulong long long) module: 'OpenGL'>
687 	^self externalCallFailed! !
688 
689 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
690 glDrawBuffer: mode
691 	"This method was automatically generated."
692 	"void glDrawBuffer(GLenum mode);"
693 	<cdecl: void 'glDrawBuffer' (ulong) module: 'OpenGL'>
694 	^self externalCallFailed! !
695 
696 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
697 glDrawElements: mode with: count with: type with: indices
698 	"This method was automatically generated."
699 	"void glDrawElements(GLenum mode, GLsizei count, GLenum type, GLvoid* indices);"
700 	<cdecl: void 'glDrawElements' (ulong long ulong void*) module: 'OpenGL'>
701 	^self externalCallFailed! !
702 
703 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
704 glDrawPixels: width with: height with: format with: type with: pixels
705 	"This method was automatically generated."
706 	"void glDrawPixels(GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* pixels);"
707 	<cdecl: void 'glDrawPixels' (long long ulong ulong void*) module: 'OpenGL'>
708 	^self externalCallFailed! !
709 
710 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
711 glDrawRangeElements: mode with: start with: end with: count with: type with: indices
712 	"This method was automatically generated."
713 	"void glDrawRangeElements(GLenum mode, GLuint start, GLuint end, GLsizei count, GLenum type, GLvoid* indices);"
714 	<cdecl: void 'glDrawRangeElements' (ulong ulong ulong long ulong void*) module: 'OpenGL'>
715 	^self externalCallFailed! !
716 
717 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
718 glEdgeFlag: flag
719 	"This method was automatically generated."
720 	"void glEdgeFlag(GLboolean flag);"
721 	<cdecl: void 'glEdgeFlag' (bool) module: 'OpenGL'>
722 	^self externalCallFailed! !
723 
724 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
725 glEdgeFlagPointer: stride with: pointer
726 	"This method was automatically generated."
727 	"void glEdgeFlagPointer(GLsizei stride, GLboolean* pointer);"
728 	<cdecl: void 'glEdgeFlagPointer' (long ulong*) module: 'OpenGL'>
729 	^self externalCallFailed! !
730 
731 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
732 glEdgeFlagPointerEXT: stride with: count with: pointer
733 	"This method was automatically generated."
734 	"void glEdgeFlagPointerEXT(GLsizei stride, GLsizei count, GLboolean* pointer);"
735 	<cdecl: void 'glEdgeFlagPointerEXT' (long long ulong*) module: 'OpenGL'>
736 	^self externalCallFailed! !
737 
738 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
739 glEdgeFlagv: flag
740 	"This method was automatically generated."
741 	"void glEdgeFlagv(GLboolean* flag);"
742 	<cdecl: void 'glEdgeFlagv' (ulong*) module: 'OpenGL'>
743 	^self externalCallFailed! !
744 
745 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
746 glEnable: cap
747 	"This method was automatically generated."
748 	"void glEnable(GLenum cap);"
749 	<cdecl: void 'glEnable' (ulong) module: 'OpenGL'>
750 	^self externalCallFailed! !
751 
752 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
753 glEnableClientState: array
754 	"This method was automatically generated."
755 	"void glEnableClientState(GLenum array);"
756 	<cdecl: void 'glEnableClientState' (ulong) module: 'OpenGL'>
757 	^self externalCallFailed! !
758 
759 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
760 glEnd
761 	"This method was automatically generated."
762 	"void glEnd();"
763 	<cdecl: void 'glEnd' (void) module: 'OpenGL'>
764 	^self externalCallFailed! !
765 
766 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
767 glEndList
768 	"This method was automatically generated."
769 	"void glEndList();"
770 	<cdecl: void 'glEndList' (void) module: 'OpenGL'>
771 	^self externalCallFailed! !
772 
773 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
774 glEvalCoord1d: u
775 	"This method was automatically generated."
776 	"void glEvalCoord1d(GLdouble u);"
777 	<cdecl: void 'glEvalCoord1d' (double) module: 'OpenGL'>
778 	^self externalCallFailed! !
779 
780 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
781 glEvalCoord1dv: u
782 	"This method was automatically generated."
783 	"void glEvalCoord1dv(GLdouble* u);"
784 	<cdecl: void 'glEvalCoord1dv' (double*) module: 'OpenGL'>
785 	^self externalCallFailed! !
786 
787 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
788 glEvalCoord1f: u
789 	"This method was automatically generated."
790 	"void glEvalCoord1f(GLfloat u);"
791 	<cdecl: void 'glEvalCoord1f' (float) module: 'OpenGL'>
792 	^self externalCallFailed! !
793 
794 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
795 glEvalCoord1fv: u
796 	"This method was automatically generated."
797 	"void glEvalCoord1fv(GLfloat* u);"
798 	<cdecl: void 'glEvalCoord1fv' (float*) module: 'OpenGL'>
799 	^self externalCallFailed! !
800 
801 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
802 glEvalCoord2d: u with: v
803 	"This method was automatically generated."
804 	"void glEvalCoord2d(GLdouble u, GLdouble v);"
805 	<cdecl: void 'glEvalCoord2d' (double double) module: 'OpenGL'>
806 	^self externalCallFailed! !
807 
808 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
809 glEvalCoord2dv: u
810 	"This method was automatically generated."
811 	"void glEvalCoord2dv(GLdouble* u);"
812 	<cdecl: void 'glEvalCoord2dv' (double*) module: 'OpenGL'>
813 	^self externalCallFailed! !
814 
815 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
816 glEvalCoord2f: u with: v
817 	"This method was automatically generated."
818 	"void glEvalCoord2f(GLfloat u, GLfloat v);"
819 	<cdecl: void 'glEvalCoord2f' (float float) module: 'OpenGL'>
820 	^self externalCallFailed! !
821 
822 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
823 glEvalCoord2fv: u
824 	"This method was automatically generated."
825 	"void glEvalCoord2fv(GLfloat* u);"
826 	<cdecl: void 'glEvalCoord2fv' (float*) module: 'OpenGL'>
827 	^self externalCallFailed! !
828 
829 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
830 glEvalMesh1: mode with: i1 with: i2
831 	"This method was automatically generated."
832 	"void glEvalMesh1(GLenum mode, GLint i1, GLint i2);"
833 	<cdecl: void 'glEvalMesh1' (ulong long long) module: 'OpenGL'>
834 	^self externalCallFailed! !
835 
836 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
837 glEvalMesh2: mode with: i1 with: i2 with: j1 with: j2
838 	"This method was automatically generated."
839 	"void glEvalMesh2(GLenum mode, GLint i1, GLint i2, GLint j1, GLint j2);"
840 	<cdecl: void 'glEvalMesh2' (ulong long long long long) module: 'OpenGL'>
841 	^self externalCallFailed! !
842 
843 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
844 glEvalPoint1: i
845 	"This method was automatically generated."
846 	"void glEvalPoint1(GLint i);"
847 	<cdecl: void 'glEvalPoint1' (long) module: 'OpenGL'>
848 	^self externalCallFailed! !
849 
850 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
851 glEvalPoint2: i with: j
852 	"This method was automatically generated."
853 	"void glEvalPoint2(GLint i, GLint j);"
854 	<cdecl: void 'glEvalPoint2' (long long) module: 'OpenGL'>
855 	^self externalCallFailed! !
856 
857 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
858 glFeedbackBuffer: size with: type with: buffer
859 	"This method was automatically generated."
860 	"void glFeedbackBuffer(GLsizei size, GLenum type, GLfloat* buffer);"
861 	<cdecl: void 'glFeedbackBuffer' (long ulong float*) module: 'OpenGL'>
862 	^self externalCallFailed! !
863 
864 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
865 glFinish
866 	"This method was automatically generated."
867 	"void glFinish();"
868 	<cdecl: void 'glFinish' (void) module: 'OpenGL'>
869 	^self externalCallFailed! !
870 
871 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
872 glFlush
873 	"This method was automatically generated."
874 	"void glFlush();"
875 	<cdecl: void 'glFlush' (void) module: 'OpenGL'>
876 	^self externalCallFailed! !
877 
878 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
879 glFogf: pname with: param
880 	"This method was automatically generated."
881 	"void glFogf(GLenum pname, GLfloat param);"
882 	<cdecl: void 'glFogf' (ulong float) module: 'OpenGL'>
883 	^self externalCallFailed! !
884 
885 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
886 glFogfv: pname with: params
887 	"This method was automatically generated."
888 	"void glFogfv(GLenum pname, GLfloat* params);"
889 	<cdecl: void 'glFogfv' (ulong float*) module: 'OpenGL'>
890 	^self externalCallFailed! !
891 
892 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
893 glFogi: pname with: param
894 	"This method was automatically generated."
895 	"void glFogi(GLenum pname, GLint param);"
896 	<cdecl: void 'glFogi' (ulong long) module: 'OpenGL'>
897 	^self externalCallFailed! !
898 
899 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
900 glFogiv: pname with: params
901 	"This method was automatically generated."
902 	"void glFogiv(GLenum pname, GLint* params);"
903 	<cdecl: void 'glFogiv' (ulong long*) module: 'OpenGL'>
904 	^self externalCallFailed! !
905 
906 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
907 glFrontFace: mode
908 	"This method was automatically generated."
909 	"void glFrontFace(GLenum mode);"
910 	<cdecl: void 'glFrontFace' (ulong) module: 'OpenGL'>
911 	^self externalCallFailed! !
912 
913 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
914 glFrustum: left with: right with: bottom with: top with: zNear with: zFar
915 	"This method was automatically generated."
916 	"void glFrustum(GLdouble left, GLdouble right, GLdouble bottom, GLdouble top, GLdouble zNear, GLdouble zFar);"
917 	<cdecl: void 'glFrustum' (double double double double double double) module: 'OpenGL'>
918 	^self externalCallFailed! !
919 
920 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/8/2003 00:18'!
921 glGenLists: range
922 	"This method was automatically generated."
923 	"GLuint glGenLists(GLsizei range);"
924 	<cdecl: ulong 'glGenLists' (long) module: 'OpenGL'>
925 	^self externalCallFailed! !
926 
927 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
928 glGenTextures: n with: textures
929 	"This method was automatically generated."
930 	"void glGenTextures(GLsizei n, GLuint* textures);"
931 	<cdecl: void 'glGenTextures' (long ulong*) module: 'OpenGL'>
932 	^self externalCallFailed! !
933 
934 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
935 glGenTexturesEXT: n with: textures
936 	"This method was automatically generated."
937 	"void glGenTexturesEXT(GLsizei n, GLuint* textures);"
938 	<cdecl: void 'glGenTexturesEXT' (long ulong*) module: 'OpenGL'>
939 	^self externalCallFailed! !
940 
941 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
942 glGetBooleanv: pname with: params
943 	"This method was automatically generated."
944 	"void glGetBooleanv(GLenum pname, GLboolean* params);"
945 	<cdecl: void 'glGetBooleanv' (ulong ulong*) module: 'OpenGL'>
946 	^self externalCallFailed! !
947 
948 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
949 glGetClipPlane: plane with: equation
950 	"This method was automatically generated."
951 	"void glGetClipPlane(GLenum plane, GLdouble* equation);"
952 	<cdecl: void 'glGetClipPlane' (ulong double*) module: 'OpenGL'>
953 	^self externalCallFailed! !
954 
955 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
956 glGetColorTable: targt with: format with: type with: table
957 	"This method was automatically generated."
958 	"void glGetColorTable(GLenum target, GLenum format, GLenum type, GLvoid* table);"
959 	<cdecl: void 'glGetColorTable' (ulong ulong ulong void*) module: 'OpenGL'>
960 	^self externalCallFailed! !
961 
962 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
963 glGetColorTableParameterfv: targt with: pname with: params
964 	"This method was automatically generated."
965 	"void glGetColorTableParameterfv(GLenum target, GLenum pname, GLfloat* params);"
966 	<cdecl: void 'glGetColorTableParameterfv' (ulong ulong float*) module: 'OpenGL'>
967 	^self externalCallFailed! !
968 
969 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
970 glGetColorTableParameteriv: targt with: pname with: params
971 	"This method was automatically generated."
972 	"void glGetColorTableParameteriv(GLenum target, GLenum pname, GLint* params);"
973 	<cdecl: void 'glGetColorTableParameteriv' (ulong ulong long*) module: 'OpenGL'>
974 	^self externalCallFailed! !
975 
976 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
977 glGetConvolutionFilter: targt with: format with: type with: image
978 	"This method was automatically generated."
979 	"void glGetConvolutionFilter(GLenum target, GLenum format, GLenum type, GLvoid* image);"
980 	<cdecl: void 'glGetConvolutionFilter' (ulong ulong ulong void*) module: 'OpenGL'>
981 	^self externalCallFailed! !
982 
983 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
984 glGetConvolutionParameterfv: targt with: pname with: params
985 	"This method was automatically generated."
986 	"void glGetConvolutionParameterfv(GLenum target, GLenum pname, GLfloat* params);"
987 	<cdecl: void 'glGetConvolutionParameterfv' (ulong ulong float*) module: 'OpenGL'>
988 	^self externalCallFailed! !
989 
990 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
991 glGetConvolutionParameteriv: targt with: pname with: params
992 	"This method was automatically generated."
993 	"void glGetConvolutionParameteriv(GLenum target, GLenum pname, GLint* params);"
994 	<cdecl: void 'glGetConvolutionParameteriv' (ulong ulong long*) module: 'OpenGL'>
995 	^self externalCallFailed! !
996 
997 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
998 glGetDoublev: pname with: params
999 	"This method was automatically generated."
1000 	"void glGetDoublev(GLenum pname, GLdouble* params);"
1001 	<cdecl: void 'glGetDoublev' (ulong double*) module: 'OpenGL'>
1002 	^self externalCallFailed! !
1003 
1004 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1005 glGetError
1006 	"This method was automatically generated."
1007 	"GLenum glGetError();"
1008 	<cdecl: ulong 'glGetError' (void) module: 'OpenGL'>
1009 	^self externalCallFailed! !
1010 
1011 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1012 glGetFloatv: pname with: params
1013 	"This method was automatically generated."
1014 	"void glGetFloatv(GLenum pname, GLfloat* params);"
1015 	<cdecl: void 'glGetFloatv' (ulong float*) module: 'OpenGL'>
1016 	^self externalCallFailed! !
1017 
1018 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1019 glGetHistogram: targt with: reset with: format with: type with: values
1020 	"This method was automatically generated."
1021 	"void glGetHistogram(GLenum target, GLboolean reset, GLenum format, GLenum type, GLvoid* values);"
1022 	<cdecl: void 'glGetHistogram' (ulong bool ulong ulong void*) module: 'OpenGL'>
1023 	^self externalCallFailed! !
1024 
1025 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1026 glGetHistogramParameterfv: targt with: pname with: params
1027 	"This method was automatically generated."
1028 	"void glGetHistogramParameterfv(GLenum target, GLenum pname, GLfloat* params);"
1029 	<cdecl: void 'glGetHistogramParameterfv' (ulong ulong float*) module: 'OpenGL'>
1030 	^self externalCallFailed! !
1031 
1032 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1033 glGetHistogramParameteriv: targt with: pname with: params
1034 	"This method was automatically generated."
1035 	"void glGetHistogramParameteriv(GLenum target, GLenum pname, GLint* params);"
1036 	<cdecl: void 'glGetHistogramParameteriv' (ulong ulong long*) module: 'OpenGL'>
1037 	^self externalCallFailed! !
1038 
1039 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1040 glGetIntegerv: pname with: params
1041 	"This method was automatically generated."
1042 	"void glGetIntegerv(GLenum pname, GLint* params);"
1043 	<cdecl: void 'glGetIntegerv' (ulong long*) module: 'OpenGL'>
1044 	^self externalCallFailed! !
1045 
1046 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1047 glGetLightfv: light with: pname with: params
1048 	"This method was automatically generated."
1049 	"void glGetLightfv(GLenum light, GLenum pname, GLfloat* params);"
1050 	<cdecl: void 'glGetLightfv' (ulong ulong float*) module: 'OpenGL'>
1051 	^self externalCallFailed! !
1052 
1053 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1054 glGetLightiv: light with: pname with: params
1055 	"This method was automatically generated."
1056 	"void glGetLightiv(GLenum light, GLenum pname, GLint* params);"
1057 	<cdecl: void 'glGetLightiv' (ulong ulong long*) module: 'OpenGL'>
1058 	^self externalCallFailed! !
1059 
1060 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1061 glGetMapdv: targt with: query with: v
1062 	"This method was automatically generated."
1063 	"void glGetMapdv(GLenum target, GLenum query, GLdouble* v);"
1064 	<cdecl: void 'glGetMapdv' (ulong ulong double*) module: 'OpenGL'>
1065 	^self externalCallFailed! !
1066 
1067 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1068 glGetMapfv: targt with: query with: v
1069 	"This method was automatically generated."
1070 	"void glGetMapfv(GLenum target, GLenum query, GLfloat* v);"
1071 	<cdecl: void 'glGetMapfv' (ulong ulong float*) module: 'OpenGL'>
1072 	^self externalCallFailed! !
1073 
1074 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1075 glGetMapiv: targt with: query with: v
1076 	"This method was automatically generated."
1077 	"void glGetMapiv(GLenum target, GLenum query, GLint* v);"
1078 	<cdecl: void 'glGetMapiv' (ulong ulong long*) module: 'OpenGL'>
1079 	^self externalCallFailed! !
1080 
1081 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1082 glGetMaterialfv: face with: pname with: params
1083 	"This method was automatically generated."
1084 	"void glGetMaterialfv(GLenum face, GLenum pname, GLfloat* params);"
1085 	<cdecl: void 'glGetMaterialfv' (ulong ulong float*) module: 'OpenGL'>
1086 	^self externalCallFailed! !
1087 
1088 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1089 glGetMaterialiv: face with: pname with: params
1090 	"This method was automatically generated."
1091 	"void glGetMaterialiv(GLenum face, GLenum pname, GLint* params);"
1092 	<cdecl: void 'glGetMaterialiv' (ulong ulong long*) module: 'OpenGL'>
1093 	^self externalCallFailed! !
1094 
1095 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1096 glGetMinmax: targt with: reset with: format with: type with: values
1097 	"This method was automatically generated."
1098 	"void glGetMinmax(GLenum target, GLboolean reset, GLenum format, GLenum type, GLvoid* values);"
1099 	<cdecl: void 'glGetMinmax' (ulong bool ulong ulong void*) module: 'OpenGL'>
1100 	^self externalCallFailed! !
1101 
1102 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1103 glGetMinmaxParameterfv: targt with: pname with: params
1104 	"This method was automatically generated."
1105 	"void glGetMinmaxParameterfv(GLenum target, GLenum pname, GLfloat* params);"
1106 	<cdecl: void 'glGetMinmaxParameterfv' (ulong ulong float*) module: 'OpenGL'>
1107 	^self externalCallFailed! !
1108 
1109 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1110 glGetMinmaxParameteriv: targt with: pname with: params
1111 	"This method was automatically generated."
1112 	"void glGetMinmaxParameteriv(GLenum target, GLenum pname, GLint* params);"
1113 	<cdecl: void 'glGetMinmaxParameteriv' (ulong ulong long*) module: 'OpenGL'>
1114 	^self externalCallFailed! !
1115 
1116 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1117 glGetPixelMapfv: map with: values
1118 	"This method was automatically generated."
1119 	"void glGetPixelMapfv(GLenum map, GLfloat* values);"
1120 	<cdecl: void 'glGetPixelMapfv' (ulong float*) module: 'OpenGL'>
1121 	^self externalCallFailed! !
1122 
1123 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1124 glGetPixelMapuiv: map with: values
1125 	"This method was automatically generated."
1126 	"void glGetPixelMapuiv(GLenum map, GLuint* values);"
1127 	<cdecl: void 'glGetPixelMapuiv' (ulong ulong*) module: 'OpenGL'>
1128 	^self externalCallFailed! !
1129 
1130 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1131 glGetPixelMapusv: map with: values
1132 	"This method was automatically generated."
1133 	"void glGetPixelMapusv(GLenum map, GLushort* values);"
1134 	<cdecl: void 'glGetPixelMapusv' (ulong ushort*) module: 'OpenGL'>
1135 	^self externalCallFailed! !
1136 
1137 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1138 glGetPointerv: pname with: params
1139 	"This method was automatically generated."
1140 	"void glGetPointerv(GLenum pname, GLvoid** params);"
1141 	<cdecl: void 'glGetPointerv' (ulong void*) module: 'OpenGL'>
1142 	^self externalCallFailed! !
1143 
1144 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1145 glGetPointervEXT: pname with: params
1146 	"This method was automatically generated."
1147 	"void glGetPointervEXT(GLenum pname, GLvoid** params);"
1148 	<cdecl: void 'glGetPointervEXT' (ulong void*) module: 'OpenGL'>
1149 	^self externalCallFailed! !
1150 
1151 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1152 glGetPolygonStipple: mask
1153 	"This method was automatically generated."
1154 	"void glGetPolygonStipple(GLubyte* mask);"
1155 	<cdecl: void 'glGetPolygonStipple' (byte*) module: 'OpenGL'>
1156 	^self externalCallFailed! !
1157 
1158 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1159 glGetSeparableFilter: targt with: format with: type with: row with: column with: span
1160 	"This method was automatically generated."
1161 	"void glGetSeparableFilter(GLenum target, GLenum format, GLenum type, GLvoid* row, GLvoid* column, GLvoid* span);"
1162 	<cdecl: void 'glGetSeparableFilter' (ulong ulong ulong void* void* void*) module: 'OpenGL'>
1163 	^self externalCallFailed! !
1164 
1165 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1166 glGetString: name
1167 	"This method was automatically generated."
1168 	"GLubyte* glGetString(GLenum name);"
1169 	<cdecl: byte* 'glGetString' (ulong) module: 'OpenGL'>
1170 	^self externalCallFailed! !
1171 
1172 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1173 glGetTexEnvfv: targt with: pname with: params
1174 	"This method was automatically generated."
1175 	"void glGetTexEnvfv(GLenum target, GLenum pname, GLfloat* params);"
1176 	<cdecl: void 'glGetTexEnvfv' (ulong ulong float*) module: 'OpenGL'>
1177 	^self externalCallFailed! !
1178 
1179 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1180 glGetTexEnviv: targt with: pname with: params
1181 	"This method was automatically generated."
1182 	"void glGetTexEnviv(GLenum target, GLenum pname, GLint* params);"
1183 	<cdecl: void 'glGetTexEnviv' (ulong ulong long*) module: 'OpenGL'>
1184 	^self externalCallFailed! !
1185 
1186 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1187 glGetTexGendv: coord with: pname with: params
1188 	"This method was automatically generated."
1189 	"void glGetTexGendv(GLenum coord, GLenum pname, GLdouble* params);"
1190 	<cdecl: void 'glGetTexGendv' (ulong ulong double*) module: 'OpenGL'>
1191 	^self externalCallFailed! !
1192 
1193 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1194 glGetTexGenfv: coord with: pname with: params
1195 	"This method was automatically generated."
1196 	"void glGetTexGenfv(GLenum coord, GLenum pname, GLfloat* params);"
1197 	<cdecl: void 'glGetTexGenfv' (ulong ulong float*) module: 'OpenGL'>
1198 	^self externalCallFailed! !
1199 
1200 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1201 glGetTexGeniv: coord with: pname with: params
1202 	"This method was automatically generated."
1203 	"void glGetTexGeniv(GLenum coord, GLenum pname, GLint* params);"
1204 	<cdecl: void 'glGetTexGeniv' (ulong ulong long*) module: 'OpenGL'>
1205 	^self externalCallFailed! !
1206 
1207 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1208 glGetTexImage: targt with: level with: format with: type with: pixels
1209 	"This method was automatically generated."
1210 	"void glGetTexImage(GLenum target, GLint level, GLenum format, GLenum type, GLvoid* pixels);"
1211 	<cdecl: void 'glGetTexImage' (ulong long ulong ulong void*) module: 'OpenGL'>
1212 	^self externalCallFailed! !
1213 
1214 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1215 glGetTexLevelParameterfv: targt with: level with: pname with: params
1216 	"This method was automatically generated."
1217 	"void glGetTexLevelParameterfv(GLenum target, GLint level, GLenum pname, GLfloat* params);"
1218 	<cdecl: void 'glGetTexLevelParameterfv' (ulong long ulong float*) module: 'OpenGL'>
1219 	^self externalCallFailed! !
1220 
1221 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1222 glGetTexLevelParameteriv: targt with: level with: pname with: params
1223 	"This method was automatically generated."
1224 	"void glGetTexLevelParameteriv(GLenum target, GLint level, GLenum pname, GLint* params);"
1225 	<cdecl: void 'glGetTexLevelParameteriv' (ulong long ulong long*) module: 'OpenGL'>
1226 	^self externalCallFailed! !
1227 
1228 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1229 glGetTexParameterfv: targt with: pname with: params
1230 	"This method was automatically generated."
1231 	"void glGetTexParameterfv(GLenum target, GLenum pname, GLfloat* params);"
1232 	<cdecl: void 'glGetTexParameterfv' (ulong ulong float*) module: 'OpenGL'>
1233 	^self externalCallFailed! !
1234 
1235 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1236 glGetTexParameteriv: targt with: pname with: params
1237 	"This method was automatically generated."
1238 	"void glGetTexParameteriv(GLenum target, GLenum pname, GLint* params);"
1239 	<cdecl: void 'glGetTexParameteriv' (ulong ulong long*) module: 'OpenGL'>
1240 	^self externalCallFailed! !
1241 
1242 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1243 glHint: targt with: mode
1244 	"This method was automatically generated."
1245 	"void glHint(GLenum target, GLenum mode);"
1246 	<cdecl: void 'glHint' (ulong ulong) module: 'OpenGL'>
1247 	^self externalCallFailed! !
1248 
1249 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1250 glHistogram: targt with: width with: internalformat with: sink
1251 	"This method was automatically generated."
1252 	"void glHistogram(GLenum target, GLsizei width, GLenum internalformat, GLboolean sink);"
1253 	<cdecl: void 'glHistogram' (ulong long ulong bool) module: 'OpenGL'>
1254 	^self externalCallFailed! !
1255 
1256 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1257 glIndexMask: mask
1258 	"This method was automatically generated."
1259 	"void glIndexMask(GLuint mask);"
1260 	<cdecl: void 'glIndexMask' (ulong) module: 'OpenGL'>
1261 	^self externalCallFailed! !
1262 
1263 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1264 glIndexPointer: type with: stride with: pointer
1265 	"This method was automatically generated."
1266 	"void glIndexPointer(GLenum type, GLsizei stride, GLvoid* pointer);"
1267 	<cdecl: void 'glIndexPointer' (ulong long void*) module: 'OpenGL'>
1268 	^self externalCallFailed! !
1269 
1270 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1271 glIndexPointerEXT: type with: stride with: count with: pointer
1272 	"This method was automatically generated."
1273 	"void glIndexPointerEXT(GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
1274 	<cdecl: void 'glIndexPointerEXT' (ulong long long void*) module: 'OpenGL'>
1275 	^self externalCallFailed! !
1276 
1277 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1278 glIndexd: c
1279 	"This method was automatically generated."
1280 	"void glIndexd(GLdouble c);"
1281 	<cdecl: void 'glIndexd' (double) module: 'OpenGL'>
1282 	^self externalCallFailed! !
1283 
1284 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1285 glIndexdv: c
1286 	"This method was automatically generated."
1287 	"void glIndexdv(GLdouble* c);"
1288 	<cdecl: void 'glIndexdv' (double*) module: 'OpenGL'>
1289 	^self externalCallFailed! !
1290 
1291 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1292 glIndexf: c
1293 	"This method was automatically generated."
1294 	"void glIndexf(GLfloat c);"
1295 	<cdecl: void 'glIndexf' (float) module: 'OpenGL'>
1296 	^self externalCallFailed! !
1297 
1298 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1299 glIndexfv: c
1300 	"This method was automatically generated."
1301 	"void glIndexfv(GLfloat* c);"
1302 	<cdecl: void 'glIndexfv' (float*) module: 'OpenGL'>
1303 	^self externalCallFailed! !
1304 
1305 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1306 glIndexi: c
1307 	"This method was automatically generated."
1308 	"void glIndexi(GLint c);"
1309 	<cdecl: void 'glIndexi' (long) module: 'OpenGL'>
1310 	^self externalCallFailed! !
1311 
1312 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1313 glIndexiv: c
1314 	"This method was automatically generated."
1315 	"void glIndexiv(GLint* c);"
1316 	<cdecl: void 'glIndexiv' (long*) module: 'OpenGL'>
1317 	^self externalCallFailed! !
1318 
1319 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1320 glIndexs: c
1321 	"This method was automatically generated."
1322 	"void glIndexs(GLshort c);"
1323 	<cdecl: void 'glIndexs' (short) module: 'OpenGL'>
1324 	^self externalCallFailed! !
1325 
1326 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1327 glIndexsv: c
1328 	"This method was automatically generated."
1329 	"void glIndexsv(GLshort* c);"
1330 	<cdecl: void 'glIndexsv' (short*) module: 'OpenGL'>
1331 	^self externalCallFailed! !
1332 
1333 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1334 glIndexub: c
1335 	"This method was automatically generated."
1336 	"void glIndexub(GLubyte c);"
1337 	<cdecl: void 'glIndexub' (byte) module: 'OpenGL'>
1338 	^self externalCallFailed! !
1339 
1340 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1341 glIndexubv: c
1342 	"This method was automatically generated."
1343 	"void glIndexubv(GLubyte* c);"
1344 	<cdecl: void 'glIndexubv' (byte*) module: 'OpenGL'>
1345 	^self externalCallFailed! !
1346 
1347 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1348 glInitNames
1349 	"This method was automatically generated."
1350 	"void glInitNames();"
1351 	<cdecl: void 'glInitNames' (void) module: 'OpenGL'>
1352 	^self externalCallFailed! !
1353 
1354 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1355 glInterleavedArrays: format with: stride with: pointer
1356 	"This method was automatically generated."
1357 	"void glInterleavedArrays(GLenum format, GLsizei stride, GLvoid* pointer);"
1358 	<cdecl: void 'glInterleavedArrays' (ulong long void*) module: 'OpenGL'>
1359 	^self externalCallFailed! !
1360 
1361 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1362 glIsEnabled: cap
1363 	"This method was automatically generated."
1364 	"GLboolean glIsEnabled(GLenum cap);"
1365 	<cdecl: bool 'glIsEnabled' (ulong) module: 'OpenGL'>
1366 	^self externalCallFailed! !
1367 
1368 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1369 glIsList: list
1370 	"This method was automatically generated."
1371 	"GLboolean glIsList(GLuint list);"
1372 	<cdecl: bool 'glIsList' (ulong) module: 'OpenGL'>
1373 	^self externalCallFailed! !
1374 
1375 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1376 glIsTexture: texture
1377 	"This method was automatically generated."
1378 	"GLboolean glIsTexture(GLuint texture);"
1379 	<cdecl: bool 'glIsTexture' (ulong) module: 'OpenGL'>
1380 	^self externalCallFailed! !
1381 
1382 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1383 glIsTextureEXT: texture
1384 	"This method was automatically generated."
1385 	"GLboolean glIsTextureEXT(GLuint texture);"
1386 	<cdecl: bool 'glIsTextureEXT' (ulong) module: 'OpenGL'>
1387 	^self externalCallFailed! !
1388 
1389 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1390 glLightModelf: pname with: param
1391 	"This method was automatically generated."
1392 	"void glLightModelf(GLenum pname, GLfloat param);"
1393 	<cdecl: void 'glLightModelf' (ulong float) module: 'OpenGL'>
1394 	^self externalCallFailed! !
1395 
1396 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1397 glLightModelfv: pname with: params
1398 	"This method was automatically generated."
1399 	"void glLightModelfv(GLenum pname, GLfloat* params);"
1400 	<cdecl: void 'glLightModelfv' (ulong float*) module: 'OpenGL'>
1401 	^self externalCallFailed! !
1402 
1403 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1404 glLightModeli: pname with: param
1405 	"This method was automatically generated."
1406 	"void glLightModeli(GLenum pname, GLint param);"
1407 	<cdecl: void 'glLightModeli' (ulong long) module: 'OpenGL'>
1408 	^self externalCallFailed! !
1409 
1410 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1411 glLightModeliv: pname with: params
1412 	"This method was automatically generated."
1413 	"void glLightModeliv(GLenum pname, GLint* params);"
1414 	<cdecl: void 'glLightModeliv' (ulong long*) module: 'OpenGL'>
1415 	^self externalCallFailed! !
1416 
1417 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1418 glLightf: light with: pname with: param
1419 	"This method was automatically generated."
1420 	"void glLightf(GLenum light, GLenum pname, GLfloat param);"
1421 	<cdecl: void 'glLightf' (ulong ulong float) module: 'OpenGL'>
1422 	^self externalCallFailed! !
1423 
1424 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1425 glLightfv: light with: pname with: params
1426 	"This method was automatically generated."
1427 	"void glLightfv(GLenum light, GLenum pname, GLfloat* params);"
1428 	<cdecl: void 'glLightfv' (ulong ulong float*) module: 'OpenGL'>
1429 	^self externalCallFailed! !
1430 
1431 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1432 glLighti: light with: pname with: param
1433 	"This method was automatically generated."
1434 	"void glLighti(GLenum light, GLenum pname, GLint param);"
1435 	<cdecl: void 'glLighti' (ulong ulong long) module: 'OpenGL'>
1436 	^self externalCallFailed! !
1437 
1438 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1439 glLightiv: light with: pname with: params
1440 	"This method was automatically generated."
1441 	"void glLightiv(GLenum light, GLenum pname, GLint* params);"
1442 	<cdecl: void 'glLightiv' (ulong ulong long*) module: 'OpenGL'>
1443 	^self externalCallFailed! !
1444 
1445 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1446 glLineStipple: factor with: pattern
1447 	"This method was automatically generated."
1448 	"void glLineStipple(GLint factor, GLushort pattern);"
1449 	<cdecl: void 'glLineStipple' (long ushort) module: 'OpenGL'>
1450 	^self externalCallFailed! !
1451 
1452 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1453 glLineWidth: width
1454 	"This method was automatically generated."
1455 	"void glLineWidth(GLfloat width);"
1456 	<cdecl: void 'glLineWidth' (float) module: 'OpenGL'>
1457 	^self externalCallFailed! !
1458 
1459 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1460 glListBase: base
1461 	"This method was automatically generated."
1462 	"void glListBase(GLuint base);"
1463 	<cdecl: void 'glListBase' (ulong) module: 'OpenGL'>
1464 	^self externalCallFailed! !
1465 
1466 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1467 glLoadIdentity
1468 	"This method was automatically generated."
1469 	"void glLoadIdentity();"
1470 	<cdecl: void 'glLoadIdentity' (void) module: 'OpenGL'>
1471 	^self externalCallFailed! !
1472 
1473 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1474 glLoadMatrixd: m
1475 	"This method was automatically generated."
1476 	"void glLoadMatrixd(GLdouble* m);"
1477 	<cdecl: void 'glLoadMatrixd' (double*) module: 'OpenGL'>
1478 	^self externalCallFailed! !
1479 
1480 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1481 glLoadMatrixf: m
1482 	"This method was automatically generated."
1483 	"void glLoadMatrixf(GLfloat* m);"
1484 	<cdecl: void 'glLoadMatrixf' (float*) module: 'OpenGL'>
1485 	^self externalCallFailed! !
1486 
1487 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1488 glLoadName: name
1489 	"This method was automatically generated."
1490 	"void glLoadName(GLuint name);"
1491 	<cdecl: void 'glLoadName' (ulong) module: 'OpenGL'>
1492 	^self externalCallFailed! !
1493 
1494 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1495 glLockArraysEXT: first with: count
1496 	"This method was automatically generated."
1497 	"void glLockArraysEXT(GLint first, GLsizei count);"
1498 	<cdecl: void 'glLockArraysEXT' (long long) module: 'OpenGL'>
1499 	^self externalCallFailed! !
1500 
1501 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1502 glLogicOp: opcode
1503 	"This method was automatically generated."
1504 	"void glLogicOp(GLenum opcode);"
1505 	<cdecl: void 'glLogicOp' (ulong) module: 'OpenGL'>
1506 	^self externalCallFailed! !
1507 
1508 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1509 glMap1d: targt with: u1 with: u2 with: stride with: order with: points
1510 	"This method was automatically generated."
1511 	"void glMap1d(GLenum target, GLdouble u1, GLdouble u2, GLint stride, GLint order, GLdouble* points);"
1512 	<cdecl: void 'glMap1d' (ulong double double long long double*) module: 'OpenGL'>
1513 	^self externalCallFailed! !
1514 
1515 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1516 glMap1f: targt with: u1 with: u2 with: stride with: order with: points
1517 	"This method was automatically generated."
1518 	"void glMap1f(GLenum target, GLfloat u1, GLfloat u2, GLint stride, GLint order, GLfloat* points);"
1519 	<cdecl: void 'glMap1f' (ulong float float long long float*) module: 'OpenGL'>
1520 	^self externalCallFailed! !
1521 
1522 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1523 glMap2d: targt with: u1 with: u2 with: ustride with: uorder with: v1 with: v2 with: vstride with: vorder with: points
1524 	"This method was automatically generated."
1525 	"void glMap2d(GLenum target, GLdouble u1, GLdouble u2, GLint ustride, GLint uorder, GLdouble v1, GLdouble v2, GLint vstride, GLint vorder, GLdouble* points);"
1526 	<cdecl: void 'glMap2d' (ulong double double long long double double long long double*) module: 'OpenGL'>
1527 	^self externalCallFailed! !
1528 
1529 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1530 glMap2f: targt with: u1 with: u2 with: ustride with: uorder with: v1 with: v2 with: vstride with: vorder with: points
1531 	"This method was automatically generated."
1532 	"void glMap2f(GLenum target, GLfloat u1, GLfloat u2, GLint ustride, GLint uorder, GLfloat v1, GLfloat v2, GLint vstride, GLint vorder, GLfloat* points);"
1533 	<cdecl: void 'glMap2f' (ulong float float long long float float long long float*) module: 'OpenGL'>
1534 	^self externalCallFailed! !
1535 
1536 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1537 glMapGrid1d: un with: u1 with: u2
1538 	"This method was automatically generated."
1539 	"void glMapGrid1d(GLint un, GLdouble u1, GLdouble u2);"
1540 	<cdecl: void 'glMapGrid1d' (long double double) module: 'OpenGL'>
1541 	^self externalCallFailed! !
1542 
1543 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1544 glMapGrid1f: un with: u1 with: u2
1545 	"This method was automatically generated."
1546 	"void glMapGrid1f(GLint un, GLfloat u1, GLfloat u2);"
1547 	<cdecl: void 'glMapGrid1f' (long float float) module: 'OpenGL'>
1548 	^self externalCallFailed! !
1549 
1550 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1551 glMapGrid2d: un with: u1 with: u2 with: vn with: v1 with: v2
1552 	"This method was automatically generated."
1553 	"void glMapGrid2d(GLint un, GLdouble u1, GLdouble u2, GLint vn, GLdouble v1, GLdouble v2);"
1554 	<cdecl: void 'glMapGrid2d' (long double double long double double) module: 'OpenGL'>
1555 	^self externalCallFailed! !
1556 
1557 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1558 glMapGrid2f: un with: u1 with: u2 with: vn with: v1 with: v2
1559 	"This method was automatically generated."
1560 	"void glMapGrid2f(GLint un, GLfloat u1, GLfloat u2, GLint vn, GLfloat v1, GLfloat v2);"
1561 	<cdecl: void 'glMapGrid2f' (long float float long float float) module: 'OpenGL'>
1562 	^self externalCallFailed! !
1563 
1564 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1565 glMaterialf: face with: pname with: param
1566 	"This method was automatically generated."
1567 	"void glMaterialf(GLenum face, GLenum pname, GLfloat param);"
1568 	<cdecl: void 'glMaterialf' (ulong ulong float) module: 'OpenGL'>
1569 	^self externalCallFailed! !
1570 
1571 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1572 glMaterialfv: face with: pname with: params
1573 	"This method was automatically generated."
1574 	"void glMaterialfv(GLenum face, GLenum pname, GLfloat* params);"
1575 	<cdecl: void 'glMaterialfv' (ulong ulong float*) module: 'OpenGL'>
1576 	^self externalCallFailed! !
1577 
1578 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1579 glMateriali: face with: pname with: param
1580 	"This method was automatically generated."
1581 	"void glMateriali(GLenum face, GLenum pname, GLint param);"
1582 	<cdecl: void 'glMateriali' (ulong ulong long) module: 'OpenGL'>
1583 	^self externalCallFailed! !
1584 
1585 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1586 glMaterialiv: face with: pname with: params
1587 	"This method was automatically generated."
1588 	"void glMaterialiv(GLenum face, GLenum pname, GLint* params);"
1589 	<cdecl: void 'glMaterialiv' (ulong ulong long*) module: 'OpenGL'>
1590 	^self externalCallFailed! !
1591 
1592 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1593 glMatrixMode: mode
1594 	"This method was automatically generated."
1595 	"void glMatrixMode(GLenum mode);"
1596 	<cdecl: void 'glMatrixMode' (ulong) module: 'OpenGL'>
1597 	^self externalCallFailed! !
1598 
1599 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1600 glMinmax: targt with: internalformat with: sink
1601 	"This method was automatically generated."
1602 	"void glMinmax(GLenum target, GLenum internalformat, GLboolean sink);"
1603 	<cdecl: void 'glMinmax' (ulong ulong bool) module: 'OpenGL'>
1604 	^self externalCallFailed! !
1605 
1606 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1607 glMultMatrixd: m
1608 	"This method was automatically generated."
1609 	"void glMultMatrixd(GLdouble* m);"
1610 	<cdecl: void 'glMultMatrixd' (double*) module: 'OpenGL'>
1611 	^self externalCallFailed! !
1612 
1613 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1614 glMultMatrixf: m
1615 	"This method was automatically generated."
1616 	"void glMultMatrixf(GLfloat* m);"
1617 	<cdecl: void 'glMultMatrixf' (float*) module: 'OpenGL'>
1618 	^self externalCallFailed! !
1619 
1620 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1621 glMultiTexCoord1dARB: targt with: s
1622 	"This method was automatically generated."
1623 	"void glMultiTexCoord1dARB(GLenum target, GLdouble s);"
1624 	<cdecl: void 'glMultiTexCoord1dARB' (ulong double) module: 'OpenGL'>
1625 	^self externalCallFailed! !
1626 
1627 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1628 glMultiTexCoord1dvARB: targt with: v
1629 	"This method was automatically generated."
1630 	"void glMultiTexCoord1dvARB(GLenum target, GLdouble* v);"
1631 	<cdecl: void 'glMultiTexCoord1dvARB' (ulong double*) module: 'OpenGL'>
1632 	^self externalCallFailed! !
1633 
1634 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1635 glMultiTexCoord1fARB: targt with: s
1636 	"This method was automatically generated."
1637 	"void glMultiTexCoord1fARB(GLenum target, GLfloat s);"
1638 	<cdecl: void 'glMultiTexCoord1fARB' (ulong float) module: 'OpenGL'>
1639 	^self externalCallFailed! !
1640 
1641 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1642 glMultiTexCoord1fvARB: targt with: v
1643 	"This method was automatically generated."
1644 	"void glMultiTexCoord1fvARB(GLenum target, GLfloat* v);"
1645 	<cdecl: void 'glMultiTexCoord1fvARB' (ulong float*) module: 'OpenGL'>
1646 	^self externalCallFailed! !
1647 
1648 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1649 glMultiTexCoord1iARB: targt with: s
1650 	"This method was automatically generated."
1651 	"void glMultiTexCoord1iARB(GLenum target, GLint s);"
1652 	<cdecl: void 'glMultiTexCoord1iARB' (ulong long) module: 'OpenGL'>
1653 	^self externalCallFailed! !
1654 
1655 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1656 glMultiTexCoord1ivARB: targt with: v
1657 	"This method was automatically generated."
1658 	"void glMultiTexCoord1ivARB(GLenum target, GLint* v);"
1659 	<cdecl: void 'glMultiTexCoord1ivARB' (ulong long*) module: 'OpenGL'>
1660 	^self externalCallFailed! !
1661 
1662 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1663 glMultiTexCoord1sARB: targt with: s
1664 	"This method was automatically generated."
1665 	"void glMultiTexCoord1sARB(GLenum target, GLshort s);"
1666 	<cdecl: void 'glMultiTexCoord1sARB' (ulong short) module: 'OpenGL'>
1667 	^self externalCallFailed! !
1668 
1669 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1670 glMultiTexCoord1svARB: targt with: v
1671 	"This method was automatically generated."
1672 	"void glMultiTexCoord1svARB(GLenum target, GLshort* v);"
1673 	<cdecl: void 'glMultiTexCoord1svARB' (ulong short*) module: 'OpenGL'>
1674 	^self externalCallFailed! !
1675 
1676 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1677 glMultiTexCoord2dARB: targt with: s with: t
1678 	"This method was automatically generated."
1679 	"void glMultiTexCoord2dARB(GLenum target, GLdouble s, GLdouble t);"
1680 	<cdecl: void 'glMultiTexCoord2dARB' (ulong double double) module: 'OpenGL'>
1681 	^self externalCallFailed! !
1682 
1683 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1684 glMultiTexCoord2dvARB: targt with: v
1685 	"This method was automatically generated."
1686 	"void glMultiTexCoord2dvARB(GLenum target, GLdouble* v);"
1687 	<cdecl: void 'glMultiTexCoord2dvARB' (ulong double*) module: 'OpenGL'>
1688 	^self externalCallFailed! !
1689 
1690 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1691 glMultiTexCoord2fARB: targt with: s with: t
1692 	"This method was automatically generated."
1693 	"void glMultiTexCoord2fARB(GLenum target, GLfloat s, GLfloat t);"
1694 	<cdecl: void 'glMultiTexCoord2fARB' (ulong float float) module: 'OpenGL'>
1695 	^self externalCallFailed! !
1696 
1697 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1698 glMultiTexCoord2fvARB: targt with: v
1699 	"This method was automatically generated."
1700 	"void glMultiTexCoord2fvARB(GLenum target, GLfloat* v);"
1701 	<cdecl: void 'glMultiTexCoord2fvARB' (ulong float*) module: 'OpenGL'>
1702 	^self externalCallFailed! !
1703 
1704 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1705 glMultiTexCoord2iARB: targt with: s with: t
1706 	"This method was automatically generated."
1707 	"void glMultiTexCoord2iARB(GLenum target, GLint s, GLint t);"
1708 	<cdecl: void 'glMultiTexCoord2iARB' (ulong long long) module: 'OpenGL'>
1709 	^self externalCallFailed! !
1710 
1711 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1712 glMultiTexCoord2ivARB: targt with: v
1713 	"This method was automatically generated."
1714 	"void glMultiTexCoord2ivARB(GLenum target, GLint* v);"
1715 	<cdecl: void 'glMultiTexCoord2ivARB' (ulong long*) module: 'OpenGL'>
1716 	^self externalCallFailed! !
1717 
1718 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1719 glMultiTexCoord2sARB: targt with: s with: t
1720 	"This method was automatically generated."
1721 	"void glMultiTexCoord2sARB(GLenum target, GLshort s, GLshort t);"
1722 	<cdecl: void 'glMultiTexCoord2sARB' (ulong short short) module: 'OpenGL'>
1723 	^self externalCallFailed! !
1724 
1725 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1726 glMultiTexCoord2svARB: targt with: v
1727 	"This method was automatically generated."
1728 	"void glMultiTexCoord2svARB(GLenum target, GLshort* v);"
1729 	<cdecl: void 'glMultiTexCoord2svARB' (ulong short*) module: 'OpenGL'>
1730 	^self externalCallFailed! !
1731 
1732 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1733 glMultiTexCoord3dARB: targt with: s with: t with: r
1734 	"This method was automatically generated."
1735 	"void glMultiTexCoord3dARB(GLenum target, GLdouble s, GLdouble t, GLdouble r);"
1736 	<cdecl: void 'glMultiTexCoord3dARB' (ulong double double double) module: 'OpenGL'>
1737 	^self externalCallFailed! !
1738 
1739 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1740 glMultiTexCoord3dvARB: targt with: v
1741 	"This method was automatically generated."
1742 	"void glMultiTexCoord3dvARB(GLenum target, GLdouble* v);"
1743 	<cdecl: void 'glMultiTexCoord3dvARB' (ulong double*) module: 'OpenGL'>
1744 	^self externalCallFailed! !
1745 
1746 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1747 glMultiTexCoord3fARB: targt with: s with: t with: r
1748 	"This method was automatically generated."
1749 	"void glMultiTexCoord3fARB(GLenum target, GLfloat s, GLfloat t, GLfloat r);"
1750 	<cdecl: void 'glMultiTexCoord3fARB' (ulong float float float) module: 'OpenGL'>
1751 	^self externalCallFailed! !
1752 
1753 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1754 glMultiTexCoord3fvARB: targt with: v
1755 	"This method was automatically generated."
1756 	"void glMultiTexCoord3fvARB(GLenum target, GLfloat* v);"
1757 	<cdecl: void 'glMultiTexCoord3fvARB' (ulong float*) module: 'OpenGL'>
1758 	^self externalCallFailed! !
1759 
1760 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1761 glMultiTexCoord3iARB: targt with: s with: t with: r
1762 	"This method was automatically generated."
1763 	"void glMultiTexCoord3iARB(GLenum target, GLint s, GLint t, GLint r);"
1764 	<cdecl: void 'glMultiTexCoord3iARB' (ulong long long long) module: 'OpenGL'>
1765 	^self externalCallFailed! !
1766 
1767 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1768 glMultiTexCoord3ivARB: targt with: v
1769 	"This method was automatically generated."
1770 	"void glMultiTexCoord3ivARB(GLenum target, GLint* v);"
1771 	<cdecl: void 'glMultiTexCoord3ivARB' (ulong long*) module: 'OpenGL'>
1772 	^self externalCallFailed! !
1773 
1774 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1775 glMultiTexCoord3sARB: targt with: s with: t with: r
1776 	"This method was automatically generated."
1777 	"void glMultiTexCoord3sARB(GLenum target, GLshort s, GLshort t, GLshort r);"
1778 	<cdecl: void 'glMultiTexCoord3sARB' (ulong short short short) module: 'OpenGL'>
1779 	^self externalCallFailed! !
1780 
1781 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1782 glMultiTexCoord3svARB: targt with: v
1783 	"This method was automatically generated."
1784 	"void glMultiTexCoord3svARB(GLenum target, GLshort* v);"
1785 	<cdecl: void 'glMultiTexCoord3svARB' (ulong short*) module: 'OpenGL'>
1786 	^self externalCallFailed! !
1787 
1788 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1789 glMultiTexCoord4dARB: targt with: s with: t with: r with: q
1790 	"This method was automatically generated."
1791 	"void glMultiTexCoord4dARB(GLenum target, GLdouble s, GLdouble t, GLdouble r, GLdouble q);"
1792 	<cdecl: void 'glMultiTexCoord4dARB' (ulong double double double double) module: 'OpenGL'>
1793 	^self externalCallFailed! !
1794 
1795 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1796 glMultiTexCoord4dvARB: targt with: v
1797 	"This method was automatically generated."
1798 	"void glMultiTexCoord4dvARB(GLenum target, GLdouble* v);"
1799 	<cdecl: void 'glMultiTexCoord4dvARB' (ulong double*) module: 'OpenGL'>
1800 	^self externalCallFailed! !
1801 
1802 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1803 glMultiTexCoord4fARB: targt with: s with: t with: r with: q
1804 	"This method was automatically generated."
1805 	"void glMultiTexCoord4fARB(GLenum target, GLfloat s, GLfloat t, GLfloat r, GLfloat q);"
1806 	<cdecl: void 'glMultiTexCoord4fARB' (ulong float float float float) module: 'OpenGL'>
1807 	^self externalCallFailed! !
1808 
1809 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1810 glMultiTexCoord4fvARB: targt with: v
1811 	"This method was automatically generated."
1812 	"void glMultiTexCoord4fvARB(GLenum target, GLfloat* v);"
1813 	<cdecl: void 'glMultiTexCoord4fvARB' (ulong float*) module: 'OpenGL'>
1814 	^self externalCallFailed! !
1815 
1816 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1817 glMultiTexCoord4iARB: targt with: s with: t with: r with: q
1818 	"This method was automatically generated."
1819 	"void glMultiTexCoord4iARB(GLenum target, GLint s, GLint t, GLint r, GLint q);"
1820 	<cdecl: void 'glMultiTexCoord4iARB' (ulong long long long long) module: 'OpenGL'>
1821 	^self externalCallFailed! !
1822 
1823 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1824 glMultiTexCoord4ivARB: targt with: v
1825 	"This method was automatically generated."
1826 	"void glMultiTexCoord4ivARB(GLenum target, GLint* v);"
1827 	<cdecl: void 'glMultiTexCoord4ivARB' (ulong long*) module: 'OpenGL'>
1828 	^self externalCallFailed! !
1829 
1830 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1831 glMultiTexCoord4sARB: targt with: s with: t with: r with: q
1832 	"This method was automatically generated."
1833 	"void glMultiTexCoord4sARB(GLenum target, GLshort s, GLshort t, GLshort r, GLshort q);"
1834 	<cdecl: void 'glMultiTexCoord4sARB' (ulong short short short short) module: 'OpenGL'>
1835 	^self externalCallFailed! !
1836 
1837 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1838 glMultiTexCoord4svARB: targt with: v
1839 	"This method was automatically generated."
1840 	"void glMultiTexCoord4svARB(GLenum target, GLshort* v);"
1841 	<cdecl: void 'glMultiTexCoord4svARB' (ulong short*) module: 'OpenGL'>
1842 	^self externalCallFailed! !
1843 
1844 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1845 glNewList: list with: mode
1846 	"This method was automatically generated."
1847 	"void glNewList(GLuint list, GLenum mode);"
1848 	<cdecl: void 'glNewList' (ulong ulong) module: 'OpenGL'>
1849 	^self externalCallFailed! !
1850 
1851 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1852 glNormal3b: nx with: ny with: nz
1853 	"This method was automatically generated."
1854 	"void glNormal3b(GLbyte nx, GLbyte ny, GLbyte nz);"
1855 	<cdecl: void 'glNormal3b' (byte byte byte) module: 'OpenGL'>
1856 	^self externalCallFailed! !
1857 
1858 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1859 glNormal3bv: v
1860 	"This method was automatically generated."
1861 	"void glNormal3bv(GLbyte* v);"
1862 	<cdecl: void 'glNormal3bv' (byte*) module: 'OpenGL'>
1863 	^self externalCallFailed! !
1864 
1865 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1866 glNormal3d: nx with: ny with: nz
1867 	"This method was automatically generated."
1868 	"void glNormal3d(GLdouble nx, GLdouble ny, GLdouble nz);"
1869 	<cdecl: void 'glNormal3d' (double double double) module: 'OpenGL'>
1870 	^self externalCallFailed! !
1871 
1872 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1873 glNormal3dv: v
1874 	"This method was automatically generated."
1875 	"void glNormal3dv(GLdouble* v);"
1876 	<cdecl: void 'glNormal3dv' (double*) module: 'OpenGL'>
1877 	^self externalCallFailed! !
1878 
1879 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1880 glNormal3f: nx with: ny with: nz
1881 	"This method was automatically generated."
1882 	"void glNormal3f(GLfloat nx, GLfloat ny, GLfloat nz);"
1883 	<cdecl: void 'glNormal3f' (float float float) module: 'OpenGL'>
1884 	^self externalCallFailed! !
1885 
1886 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1887 glNormal3fv: v
1888 	"This method was automatically generated."
1889 	"void glNormal3fv(GLfloat* v);"
1890 	<cdecl: void 'glNormal3fv' (float*) module: 'OpenGL'>
1891 	^self externalCallFailed! !
1892 
1893 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1894 glNormal3i: nx with: ny with: nz
1895 	"This method was automatically generated."
1896 	"void glNormal3i(GLint nx, GLint ny, GLint nz);"
1897 	<cdecl: void 'glNormal3i' (long long long) module: 'OpenGL'>
1898 	^self externalCallFailed! !
1899 
1900 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1901 glNormal3iv: v
1902 	"This method was automatically generated."
1903 	"void glNormal3iv(GLint* v);"
1904 	<cdecl: void 'glNormal3iv' (long*) module: 'OpenGL'>
1905 	^self externalCallFailed! !
1906 
1907 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1908 glNormal3s: nx with: ny with: nz
1909 	"This method was automatically generated."
1910 	"void glNormal3s(GLshort nx, GLshort ny, GLshort nz);"
1911 	<cdecl: void 'glNormal3s' (short short short) module: 'OpenGL'>
1912 	^self externalCallFailed! !
1913 
1914 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1915 glNormal3sv: v
1916 	"This method was automatically generated."
1917 	"void glNormal3sv(GLshort* v);"
1918 	<cdecl: void 'glNormal3sv' (short*) module: 'OpenGL'>
1919 	^self externalCallFailed! !
1920 
1921 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1922 glNormalPointer: type with: stride with: pointer
1923 	"This method was automatically generated."
1924 	"void glNormalPointer(GLenum type, GLsizei stride, GLvoid* pointer);"
1925 	<cdecl: void 'glNormalPointer' (ulong long void*) module: 'OpenGL'>
1926 	^self externalCallFailed! !
1927 
1928 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1929 glNormalPointerEXT: type with: stride with: count with: pointer
1930 	"This method was automatically generated."
1931 	"void glNormalPointerEXT(GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
1932 	<cdecl: void 'glNormalPointerEXT' (ulong long long void*) module: 'OpenGL'>
1933 	^self externalCallFailed! !
1934 
1935 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1936 glOrtho: left with: right with: bottom with: top with: zNear with: zFar
1937 	"This method was automatically generated."
1938 	"void glOrtho(GLdouble left, GLdouble right, GLdouble bottom, GLdouble top, GLdouble zNear, GLdouble zFar);"
1939 	<cdecl: void 'glOrtho' (double double double double double double) module: 'OpenGL'>
1940 	^self externalCallFailed! !
1941 
1942 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1943 glPassThrough: token
1944 	"This method was automatically generated."
1945 	"void glPassThrough(GLfloat token);"
1946 	<cdecl: void 'glPassThrough' (float) module: 'OpenGL'>
1947 	^self externalCallFailed! !
1948 
1949 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1950 glPixelMapfv: map with: mapsize with: values
1951 	"This method was automatically generated."
1952 	"void glPixelMapfv(GLenum map, GLint mapsize, GLfloat* values);"
1953 	<cdecl: void 'glPixelMapfv' (ulong long float*) module: 'OpenGL'>
1954 	^self externalCallFailed! !
1955 
1956 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1957 glPixelMapuiv: map with: mapsize with: values
1958 	"This method was automatically generated."
1959 	"void glPixelMapuiv(GLenum map, GLint mapsize, GLuint* values);"
1960 	<cdecl: void 'glPixelMapuiv' (ulong long ulong*) module: 'OpenGL'>
1961 	^self externalCallFailed! !
1962 
1963 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1964 glPixelMapusv: map with: mapsize with: values
1965 	"This method was automatically generated."
1966 	"void glPixelMapusv(GLenum map, GLint mapsize, GLushort* values);"
1967 	<cdecl: void 'glPixelMapusv' (ulong long ushort*) module: 'OpenGL'>
1968 	^self externalCallFailed! !
1969 
1970 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1971 glPixelStoref: pname with: param
1972 	"This method was automatically generated."
1973 	"void glPixelStoref(GLenum pname, GLfloat param);"
1974 	<cdecl: void 'glPixelStoref' (ulong float) module: 'OpenGL'>
1975 	^self externalCallFailed! !
1976 
1977 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1978 glPixelStorei: pname with: param
1979 	"This method was automatically generated."
1980 	"void glPixelStorei(GLenum pname, GLint param);"
1981 	<cdecl: void 'glPixelStorei' (ulong long) module: 'OpenGL'>
1982 	^self externalCallFailed! !
1983 
1984 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1985 glPixelTransferf: pname with: param
1986 	"This method was automatically generated."
1987 	"void glPixelTransferf(GLenum pname, GLfloat param);"
1988 	<cdecl: void 'glPixelTransferf' (ulong float) module: 'OpenGL'>
1989 	^self externalCallFailed! !
1990 
1991 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1992 glPixelTransferi: pname with: param
1993 	"This method was automatically generated."
1994 	"void glPixelTransferi(GLenum pname, GLint param);"
1995 	<cdecl: void 'glPixelTransferi' (ulong long) module: 'OpenGL'>
1996 	^self externalCallFailed! !
1997 
1998 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
1999 glPixelZoom: xfactor with: yfactor
2000 	"This method was automatically generated."
2001 	"void glPixelZoom(GLfloat xfactor, GLfloat yfactor);"
2002 	<cdecl: void 'glPixelZoom' (float float) module: 'OpenGL'>
2003 	^self externalCallFailed! !
2004 
2005 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2006 glPointSize: size
2007 	"This method was automatically generated."
2008 	"void glPointSize(GLfloat size);"
2009 	<cdecl: void 'glPointSize' (float) module: 'OpenGL'>
2010 	^self externalCallFailed! !
2011 
2012 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2013 glPolygonMode: face with: mode
2014 	"This method was automatically generated."
2015 	"void glPolygonMode(GLenum face, GLenum mode);"
2016 	<cdecl: void 'glPolygonMode' (ulong ulong) module: 'OpenGL'>
2017 	^self externalCallFailed! !
2018 
2019 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2020 glPolygonOffset: factor with: units
2021 	"This method was automatically generated."
2022 	"void glPolygonOffset(GLfloat factor, GLfloat units);"
2023 	<cdecl: void 'glPolygonOffset' (float float) module: 'OpenGL'>
2024 	^self externalCallFailed! !
2025 
2026 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2027 glPolygonStipple: mask
2028 	"This method was automatically generated."
2029 	"void glPolygonStipple(GLubyte* mask);"
2030 	<cdecl: void 'glPolygonStipple' (byte*) module: 'OpenGL'>
2031 	^self externalCallFailed! !
2032 
2033 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2034 glPopAttrib
2035 	"This method was automatically generated."
2036 	"void glPopAttrib();"
2037 	<cdecl: void 'glPopAttrib' (void) module: 'OpenGL'>
2038 	^self externalCallFailed! !
2039 
2040 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2041 glPopClientAttrib
2042 	"This method was automatically generated."
2043 	"void glPopClientAttrib();"
2044 	<cdecl: void 'glPopClientAttrib' (void) module: 'OpenGL'>
2045 	^self externalCallFailed! !
2046 
2047 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2048 glPopMatrix
2049 	"This method was automatically generated."
2050 	"void glPopMatrix();"
2051 	<cdecl: void 'glPopMatrix' (void) module: 'OpenGL'>
2052 	^self externalCallFailed! !
2053 
2054 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2055 glPopName
2056 	"This method was automatically generated."
2057 	"void glPopName();"
2058 	<cdecl: void 'glPopName' (void) module: 'OpenGL'>
2059 	^self externalCallFailed! !
2060 
2061 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2062 glPrioritizeTextures: n with: texturez with: priorities
2063 	"This method was automatically generated."
2064 	"void glPrioritizeTextures(GLsizei n, GLuint* textures, GLclampf* priorities);"
2065 	<cdecl: void 'glPrioritizeTextures' (long ulong* float*) module: 'OpenGL'>
2066 	^self externalCallFailed! !
2067 
2068 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2069 glPushAttrib: mask
2070 	"This method was automatically generated."
2071 	"void glPushAttrib(GLbitfield mask);"
2072 	<cdecl: void 'glPushAttrib' (ulong) module: 'OpenGL'>
2073 	^self externalCallFailed! !
2074 
2075 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2076 glPushClientAttrib: mask
2077 	"This method was automatically generated."
2078 	"void glPushClientAttrib(GLbitfield mask);"
2079 	<cdecl: void 'glPushClientAttrib' (ulong) module: 'OpenGL'>
2080 	^self externalCallFailed! !
2081 
2082 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2083 glPushMatrix
2084 	"This method was automatically generated."
2085 	"void glPushMatrix();"
2086 	<cdecl: void 'glPushMatrix' (void) module: 'OpenGL'>
2087 	^self externalCallFailed! !
2088 
2089 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2090 glPushName: name
2091 	"This method was automatically generated."
2092 	"void glPushName(GLuint name);"
2093 	<cdecl: void 'glPushName' (ulong) module: 'OpenGL'>
2094 	^self externalCallFailed! !
2095 
2096 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2097 glRasterPos2d: x with: y
2098 	"This method was automatically generated."
2099 	"void glRasterPos2d(GLdouble x, GLdouble y);"
2100 	<cdecl: void 'glRasterPos2d' (double double) module: 'OpenGL'>
2101 	^self externalCallFailed! !
2102 
2103 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2104 glRasterPos2dv: v
2105 	"This method was automatically generated."
2106 	"void glRasterPos2dv(GLdouble* v);"
2107 	<cdecl: void 'glRasterPos2dv' (double*) module: 'OpenGL'>
2108 	^self externalCallFailed! !
2109 
2110 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2111 glRasterPos2f: x with: y
2112 	"This method was automatically generated."
2113 	"void glRasterPos2f(GLfloat x, GLfloat y);"
2114 	<cdecl: void 'glRasterPos2f' (float float) module: 'OpenGL'>
2115 	^self externalCallFailed! !
2116 
2117 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2118 glRasterPos2fv: v
2119 	"This method was automatically generated."
2120 	"void glRasterPos2fv(GLfloat* v);"
2121 	<cdecl: void 'glRasterPos2fv' (float*) module: 'OpenGL'>
2122 	^self externalCallFailed! !
2123 
2124 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2125 glRasterPos2i: x with: y
2126 	"This method was automatically generated."
2127 	"void glRasterPos2i(GLint x, GLint y);"
2128 	<cdecl: void 'glRasterPos2i' (long long) module: 'OpenGL'>
2129 	^self externalCallFailed! !
2130 
2131 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2132 glRasterPos2iv: v
2133 	"This method was automatically generated."
2134 	"void glRasterPos2iv(GLint* v);"
2135 	<cdecl: void 'glRasterPos2iv' (long*) module: 'OpenGL'>
2136 	^self externalCallFailed! !
2137 
2138 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2139 glRasterPos2s: x with: y
2140 	"This method was automatically generated."
2141 	"void glRasterPos2s(GLshort x, GLshort y);"
2142 	<cdecl: void 'glRasterPos2s' (short short) module: 'OpenGL'>
2143 	^self externalCallFailed! !
2144 
2145 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2146 glRasterPos2sv: v
2147 	"This method was automatically generated."
2148 	"void glRasterPos2sv(GLshort* v);"
2149 	<cdecl: void 'glRasterPos2sv' (short*) module: 'OpenGL'>
2150 	^self externalCallFailed! !
2151 
2152 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2153 glRasterPos3d: x with: y with: z
2154 	"This method was automatically generated."
2155 	"void glRasterPos3d(GLdouble x, GLdouble y, GLdouble z);"
2156 	<cdecl: void 'glRasterPos3d' (double double double) module: 'OpenGL'>
2157 	^self externalCallFailed! !
2158 
2159 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2160 glRasterPos3dv: v
2161 	"This method was automatically generated."
2162 	"void glRasterPos3dv(GLdouble* v);"
2163 	<cdecl: void 'glRasterPos3dv' (double*) module: 'OpenGL'>
2164 	^self externalCallFailed! !
2165 
2166 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2167 glRasterPos3f: x with: y with: z
2168 	"This method was automatically generated."
2169 	"void glRasterPos3f(GLfloat x, GLfloat y, GLfloat z);"
2170 	<cdecl: void 'glRasterPos3f' (float float float) module: 'OpenGL'>
2171 	^self externalCallFailed! !
2172 
2173 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2174 glRasterPos3fv: v
2175 	"This method was automatically generated."
2176 	"void glRasterPos3fv(GLfloat* v);"
2177 	<cdecl: void 'glRasterPos3fv' (float*) module: 'OpenGL'>
2178 	^self externalCallFailed! !
2179 
2180 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2181 glRasterPos3i: x with: y with: z
2182 	"This method was automatically generated."
2183 	"void glRasterPos3i(GLint x, GLint y, GLint z);"
2184 	<cdecl: void 'glRasterPos3i' (long long long) module: 'OpenGL'>
2185 	^self externalCallFailed! !
2186 
2187 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2188 glRasterPos3iv: v
2189 	"This method was automatically generated."
2190 	"void glRasterPos3iv(GLint* v);"
2191 	<cdecl: void 'glRasterPos3iv' (long*) module: 'OpenGL'>
2192 	^self externalCallFailed! !
2193 
2194 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2195 glRasterPos3s: x with: y with: z
2196 	"This method was automatically generated."
2197 	"void glRasterPos3s(GLshort x, GLshort y, GLshort z);"
2198 	<cdecl: void 'glRasterPos3s' (short short short) module: 'OpenGL'>
2199 	^self externalCallFailed! !
2200 
2201 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2202 glRasterPos3sv: v
2203 	"This method was automatically generated."
2204 	"void glRasterPos3sv(GLshort* v);"
2205 	<cdecl: void 'glRasterPos3sv' (short*) module: 'OpenGL'>
2206 	^self externalCallFailed! !
2207 
2208 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2209 glRasterPos4d: x with: y with: z with: w
2210 	"This method was automatically generated."
2211 	"void glRasterPos4d(GLdouble x, GLdouble y, GLdouble z, GLdouble w);"
2212 	<cdecl: void 'glRasterPos4d' (double double double double) module: 'OpenGL'>
2213 	^self externalCallFailed! !
2214 
2215 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2216 glRasterPos4dv: v
2217 	"This method was automatically generated."
2218 	"void glRasterPos4dv(GLdouble* v);"
2219 	<cdecl: void 'glRasterPos4dv' (double*) module: 'OpenGL'>
2220 	^self externalCallFailed! !
2221 
2222 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2223 glRasterPos4f: x with: y with: z with: w
2224 	"This method was automatically generated."
2225 	"void glRasterPos4f(GLfloat x, GLfloat y, GLfloat z, GLfloat w);"
2226 	<cdecl: void 'glRasterPos4f' (float float float float) module: 'OpenGL'>
2227 	^self externalCallFailed! !
2228 
2229 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2230 glRasterPos4fv: v
2231 	"This method was automatically generated."
2232 	"void glRasterPos4fv(GLfloat* v);"
2233 	<cdecl: void 'glRasterPos4fv' (float*) module: 'OpenGL'>
2234 	^self externalCallFailed! !
2235 
2236 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2237 glRasterPos4i: x with: y with: z with: w
2238 	"This method was automatically generated."
2239 	"void glRasterPos4i(GLint x, GLint y, GLint z, GLint w);"
2240 	<cdecl: void 'glRasterPos4i' (long long long long) module: 'OpenGL'>
2241 	^self externalCallFailed! !
2242 
2243 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2244 glRasterPos4iv: v
2245 	"This method was automatically generated."
2246 	"void glRasterPos4iv(GLint* v);"
2247 	<cdecl: void 'glRasterPos4iv' (long*) module: 'OpenGL'>
2248 	^self externalCallFailed! !
2249 
2250 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2251 glRasterPos4s: x with: y with: z with: w
2252 	"This method was automatically generated."
2253 	"void glRasterPos4s(GLshort x, GLshort y, GLshort z, GLshort w);"
2254 	<cdecl: void 'glRasterPos4s' (short short short short) module: 'OpenGL'>
2255 	^self externalCallFailed! !
2256 
2257 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2258 glRasterPos4sv: v
2259 	"This method was automatically generated."
2260 	"void glRasterPos4sv(GLshort* v);"
2261 	<cdecl: void 'glRasterPos4sv' (short*) module: 'OpenGL'>
2262 	^self externalCallFailed! !
2263 
2264 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2265 glReadBuffer: mode
2266 	"This method was automatically generated."
2267 	"void glReadBuffer(GLenum mode);"
2268 	<cdecl: void 'glReadBuffer' (ulong) module: 'OpenGL'>
2269 	^self externalCallFailed! !
2270 
2271 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2272 glReadPixels: x with: y with: width with: height with: format with: type with: pixels
2273 	"This method was automatically generated."
2274 	"void glReadPixels(GLint x, GLint y, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* pixels);"
2275 	<cdecl: void 'glReadPixels' (long long long long ulong ulong void*) module: 'OpenGL'>
2276 	^self externalCallFailed! !
2277 
2278 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2279 glRectd: x1 with: y1 with: x2 with: y2
2280 	"This method was automatically generated."
2281 	"void glRectd(GLdouble x1, GLdouble y1, GLdouble x2, GLdouble y2);"
2282 	<cdecl: void 'glRectd' (double double double double) module: 'OpenGL'>
2283 	^self externalCallFailed! !
2284 
2285 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2286 glRectdv: v1 with: v2
2287 	"This method was automatically generated."
2288 	"void glRectdv(GLdouble* v1, GLdouble* v2);"
2289 	<cdecl: void 'glRectdv' (double* double*) module: 'OpenGL'>
2290 	^self externalCallFailed! !
2291 
2292 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2293 glRectf: x1 with: y1 with: x2 with: y2
2294 	"This method was automatically generated."
2295 	"void glRectf(GLfloat x1, GLfloat y1, GLfloat x2, GLfloat y2);"
2296 	<cdecl: void 'glRectf' (float float float float) module: 'OpenGL'>
2297 	^self externalCallFailed! !
2298 
2299 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2300 glRectfv: v1 with: v2
2301 	"This method was automatically generated."
2302 	"void glRectfv(GLfloat* v1, GLfloat* v2);"
2303 	<cdecl: void 'glRectfv' (float* float*) module: 'OpenGL'>
2304 	^self externalCallFailed! !
2305 
2306 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2307 glRecti: x1 with: y1 with: x2 with: y2
2308 	"This method was automatically generated."
2309 	"void glRecti(GLint x1, GLint y1, GLint x2, GLint y2);"
2310 	<cdecl: void 'glRecti' (long long long long) module: 'OpenGL'>
2311 	^self externalCallFailed! !
2312 
2313 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2314 glRectiv: v1 with: v2
2315 	"This method was automatically generated."
2316 	"void glRectiv(GLint* v1, GLint* v2);"
2317 	<cdecl: void 'glRectiv' (long* long*) module: 'OpenGL'>
2318 	^self externalCallFailed! !
2319 
2320 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2321 glRects: x1 with: y1 with: x2 with: y2
2322 	"This method was automatically generated."
2323 	"void glRects(GLshort x1, GLshort y1, GLshort x2, GLshort y2);"
2324 	<cdecl: void 'glRects' (short short short short) module: 'OpenGL'>
2325 	^self externalCallFailed! !
2326 
2327 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2328 glRectsv: v1 with: v2
2329 	"This method was automatically generated."
2330 	"void glRectsv(GLshort* v1, GLshort* v2);"
2331 	<cdecl: void 'glRectsv' (short* short*) module: 'OpenGL'>
2332 	^self externalCallFailed! !
2333 
2334 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2335 glRenderMode: mode
2336 	"This method was automatically generated."
2337 	"GLint glRenderMode(GLenum mode);"
2338 	<cdecl: long 'glRenderMode' (ulong) module: 'OpenGL'>
2339 	^self externalCallFailed! !
2340 
2341 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2342 glResetHistogram: target
2343 	"This method was automatically generated."
2344 	"void glResetHistogram(GLenum target);"
2345 	<cdecl: void 'glResetHistogram' (ulong) module: 'OpenGL'>
2346 	^self externalCallFailed! !
2347 
2348 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2349 glResetMinmax: target
2350 	"This method was automatically generated."
2351 	"void glResetMinmax(GLenum target);"
2352 	<cdecl: void 'glResetMinmax' (ulong) module: 'OpenGL'>
2353 	^self externalCallFailed! !
2354 
2355 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2356 glRotated: angle with: x with: y with: z
2357 	"This method was automatically generated."
2358 	"void glRotated(GLdouble angle, GLdouble x, GLdouble y, GLdouble z);"
2359 	<cdecl: void 'glRotated' (double double double double) module: 'OpenGL'>
2360 	^self externalCallFailed! !
2361 
2362 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2363 glRotatef: angle with: x with: y with: z
2364 	"This method was automatically generated."
2365 	"void glRotatef(GLfloat angle, GLfloat x, GLfloat y, GLfloat z);"
2366 	<cdecl: void 'glRotatef' (float float float float) module: 'OpenGL'>
2367 	^self externalCallFailed! !
2368 
2369 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2370 glScaled: x with: y with: z
2371 	"This method was automatically generated."
2372 	"void glScaled(GLdouble x, GLdouble y, GLdouble z);"
2373 	<cdecl: void 'glScaled' (double double double) module: 'OpenGL'>
2374 	^self externalCallFailed! !
2375 
2376 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2377 glScalef: x with: y with: z
2378 	"This method was automatically generated."
2379 	"void glScalef(GLfloat x, GLfloat y, GLfloat z);"
2380 	<cdecl: void 'glScalef' (float float float) module: 'OpenGL'>
2381 	^self externalCallFailed! !
2382 
2383 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2384 glScissor: x with: y with: width with: height
2385 	"This method was automatically generated."
2386 	"void glScissor(GLint x, GLint y, GLsizei width, GLsizei height);"
2387 	<cdecl: void 'glScissor' (long long long long) module: 'OpenGL'>
2388 	^self externalCallFailed! !
2389 
2390 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2391 glSelectBuffer: size with: buffer
2392 	"This method was automatically generated."
2393 	"void glSelectBuffer(GLsizei size, GLuint* buffer);"
2394 	<cdecl: void 'glSelectBuffer' (long ulong*) module: 'OpenGL'>
2395 	^self externalCallFailed! !
2396 
2397 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2398 glSeparableFilter2D: targt with: internalformat with: width with: height with: format with: type with: row with: column
2399 	"This method was automatically generated."
2400 	"void glSeparableFilter2D(GLenum target, GLenum internalformat, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* row, GLvoid* column);"
2401 	<cdecl: void 'glSeparableFilter2D' (ulong ulong long long ulong ulong void* void*) module: 'OpenGL'>
2402 	^self externalCallFailed! !
2403 
2404 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2405 glShadeModel: mode
2406 	"This method was automatically generated."
2407 	"void glShadeModel(GLenum mode);"
2408 	<cdecl: void 'glShadeModel' (ulong) module: 'OpenGL'>
2409 	^self externalCallFailed! !
2410 
2411 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2412 glStencilFunc: func with: ref with: mask
2413 	"This method was automatically generated."
2414 	"void glStencilFunc(GLenum func, GLint ref, GLuint mask);"
2415 	<cdecl: void 'glStencilFunc' (ulong long ulong) module: 'OpenGL'>
2416 	^self externalCallFailed! !
2417 
2418 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2419 glStencilMask: mask
2420 	"This method was automatically generated."
2421 	"void glStencilMask(GLuint mask);"
2422 	<cdecl: void 'glStencilMask' (ulong) module: 'OpenGL'>
2423 	^self externalCallFailed! !
2424 
2425 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2426 glStencilOp: fail with: zfail with: zpass
2427 	"This method was automatically generated."
2428 	"void glStencilOp(GLenum fail, GLenum zfail, GLenum zpass);"
2429 	<cdecl: void 'glStencilOp' (ulong ulong ulong) module: 'OpenGL'>
2430 	^self externalCallFailed! !
2431 
2432 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2433 glTexCoord1d: s
2434 	"This method was automatically generated."
2435 	"void glTexCoord1d(GLdouble s);"
2436 	<cdecl: void 'glTexCoord1d' (double) module: 'OpenGL'>
2437 	^self externalCallFailed! !
2438 
2439 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2440 glTexCoord1dv: v
2441 	"This method was automatically generated."
2442 	"void glTexCoord1dv(GLdouble* v);"
2443 	<cdecl: void 'glTexCoord1dv' (double*) module: 'OpenGL'>
2444 	^self externalCallFailed! !
2445 
2446 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2447 glTexCoord1f: s
2448 	"This method was automatically generated."
2449 	"void glTexCoord1f(GLfloat s);"
2450 	<cdecl: void 'glTexCoord1f' (float) module: 'OpenGL'>
2451 	^self externalCallFailed! !
2452 
2453 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2454 glTexCoord1fv: v
2455 	"This method was automatically generated."
2456 	"void glTexCoord1fv(GLfloat* v);"
2457 	<cdecl: void 'glTexCoord1fv' (float*) module: 'OpenGL'>
2458 	^self externalCallFailed! !
2459 
2460 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2461 glTexCoord1i: s
2462 	"This method was automatically generated."
2463 	"void glTexCoord1i(GLint s);"
2464 	<cdecl: void 'glTexCoord1i' (long) module: 'OpenGL'>
2465 	^self externalCallFailed! !
2466 
2467 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2468 glTexCoord1iv: v
2469 	"This method was automatically generated."
2470 	"void glTexCoord1iv(GLint* v);"
2471 	<cdecl: void 'glTexCoord1iv' (long*) module: 'OpenGL'>
2472 	^self externalCallFailed! !
2473 
2474 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2475 glTexCoord1s: s
2476 	"This method was automatically generated."
2477 	"void glTexCoord1s(GLshort s);"
2478 	<cdecl: void 'glTexCoord1s' (short) module: 'OpenGL'>
2479 	^self externalCallFailed! !
2480 
2481 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2482 glTexCoord1sv: v
2483 	"This method was automatically generated."
2484 	"void glTexCoord1sv(GLshort* v);"
2485 	<cdecl: void 'glTexCoord1sv' (short*) module: 'OpenGL'>
2486 	^self externalCallFailed! !
2487 
2488 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2489 glTexCoord2d: s with: t
2490 	"This method was automatically generated."
2491 	"void glTexCoord2d(GLdouble s, GLdouble t);"
2492 	<cdecl: void 'glTexCoord2d' (double double) module: 'OpenGL'>
2493 	^self externalCallFailed! !
2494 
2495 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2496 glTexCoord2dv: v
2497 	"This method was automatically generated."
2498 	"void glTexCoord2dv(GLdouble* v);"
2499 	<cdecl: void 'glTexCoord2dv' (double*) module: 'OpenGL'>
2500 	^self externalCallFailed! !
2501 
2502 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2503 glTexCoord2f: s with: t
2504 	"This method was automatically generated."
2505 	"void glTexCoord2f(GLfloat s, GLfloat t);"
2506 	<cdecl: void 'glTexCoord2f' (float float) module: 'OpenGL'>
2507 	^self externalCallFailed! !
2508 
2509 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2510 glTexCoord2fv: v
2511 	"This method was automatically generated."
2512 	"void glTexCoord2fv(GLfloat* v);"
2513 	<cdecl: void 'glTexCoord2fv' (float*) module: 'OpenGL'>
2514 	^self externalCallFailed! !
2515 
2516 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2517 glTexCoord2i: s with: t
2518 	"This method was automatically generated."
2519 	"void glTexCoord2i(GLint s, GLint t);"
2520 	<cdecl: void 'glTexCoord2i' (long long) module: 'OpenGL'>
2521 	^self externalCallFailed! !
2522 
2523 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2524 glTexCoord2iv: v
2525 	"This method was automatically generated."
2526 	"void glTexCoord2iv(GLint* v);"
2527 	<cdecl: void 'glTexCoord2iv' (long*) module: 'OpenGL'>
2528 	^self externalCallFailed! !
2529 
2530 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2531 glTexCoord2s: s with: t
2532 	"This method was automatically generated."
2533 	"void glTexCoord2s(GLshort s, GLshort t);"
2534 	<cdecl: void 'glTexCoord2s' (short short) module: 'OpenGL'>
2535 	^self externalCallFailed! !
2536 
2537 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2538 glTexCoord2sv: v
2539 	"This method was automatically generated."
2540 	"void glTexCoord2sv(GLshort* v);"
2541 	<cdecl: void 'glTexCoord2sv' (short*) module: 'OpenGL'>
2542 	^self externalCallFailed! !
2543 
2544 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2545 glTexCoord3d: s with: t with: r
2546 	"This method was automatically generated."
2547 	"void glTexCoord3d(GLdouble s, GLdouble t, GLdouble r);"
2548 	<cdecl: void 'glTexCoord3d' (double double double) module: 'OpenGL'>
2549 	^self externalCallFailed! !
2550 
2551 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2552 glTexCoord3dv: v
2553 	"This method was automatically generated."
2554 	"void glTexCoord3dv(GLdouble* v);"
2555 	<cdecl: void 'glTexCoord3dv' (double*) module: 'OpenGL'>
2556 	^self externalCallFailed! !
2557 
2558 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2559 glTexCoord3f: s with: t with: r
2560 	"This method was automatically generated."
2561 	"void glTexCoord3f(GLfloat s, GLfloat t, GLfloat r);"
2562 	<cdecl: void 'glTexCoord3f' (float float float) module: 'OpenGL'>
2563 	^self externalCallFailed! !
2564 
2565 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2566 glTexCoord3fv: v
2567 	"This method was automatically generated."
2568 	"void glTexCoord3fv(GLfloat* v);"
2569 	<cdecl: void 'glTexCoord3fv' (float*) module: 'OpenGL'>
2570 	^self externalCallFailed! !
2571 
2572 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2573 glTexCoord3i: s with: t with: r
2574 	"This method was automatically generated."
2575 	"void glTexCoord3i(GLint s, GLint t, GLint r);"
2576 	<cdecl: void 'glTexCoord3i' (long long long) module: 'OpenGL'>
2577 	^self externalCallFailed! !
2578 
2579 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2580 glTexCoord3iv: v
2581 	"This method was automatically generated."
2582 	"void glTexCoord3iv(GLint* v);"
2583 	<cdecl: void 'glTexCoord3iv' (long*) module: 'OpenGL'>
2584 	^self externalCallFailed! !
2585 
2586 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2587 glTexCoord3s: s with: t with: r
2588 	"This method was automatically generated."
2589 	"void glTexCoord3s(GLshort s, GLshort t, GLshort r);"
2590 	<cdecl: void 'glTexCoord3s' (short short short) module: 'OpenGL'>
2591 	^self externalCallFailed! !
2592 
2593 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2594 glTexCoord3sv: v
2595 	"This method was automatically generated."
2596 	"void glTexCoord3sv(GLshort* v);"
2597 	<cdecl: void 'glTexCoord3sv' (short*) module: 'OpenGL'>
2598 	^self externalCallFailed! !
2599 
2600 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2601 glTexCoord4d: s with: t with: r with: q
2602 	"This method was automatically generated."
2603 	"void glTexCoord4d(GLdouble s, GLdouble t, GLdouble r, GLdouble q);"
2604 	<cdecl: void 'glTexCoord4d' (double double double double) module: 'OpenGL'>
2605 	^self externalCallFailed! !
2606 
2607 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2608 glTexCoord4dv: v
2609 	"This method was automatically generated."
2610 	"void glTexCoord4dv(GLdouble* v);"
2611 	<cdecl: void 'glTexCoord4dv' (double*) module: 'OpenGL'>
2612 	^self externalCallFailed! !
2613 
2614 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2615 glTexCoord4f: s with: t with: r with: q
2616 	"This method was automatically generated."
2617 	"void glTexCoord4f(GLfloat s, GLfloat t, GLfloat r, GLfloat q);"
2618 	<cdecl: void 'glTexCoord4f' (float float float float) module: 'OpenGL'>
2619 	^self externalCallFailed! !
2620 
2621 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2622 glTexCoord4fv: v
2623 	"This method was automatically generated."
2624 	"void glTexCoord4fv(GLfloat* v);"
2625 	<cdecl: void 'glTexCoord4fv' (float*) module: 'OpenGL'>
2626 	^self externalCallFailed! !
2627 
2628 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2629 glTexCoord4i: s with: t with: r with: q
2630 	"This method was automatically generated."
2631 	"void glTexCoord4i(GLint s, GLint t, GLint r, GLint q);"
2632 	<cdecl: void 'glTexCoord4i' (long long long long) module: 'OpenGL'>
2633 	^self externalCallFailed! !
2634 
2635 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2636 glTexCoord4iv: v
2637 	"This method was automatically generated."
2638 	"void glTexCoord4iv(GLint* v);"
2639 	<cdecl: void 'glTexCoord4iv' (long*) module: 'OpenGL'>
2640 	^self externalCallFailed! !
2641 
2642 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2643 glTexCoord4s: s with: t with: r with: q
2644 	"This method was automatically generated."
2645 	"void glTexCoord4s(GLshort s, GLshort t, GLshort r, GLshort q);"
2646 	<cdecl: void 'glTexCoord4s' (short short short short) module: 'OpenGL'>
2647 	^self externalCallFailed! !
2648 
2649 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2650 glTexCoord4sv: v
2651 	"This method was automatically generated."
2652 	"void glTexCoord4sv(GLshort* v);"
2653 	<cdecl: void 'glTexCoord4sv' (short*) module: 'OpenGL'>
2654 	^self externalCallFailed! !
2655 
2656 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2657 glTexCoordPointer: size with: type with: stride with: pointer
2658 	"This method was automatically generated."
2659 	"void glTexCoordPointer(GLint size, GLenum type, GLsizei stride, GLvoid* pointer);"
2660 	<cdecl: void 'glTexCoordPointer' (long ulong long void*) module: 'OpenGL'>
2661 	^self externalCallFailed! !
2662 
2663 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2664 glTexCoordPointerEXT: size with: type with: stride with: count with: pointer
2665 	"This method was automatically generated."
2666 	"void glTexCoordPointerEXT(GLint size, GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
2667 	<cdecl: void 'glTexCoordPointerEXT' (long ulong long long void*) module: 'OpenGL'>
2668 	^self externalCallFailed! !
2669 
2670 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2671 glTexEnvf: targt with: pname with: param
2672 	"This method was automatically generated."
2673 	"void glTexEnvf(GLenum target, GLenum pname, GLfloat param);"
2674 	<cdecl: void 'glTexEnvf' (ulong ulong float) module: 'OpenGL'>
2675 	^self externalCallFailed! !
2676 
2677 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2678 glTexEnvfv: targt with: pname with: params
2679 	"This method was automatically generated."
2680 	"void glTexEnvfv(GLenum target, GLenum pname, GLfloat* params);"
2681 	<cdecl: void 'glTexEnvfv' (ulong ulong float*) module: 'OpenGL'>
2682 	^self externalCallFailed! !
2683 
2684 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2685 glTexEnvi: targt with: pname with: param
2686 	"This method was automatically generated."
2687 	"void glTexEnvi(GLenum target, GLenum pname, GLint param);"
2688 	<cdecl: void 'glTexEnvi' (ulong ulong long) module: 'OpenGL'>
2689 	^self externalCallFailed! !
2690 
2691 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2692 glTexEnviv: targt with: pname with: params
2693 	"This method was automatically generated."
2694 	"void glTexEnviv(GLenum target, GLenum pname, GLint* params);"
2695 	<cdecl: void 'glTexEnviv' (ulong ulong long*) module: 'OpenGL'>
2696 	^self externalCallFailed! !
2697 
2698 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2699 glTexGend: coord with: pname with: param
2700 	"This method was automatically generated."
2701 	"void glTexGend(GLenum coord, GLenum pname, GLdouble param);"
2702 	<cdecl: void 'glTexGend' (ulong ulong double) module: 'OpenGL'>
2703 	^self externalCallFailed! !
2704 
2705 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2706 glTexGendv: coord with: pname with: params
2707 	"This method was automatically generated."
2708 	"void glTexGendv(GLenum coord, GLenum pname, GLdouble* params);"
2709 	<cdecl: void 'glTexGendv' (ulong ulong double*) module: 'OpenGL'>
2710 	^self externalCallFailed! !
2711 
2712 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2713 glTexGenf: coord with: pname with: param
2714 	"This method was automatically generated."
2715 	"void glTexGenf(GLenum coord, GLenum pname, GLfloat param);"
2716 	<cdecl: void 'glTexGenf' (ulong ulong float) module: 'OpenGL'>
2717 	^self externalCallFailed! !
2718 
2719 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2720 glTexGenfv: coord with: pname with: params
2721 	"This method was automatically generated."
2722 	"void glTexGenfv(GLenum coord, GLenum pname, GLfloat* params);"
2723 	<cdecl: void 'glTexGenfv' (ulong ulong float*) module: 'OpenGL'>
2724 	^self externalCallFailed! !
2725 
2726 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2727 glTexGeni: coord with: pname with: param
2728 	"This method was automatically generated."
2729 	"void glTexGeni(GLenum coord, GLenum pname, GLint param);"
2730 	<cdecl: void 'glTexGeni' (ulong ulong long) module: 'OpenGL'>
2731 	^self externalCallFailed! !
2732 
2733 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2734 glTexGeniv: coord with: pname with: params
2735 	"This method was automatically generated."
2736 	"void glTexGeniv(GLenum coord, GLenum pname, GLint* params);"
2737 	<cdecl: void 'glTexGeniv' (ulong ulong long*) module: 'OpenGL'>
2738 	^self externalCallFailed! !
2739 
2740 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2741 glTexImage1D: targt with: level with: internalformat with: width with: border with: format with: type with: pixels
2742 	"This method was automatically generated."
2743 	"void glTexImage1D(GLenum target, GLint level, GLint internalformat, GLsizei width, GLint border, GLenum format, GLenum type, GLvoid* pixels);"
2744 	<cdecl: void 'glTexImage1D' (ulong long long long long ulong ulong void*) module: 'OpenGL'>
2745 	^self externalCallFailed! !
2746 
2747 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2748 glTexImage2D: targt with: level with: internalformat with: width with: height with: border with: format with: type with: pixels
2749 	"This method was automatically generated."
2750 	"void glTexImage2D(GLenum target, GLint level, GLint internalformat, GLsizei width, GLsizei height, GLint border, GLenum format, GLenum type, GLvoid* pixels);"
2751 	<cdecl: void 'glTexImage2D' (ulong long long long long long ulong ulong void*) module: 'OpenGL'>
2752 	^self externalCallFailed! !
2753 
2754 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2755 glTexImage3D: targt with: level with: internalformat with: width with: height with: depth with: border with: format with: type with: pixels
2756 	"This method was automatically generated."
2757 	"void glTexImage3D(GLenum target, GLint level, GLenum internalformat, GLsizei width, GLsizei height, GLsizei depth, GLint border, GLenum format, GLenum type, GLvoid* pixels);"
2758 	<cdecl: void 'glTexImage3D' (ulong long ulong long long long long ulong ulong void*) module: 'OpenGL'>
2759 	^self externalCallFailed! !
2760 
2761 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2762 glTexParameterf: targt with: pname with: param
2763 	"This method was automatically generated."
2764 	"void glTexParameterf(GLenum target, GLenum pname, GLfloat param);"
2765 	<cdecl: void 'glTexParameterf' (ulong ulong float) module: 'OpenGL'>
2766 	^self externalCallFailed! !
2767 
2768 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2769 glTexParameterfv: targt with: pname with: params
2770 	"This method was automatically generated."
2771 	"void glTexParameterfv(GLenum target, GLenum pname, GLfloat* params);"
2772 	<cdecl: void 'glTexParameterfv' (ulong ulong float*) module: 'OpenGL'>
2773 	^self externalCallFailed! !
2774 
2775 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2776 glTexParameteri: targt with: pname with: param
2777 	"This method was automatically generated."
2778 	"void glTexParameteri(GLenum target, GLenum pname, GLint param);"
2779 	<cdecl: void 'glTexParameteri' (ulong ulong long) module: 'OpenGL'>
2780 	^self externalCallFailed! !
2781 
2782 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2783 glTexParameteriv: targt with: pname with: params
2784 	"This method was automatically generated."
2785 	"void glTexParameteriv(GLenum target, GLenum pname, GLint* params);"
2786 	<cdecl: void 'glTexParameteriv' (ulong ulong long*) module: 'OpenGL'>
2787 	^self externalCallFailed! !
2788 
2789 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2790 glTexSubImage1D: targt with: level with: xoffset with: width with: format with: type with: pixels
2791 	"This method was automatically generated."
2792 	"void glTexSubImage1D(GLenum target, GLint level, GLint xoffset, GLsizei width, GLenum format, GLenum type, GLvoid* pixels);"
2793 	<cdecl: void 'glTexSubImage1D' (ulong long long long ulong ulong void*) module: 'OpenGL'>
2794 	^self externalCallFailed! !
2795 
2796 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2797 glTexSubImage2D: targt with: level with: xoffset with: yoffset with: width with: height with: format with: type with: pixels
2798 	"This method was automatically generated."
2799 	"void glTexSubImage2D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* pixels);"
2800 	<cdecl: void 'glTexSubImage2D' (ulong long long long long long ulong ulong void*) module: 'OpenGL'>
2801 	^self externalCallFailed! !
2802 
2803 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2804 glTexSubImage3D: targt with: level with: xoffset with: yoffset with: zoffset with: width with: height with: depth with: format with: type with: pixels
2805 	"This method was automatically generated."
2806 	"void glTexSubImage3D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLint zoffset, GLsizei width, GLsizei height, GLsizei depth, GLenum format, GLenum type, GLvoid* pixels);"
2807 	<cdecl: void 'glTexSubImage3D' (ulong long long long long long long long ulong ulong void*) module: 'OpenGL'>
2808 	^self externalCallFailed! !
2809 
2810 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2811 glTranslated: x with: y with: z
2812 	"This method was automatically generated."
2813 	"void glTranslated(GLdouble x, GLdouble y, GLdouble z);"
2814 	<cdecl: void 'glTranslated' (double double double) module: 'OpenGL'>
2815 	^self externalCallFailed! !
2816 
2817 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2818 glTranslatef: x with: y with: z
2819 	"This method was automatically generated."
2820 	"void glTranslatef(GLfloat x, GLfloat y, GLfloat z);"
2821 	<cdecl: void 'glTranslatef' (float float float) module: 'OpenGL'>
2822 	^self externalCallFailed! !
2823 
2824 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2825 glUnlockArraysEXT
2826 	"This method was automatically generated."
2827 	"void glUnlockArraysEXT();"
2828 	<cdecl: void 'glUnlockArraysEXT' (void) module: 'OpenGL'>
2829 	^self externalCallFailed! !
2830 
2831 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2832 glVertex2d: x with: y
2833 	"This method was automatically generated."
2834 	"void glVertex2d(GLdouble x, GLdouble y);"
2835 	<cdecl: void 'glVertex2d' (double double) module: 'OpenGL'>
2836 	^self externalCallFailed! !
2837 
2838 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2839 glVertex2dv: v
2840 	"This method was automatically generated."
2841 	"void glVertex2dv(GLdouble* v);"
2842 	<cdecl: void 'glVertex2dv' (double*) module: 'OpenGL'>
2843 	^self externalCallFailed! !
2844 
2845 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2846 glVertex2f: x with: y
2847 	"This method was automatically generated."
2848 	"void glVertex2f(GLfloat x, GLfloat y);"
2849 	<cdecl: void 'glVertex2f' (float float) module: 'OpenGL'>
2850 	^self externalCallFailed! !
2851 
2852 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2853 glVertex2fv: v
2854 	"This method was automatically generated."
2855 	"void glVertex2fv(GLfloat* v);"
2856 	<cdecl: void 'glVertex2fv' (float*) module: 'OpenGL'>
2857 	^self externalCallFailed! !
2858 
2859 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2860 glVertex2i: x with: y
2861 	"This method was automatically generated."
2862 	"void glVertex2i(GLint x, GLint y);"
2863 	<cdecl: void 'glVertex2i' (long long) module: 'OpenGL'>
2864 	^self externalCallFailed! !
2865 
2866 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2867 glVertex2iv: v
2868 	"This method was automatically generated."
2869 	"void glVertex2iv(GLint* v);"
2870 	<cdecl: void 'glVertex2iv' (long*) module: 'OpenGL'>
2871 	^self externalCallFailed! !
2872 
2873 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2874 glVertex2s: x with: y
2875 	"This method was automatically generated."
2876 	"void glVertex2s(GLshort x, GLshort y);"
2877 	<cdecl: void 'glVertex2s' (short short) module: 'OpenGL'>
2878 	^self externalCallFailed! !
2879 
2880 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2881 glVertex2sv: v
2882 	"This method was automatically generated."
2883 	"void glVertex2sv(GLshort* v);"
2884 	<cdecl: void 'glVertex2sv' (short*) module: 'OpenGL'>
2885 	^self externalCallFailed! !
2886 
2887 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2888 glVertex3d: x with: y with: z
2889 	"This method was automatically generated."
2890 	"void glVertex3d(GLdouble x, GLdouble y, GLdouble z);"
2891 	<cdecl: void 'glVertex3d' (double double double) module: 'OpenGL'>
2892 	^self externalCallFailed! !
2893 
2894 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2895 glVertex3dv: v
2896 	"This method was automatically generated."
2897 	"void glVertex3dv(GLdouble* v);"
2898 	<cdecl: void 'glVertex3dv' (double*) module: 'OpenGL'>
2899 	^self externalCallFailed! !
2900 
2901 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2902 glVertex3f: x with: y with: z
2903 	"This method was automatically generated."
2904 	"void glVertex3f(GLfloat x, GLfloat y, GLfloat z);"
2905 	<cdecl: void 'glVertex3f' (float float float) module: 'OpenGL'>
2906 	^self externalCallFailed! !
2907 
2908 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2909 glVertex3fv: v
2910 	"This method was automatically generated."
2911 	"void glVertex3fv(GLfloat* v);"
2912 	<cdecl: void 'glVertex3fv' (float*) module: 'OpenGL'>
2913 	^self externalCallFailed! !
2914 
2915 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2916 glVertex3i: x with: y with: z
2917 	"This method was automatically generated."
2918 	"void glVertex3i(GLint x, GLint y, GLint z);"
2919 	<cdecl: void 'glVertex3i' (long long long) module: 'OpenGL'>
2920 	^self externalCallFailed! !
2921 
2922 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2923 glVertex3iv: v
2924 	"This method was automatically generated."
2925 	"void glVertex3iv(GLint* v);"
2926 	<cdecl: void 'glVertex3iv' (long*) module: 'OpenGL'>
2927 	^self externalCallFailed! !
2928 
2929 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2930 glVertex3s: x with: y with: z
2931 	"This method was automatically generated."
2932 	"void glVertex3s(GLshort x, GLshort y, GLshort z);"
2933 	<cdecl: void 'glVertex3s' (short short short) module: 'OpenGL'>
2934 	^self externalCallFailed! !
2935 
2936 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2937 glVertex3sv: v
2938 	"This method was automatically generated."
2939 	"void glVertex3sv(GLshort* v);"
2940 	<cdecl: void 'glVertex3sv' (short*) module: 'OpenGL'>
2941 	^self externalCallFailed! !
2942 
2943 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2944 glVertex4d: x with: y with: z with: w
2945 	"This method was automatically generated."
2946 	"void glVertex4d(GLdouble x, GLdouble y, GLdouble z, GLdouble w);"
2947 	<cdecl: void 'glVertex4d' (double double double double) module: 'OpenGL'>
2948 	^self externalCallFailed! !
2949 
2950 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2951 glVertex4dv: v
2952 	"This method was automatically generated."
2953 	"void glVertex4dv(GLdouble* v);"
2954 	<cdecl: void 'glVertex4dv' (double*) module: 'OpenGL'>
2955 	^self externalCallFailed! !
2956 
2957 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2958 glVertex4f: x with: y with: z with: w
2959 	"This method was automatically generated."
2960 	"void glVertex4f(GLfloat x, GLfloat y, GLfloat z, GLfloat w);"
2961 	<cdecl: void 'glVertex4f' (float float float float) module: 'OpenGL'>
2962 	^self externalCallFailed! !
2963 
2964 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2965 glVertex4fv: v
2966 	"This method was automatically generated."
2967 	"void glVertex4fv(GLfloat* v);"
2968 	<cdecl: void 'glVertex4fv' (float*) module: 'OpenGL'>
2969 	^self externalCallFailed! !
2970 
2971 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2972 glVertex4i: x with: y with: z with: w
2973 	"This method was automatically generated."
2974 	"void glVertex4i(GLint x, GLint y, GLint z, GLint w);"
2975 	<cdecl: void 'glVertex4i' (long long long long) module: 'OpenGL'>
2976 	^self externalCallFailed! !
2977 
2978 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2979 glVertex4iv: v
2980 	"This method was automatically generated."
2981 	"void glVertex4iv(GLint* v);"
2982 	<cdecl: void 'glVertex4iv' (long*) module: 'OpenGL'>
2983 	^self externalCallFailed! !
2984 
2985 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2986 glVertex4s: x with: y with: z with: w
2987 	"This method was automatically generated."
2988 	"void glVertex4s(GLshort x, GLshort y, GLshort z, GLshort w);"
2989 	<cdecl: void 'glVertex4s' (short short short short) module: 'OpenGL'>
2990 	^self externalCallFailed! !
2991 
2992 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
2993 glVertex4sv: v
2994 	"This method was automatically generated."
2995 	"void glVertex4sv(GLshort* v);"
2996 	<cdecl: void 'glVertex4sv' (short*) module: 'OpenGL'>
2997 	^self externalCallFailed! !
2998 
2999 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
3000 glVertexPointer: size with: type with: stride with: pointer
3001 	"This method was automatically generated."
3002 	"void glVertexPointer(GLint size, GLenum type, GLsizei stride, GLvoid* pointer);"
3003 	<cdecl: void 'glVertexPointer' (long ulong long void*) module: 'OpenGL'>
3004 	^self externalCallFailed! !
3005 
3006 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
3007 glVertexPointerEXT: size with: type with: stride with: count with: pointer
3008 	"This method was automatically generated."
3009 	"void glVertexPointerEXT(GLint size, GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
3010 	<cdecl: void 'glVertexPointerEXT' (long ulong long long void*) module: 'OpenGL'>
3011 	^self externalCallFailed! !
3012 
3013 !GLXUnixQuartz methodsFor: 'OpenGL API' stamp: 'ikp 1/7/2003 21:14'!
3014 glViewport: x with: y with: width with: height
3015 	"This method was automatically generated."
3016 	"void glViewport(GLint x, GLint y, GLsizei width, GLsizei height);"
3017 	<cdecl: void 'glViewport' (long long long long) module: 'OpenGL'>
3018 	^self externalCallFailed! !
3019 
3020 
3021 !GLXUnixQuartz class methodsFor: 'as yet unclassified' stamp: 'ikp 1/16/2003 05:38'!
3022 test
3023 	"GLXUnixOSX test"
3024 
3025 	<cdecl: void 'ffiTest2' (long long) module: 'B3DAcceleratorPlugin'>
3026 	^self error: 'test failed'! !
3027 
3028 !GLXUnixQuartz class methodsFor: 'as yet unclassified' stamp: 'ikp 1/16/2003 05:39'!
3029 test: x with: y
3030 	"GLXUnixOSX test: 6 with: 7"
3031 
3032 	<cdecl: void 'ffiTest2' (long long) module: 'B3DAcceleratorPlugin'>
3033 	^self error: 'test failed'! !
3034 
3035 
3036 !GLXUnixX11BE methodsFor: 'accessing' stamp: 'bf 10/21/2002 19:10'!
3037 imagePixelFormat32
3038 	^GLBgra! !
3039 
3040 !GLXUnixX11BE methodsFor: 'accessing' stamp: 'ikp 2/3/2003 17:01'!
3041 imagePixelType32
3042 	^GLUnsignedInt8888Rev! !
3043 
3044 !GLXUnixX11BE methodsFor: 'accessing' stamp: 'bf 10/21/2002 19:15'!
3045 textureInternalFormat
3046 	^GLRgba! !
3047 
3048 !GLXUnixX11BE methodsFor: 'accessing' stamp: 'bf 10/21/2002 19:09'!
3049 texturePixelFormat
3050 	^GLBgra! !
3051 
3052 !GLXUnixX11BE methodsFor: 'accessing' stamp: 'ikp 2/3/2003 17:02'!
3053 texturePixelType
3054 	^GLUnsignedInt8888Rev! !
3055 
3056 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3057 glAccum: op with: value
3058 	"This method was automatically generated."
3059 	"void glAccum(GLenum op, GLfloat value);"
3060 	<cdecl: void 'glAccum' (ulong float) module: 'GL'>
3061 	^self externalCallFailed! !
3062 
3063 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3064 glActiveTextureARB: texture
3065 	"This method was automatically generated."
3066 	"void glActiveTextureARB(GLenum texture);"
3067 	<cdecl: void 'glActiveTextureARB' (ulong) module: 'GL'>
3068 	^self externalCallFailed! !
3069 
3070 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3071 glAlphaFunc: func with: ref
3072 	"This method was automatically generated."
3073 	"void glAlphaFunc(GLenum func, GLclampf ref);"
3074 	<cdecl: void 'glAlphaFunc' (ulong float) module: 'GL'>
3075 	^self externalCallFailed! !
3076 
3077 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3078 glAreTexturesResident: n with: textures with: residences
3079 	"This method was automatically generated."
3080 	"GLboolean glAreTexturesResident(GLsizei n, GLuint* textures, GLboolean* residences);"
3081 	<cdecl: bool 'glAreTexturesResident' (long ulong* ulong*) module: 'GL'>
3082 	^self externalCallFailed! !
3083 
3084 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3085 glAreTexturesResidentEXT: n with: textures with: residences
3086 	"This method was automatically generated."
3087 	"GLboolean glAreTexturesResidentEXT(GLsizei n, GLuint* textures, GLboolean* residences);"
3088 	<cdecl: bool 'glAreTexturesResidentEXT' (long ulong* ulong*) module: 'GL'>
3089 	^self externalCallFailed! !
3090 
3091 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3092 glArrayElement: i
3093 	"This method was automatically generated."
3094 	"void glArrayElement(GLint i);"
3095 	<cdecl: void 'glArrayElement' (long) module: 'GL'>
3096 	^self externalCallFailed! !
3097 
3098 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3099 glArrayElementEXT: i
3100 	"This method was automatically generated."
3101 	"void glArrayElementEXT(GLint i);"
3102 	<cdecl: void 'glArrayElementEXT' (long) module: 'GL'>
3103 	^self externalCallFailed! !
3104 
3105 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3106 glBegin: mode
3107 	"This method was automatically generated."
3108 	"void glBegin(GLenum mode);"
3109 	<cdecl: void 'glBegin' (ulong) module: 'GL'>
3110 	^self externalCallFailed! !
3111 
3112 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3113 glBindTexture: target with: texture
3114 	"This method was automatically generated."
3115 	"void glBindTexture(GLenum target, GLuint texture);"
3116 	<cdecl: void 'glBindTexture' (ulong ulong) module: 'GL'>
3117 	^self externalCallFailed! !
3118 
3119 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3120 glBitmap: width with: height with: xorig with: yorig with: xmove with: ymove with: bitmap
3121 	"This method was automatically generated."
3122 	"void glBitmap(GLsizei width, GLsizei height, GLfloat xorig, GLfloat yorig, GLfloat xmove, GLfloat ymove, GLubyte* bitmap);"
3123 	<cdecl: void 'glBitmap' (long long float float float float void*) module: 'GL'>
3124 	^self externalCallFailed! !
3125 
3126 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3127 glBlendColor: red with: green with: blue with: alpha
3128 	"This method was automatically generated."
3129 	"void glBlendColor(GLclampf red, GLclampf green, GLclampf blue, GLclampf alpha);"
3130 	<cdecl: void 'glBlendColor' (float float float float) module: 'GL'>
3131 	^self externalCallFailed! !
3132 
3133 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3134 glBlendEquation: mode
3135 	"This method was automatically generated."
3136 	"void glBlendEquation(GLenum mode);"
3137 	<cdecl: void 'glBlendEquation' (ulong) module: 'GL'>
3138 	^self externalCallFailed! !
3139 
3140 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3141 glBlendFunc: sfactor with: dfactor
3142 	"This method was automatically generated."
3143 	"void glBlendFunc(GLenum sfactor, GLenum dfactor);"
3144 	<cdecl: void 'glBlendFunc' (ulong ulong) module: 'GL'>
3145 	^self externalCallFailed! !
3146 
3147 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3148 glCallList: list
3149 	"This method was automatically generated."
3150 	"void glCallList(GLuint list);"
3151 	<cdecl: void 'glCallList' (ulong) module: 'GL'>
3152 	^self externalCallFailed! !
3153 
3154 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3155 glCallLists: n with: type with: lists
3156 	"This method was automatically generated."
3157 	"void glCallLists(GLsizei n, GLenum type, GLvoid* lists);"
3158 	<cdecl: void 'glCallLists' (long ulong void*) module: 'GL'>
3159 	^self externalCallFailed! !
3160 
3161 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3162 glClear: mask
3163 	"This method was automatically generated."
3164 	"void glClear(GLbitfield mask);"
3165 	<cdecl: void 'glClear' (ulong) module: 'GL'>
3166 	^self externalCallFailed! !
3167 
3168 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3169 glClearAccum: red with: green with: blue with: alpha
3170 	"This method was automatically generated."
3171 	"void glClearAccum(GLfloat red, GLfloat green, GLfloat blue, GLfloat alpha);"
3172 	<cdecl: void 'glClearAccum' (float float float float) module: 'GL'>
3173 	^self externalCallFailed! !
3174 
3175 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3176 glClearColor: red with: green with: blue with: alpha
3177 	"This method was automatically generated."
3178 	"void glClearColor(GLclampf red, GLclampf green, GLclampf blue, GLclampf alpha);"
3179 	<cdecl: void 'glClearColor' (float float float float) module: 'GL'>
3180 	^self externalCallFailed! !
3181 
3182 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3183 glClearDepth: depth
3184 	"This method was automatically generated."
3185 	"void glClearDepth(GLclampd depth);"
3186 	<cdecl: void 'glClearDepth' (double) module: 'GL'>
3187 	^self externalCallFailed! !
3188 
3189 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3190 glClearIndex: c
3191 	"This method was automatically generated."
3192 	"void glClearIndex(GLfloat c);"
3193 	<cdecl: void 'glClearIndex' (float) module: 'GL'>
3194 	^self externalCallFailed! !
3195 
3196 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3197 glClearStencil: s
3198 	"This method was automatically generated."
3199 	"void glClearStencil(GLint s);"
3200 	<cdecl: void 'glClearStencil' (long) module: 'GL'>
3201 	^self externalCallFailed! !
3202 
3203 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3204 glClientActiveTextureARB: texture
3205 	"This method was automatically generated."
3206 	"void glClientActiveTextureARB(GLenum texture);"
3207 	<cdecl: void 'glClientActiveTextureARB' (ulong) module: 'GL'>
3208 	^self externalCallFailed! !
3209 
3210 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3211 glClipPlane: plane with: equation
3212 	"This method was automatically generated."
3213 	"void glClipPlane(GLenum plane, GLdouble* equation);"
3214 	<cdecl: void 'glClipPlane' (ulong double*) module: 'GL'>
3215 	^self externalCallFailed! !
3216 
3217 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3218 glColor3b: red with: green with: blue
3219 	"This method was automatically generated."
3220 	"void glColor3b(GLbyte red, GLbyte green, GLbyte blue);"
3221 	<cdecl: void 'glColor3b' (byte byte byte) module: 'GL'>
3222 	^self externalCallFailed! !
3223 
3224 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3225 glColor3bv: v
3226 	"This method was automatically generated."
3227 	"void glColor3bv(GLbyte* v);"
3228 	<cdecl: void 'glColor3bv' (byte*) module: 'GL'>
3229 	^self externalCallFailed! !
3230 
3231 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3232 glColor3d: red with: green with: blue
3233 	"This method was automatically generated."
3234 	"void glColor3d(GLdouble red, GLdouble green, GLdouble blue);"
3235 	<cdecl: void 'glColor3d' (double double double) module: 'GL'>
3236 	^self externalCallFailed! !
3237 
3238 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3239 glColor3dv: v
3240 	"This method was automatically generated."
3241 	"void glColor3dv(GLdouble* v);"
3242 	<cdecl: void 'glColor3dv' (double*) module: 'GL'>
3243 	^self externalCallFailed! !
3244 
3245 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3246 glColor3f: red with: green with: blue
3247 	"This method was automatically generated."
3248 	"void glColor3f(GLfloat red, GLfloat green, GLfloat blue);"
3249 	<cdecl: void 'glColor3f' (float float float) module: 'GL'>
3250 	^self externalCallFailed! !
3251 
3252 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3253 glColor3fv: v
3254 	"This method was automatically generated."
3255 	"void glColor3fv(GLfloat* v);"
3256 	<cdecl: void 'glColor3fv' (float*) module: 'GL'>
3257 	^self externalCallFailed! !
3258 
3259 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3260 glColor3i: red with: green with: blue
3261 	"This method was automatically generated."
3262 	"void glColor3i(GLint red, GLint green, GLint blue);"
3263 	<cdecl: void 'glColor3i' (long long long) module: 'GL'>
3264 	^self externalCallFailed! !
3265 
3266 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3267 glColor3iv: v
3268 	"This method was automatically generated."
3269 	"void glColor3iv(GLint* v);"
3270 	<cdecl: void 'glColor3iv' (long*) module: 'GL'>
3271 	^self externalCallFailed! !
3272 
3273 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3274 glColor3s: red with: green with: blue
3275 	"This method was automatically generated."
3276 	"void glColor3s(GLshort red, GLshort green, GLshort blue);"
3277 	<cdecl: void 'glColor3s' (short short short) module: 'GL'>
3278 	^self externalCallFailed! !
3279 
3280 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3281 glColor3sv: v
3282 	"This method was automatically generated."
3283 	"void glColor3sv(GLshort* v);"
3284 	<cdecl: void 'glColor3sv' (short*) module: 'GL'>
3285 	^self externalCallFailed! !
3286 
3287 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3288 glColor3ub: red with: green with: blue
3289 	"This method was automatically generated."
3290 	"void glColor3ub(GLubyte red, GLubyte green, GLubyte blue);"
3291 	<cdecl: void 'glColor3ub' (byte byte byte) module: 'GL'>
3292 	^self externalCallFailed! !
3293 
3294 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3295 glColor3ubv: v
3296 	"This method was automatically generated."
3297 	"void glColor3ubv(GLubyte* v);"
3298 	<cdecl: void 'glColor3ubv' (byte*) module: 'GL'>
3299 	^self externalCallFailed! !
3300 
3301 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3302 glColor3ui: red with: green with: blue
3303 	"This method was automatically generated."
3304 	"void glColor3ui(GLuint red, GLuint green, GLuint blue);"
3305 	<cdecl: void 'glColor3ui' (ulong ulong ulong) module: 'GL'>
3306 	^self externalCallFailed! !
3307 
3308 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3309 glColor3uiv: v
3310 	"This method was automatically generated."
3311 	"void glColor3uiv(GLuint* v);"
3312 	<cdecl: void 'glColor3uiv' (ulong*) module: 'GL'>
3313 	^self externalCallFailed! !
3314 
3315 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3316 glColor3us: red with: green with: blue
3317 	"This method was automatically generated."
3318 	"void glColor3us(GLushort red, GLushort green, GLushort blue);"
3319 	<cdecl: void 'glColor3us' (ushort ushort ushort) module: 'GL'>
3320 	^self externalCallFailed! !
3321 
3322 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3323 glColor3usv: v
3324 	"This method was automatically generated."
3325 	"void glColor3usv(GLushort* v);"
3326 	<cdecl: void 'glColor3usv' (ushort*) module: 'GL'>
3327 	^self externalCallFailed! !
3328 
3329 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3330 glColor4b: red with: green with: blue with: alpha
3331 	"This method was automatically generated."
3332 	"void glColor4b(GLbyte red, GLbyte green, GLbyte blue, GLbyte alpha);"
3333 	<cdecl: void 'glColor4b' (byte byte byte byte) module: 'GL'>
3334 	^self externalCallFailed! !
3335 
3336 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3337 glColor4bv: v
3338 	"This method was automatically generated."
3339 	"void glColor4bv(GLbyte* v);"
3340 	<cdecl: void 'glColor4bv' (byte*) module: 'GL'>
3341 	^self externalCallFailed! !
3342 
3343 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3344 glColor4d: red with: green with: blue with: alpha
3345 	"This method was automatically generated."
3346 	"void glColor4d(GLdouble red, GLdouble green, GLdouble blue, GLdouble alpha);"
3347 	<cdecl: void 'glColor4d' (double double double double) module: 'GL'>
3348 	^self externalCallFailed! !
3349 
3350 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3351 glColor4dv: v
3352 	"This method was automatically generated."
3353 	"void glColor4dv(GLdouble* v);"
3354 	<cdecl: void 'glColor4dv' (double*) module: 'GL'>
3355 	^self externalCallFailed! !
3356 
3357 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3358 glColor4f: red with: green with: blue with: alpha
3359 	"This method was automatically generated."
3360 	"void glColor4f(GLfloat red, GLfloat green, GLfloat blue, GLfloat alpha);"
3361 	<cdecl: void 'glColor4f' (float float float float) module: 'GL'>
3362 	^self externalCallFailed! !
3363 
3364 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3365 glColor4fv: v
3366 	"This method was automatically generated."
3367 	"void glColor4fv(GLfloat* v);"
3368 	<cdecl: void 'glColor4fv' (float*) module: 'GL'>
3369 	^self externalCallFailed! !
3370 
3371 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3372 glColor4i: red with: green with: blue with: alpha
3373 	"This method was automatically generated."
3374 	"void glColor4i(GLint red, GLint green, GLint blue, GLint alpha);"
3375 	<cdecl: void 'glColor4i' (long long long long) module: 'GL'>
3376 	^self externalCallFailed! !
3377 
3378 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3379 glColor4iv: v
3380 	"This method was automatically generated."
3381 	"void glColor4iv(GLint* v);"
3382 	<cdecl: void 'glColor4iv' (long*) module: 'GL'>
3383 	^self externalCallFailed! !
3384 
3385 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3386 glColor4s: red with: green with: blue with: alpha
3387 	"This method was automatically generated."
3388 	"void glColor4s(GLshort red, GLshort green, GLshort blue, GLshort alpha);"
3389 	<cdecl: void 'glColor4s' (short short short short) module: 'GL'>
3390 	^self externalCallFailed! !
3391 
3392 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3393 glColor4sv: v
3394 	"This method was automatically generated."
3395 	"void glColor4sv(GLshort* v);"
3396 	<cdecl: void 'glColor4sv' (short*) module: 'GL'>
3397 	^self externalCallFailed! !
3398 
3399 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3400 glColor4ub: red with: green with: blue with: alpha
3401 	"This method was automatically generated."
3402 	"void glColor4ub(GLubyte red, GLubyte green, GLubyte blue, GLubyte alpha);"
3403 	<cdecl: void 'glColor4ub' (byte byte byte byte) module: 'GL'>
3404 	^self externalCallFailed! !
3405 
3406 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3407 glColor4ubv: v
3408 	"This method was automatically generated."
3409 	"void glColor4ubv(GLubyte* v);"
3410 	<cdecl: void 'glColor4ubv' (byte*) module: 'GL'>
3411 	^self externalCallFailed! !
3412 
3413 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3414 glColor4ui: red with: green with: blue with: alpha
3415 	"This method was automatically generated."
3416 	"void glColor4ui(GLuint red, GLuint green, GLuint blue, GLuint alpha);"
3417 	<cdecl: void 'glColor4ui' (ulong ulong ulong ulong) module: 'GL'>
3418 	^self externalCallFailed! !
3419 
3420 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3421 glColor4uiv: v
3422 	"This method was automatically generated."
3423 	"void glColor4uiv(GLuint* v);"
3424 	<cdecl: void 'glColor4uiv' (ulong*) module: 'GL'>
3425 	^self externalCallFailed! !
3426 
3427 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3428 glColor4us: red with: green with: blue with: alpha
3429 	"This method was automatically generated."
3430 	"void glColor4us(GLushort red, GLushort green, GLushort blue, GLushort alpha);"
3431 	<cdecl: void 'glColor4us' (ushort ushort ushort ushort) module: 'GL'>
3432 	^self externalCallFailed! !
3433 
3434 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3435 glColor4usv: v
3436 	"This method was automatically generated."
3437 	"void glColor4usv(GLushort* v);"
3438 	<cdecl: void 'glColor4usv' (ushort*) module: 'GL'>
3439 	^self externalCallFailed! !
3440 
3441 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3442 glColorMask: red with: green with: blue with: alpha
3443 	"This method was automatically generated."
3444 	"void glColorMask(GLboolean red, GLboolean green, GLboolean blue, GLboolean alpha);"
3445 	<cdecl: void 'glColorMask' (bool bool bool bool) module: 'GL'>
3446 	^self externalCallFailed! !
3447 
3448 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3449 glColorMaterial: face with: mode
3450 	"This method was automatically generated."
3451 	"void glColorMaterial(GLenum face, GLenum mode);"
3452 	<cdecl: void 'glColorMaterial' (ulong ulong) module: 'GL'>
3453 	^self externalCallFailed! !
3454 
3455 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3456 glColorPointer: size with: type with: stride with: pointer
3457 	"This method was automatically generated."
3458 	"void glColorPointer(GLint size, GLenum type, GLsizei stride, GLvoid* pointer);"
3459 	<cdecl: void 'glColorPointer' (long ulong long void*) module: 'GL'>
3460 	^self externalCallFailed! !
3461 
3462 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3463 glColorPointerEXT: size with: type with: stride with: count with: pointer
3464 	"This method was automatically generated."
3465 	"void glColorPointerEXT(GLint size, GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
3466 	<cdecl: void 'glColorPointerEXT' (long ulong long long void*) module: 'GL'>
3467 	^self externalCallFailed! !
3468 
3469 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3470 glColorSubTable: target with: start with: count with: format with: type with: data
3471 	"This method was automatically generated."
3472 	"void glColorSubTable(GLenum target, GLsizei start, GLsizei count, GLenum format, GLenum type, GLvoid* data);"
3473 	<cdecl: void 'glColorSubTable' (ulong long long ulong ulong void*) module: 'GL'>
3474 	^self externalCallFailed! !
3475 
3476 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3477 glColorTable: target with: internalformat with: width with: format with: type with: table
3478 	"This method was automatically generated."
3479 	"void glColorTable(GLenum target, GLenum internalformat, GLsizei width, GLenum format, GLenum type, GLvoid* table);"
3480 	<cdecl: void 'glColorTable' (ulong ulong long ulong ulong void*) module: 'GL'>
3481 	^self externalCallFailed! !
3482 
3483 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3484 glColorTableParameterfv: target with: pname with: params
3485 	"This method was automatically generated."
3486 	"void glColorTableParameterfv(GLenum target, GLenum pname, GLfloat* params);"
3487 	<cdecl: void 'glColorTableParameterfv' (ulong ulong float*) module: 'GL'>
3488 	^self externalCallFailed! !
3489 
3490 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3491 glColorTableParameteriv: target with: pname with: params
3492 	"This method was automatically generated."
3493 	"void glColorTableParameteriv(GLenum target, GLenum pname, GLint* params);"
3494 	<cdecl: void 'glColorTableParameteriv' (ulong ulong long*) module: 'GL'>
3495 	^self externalCallFailed! !
3496 
3497 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3498 glConvolutionFilter1D: target with: internalformat with: width with: format with: type with: image
3499 	"This method was automatically generated."
3500 	"void glConvolutionFilter1D(GLenum target, GLenum internalformat, GLsizei width, GLenum format, GLenum type, GLvoid* image);"
3501 	<cdecl: void 'glConvolutionFilter1D' (ulong ulong long ulong ulong void*) module: 'GL'>
3502 	^self externalCallFailed! !
3503 
3504 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3505 glConvolutionFilter2D: target with: internalformat with: width with: height with: format with: type with: image
3506 	"This method was automatically generated."
3507 	"void glConvolutionFilter2D(GLenum target, GLenum internalformat, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* image);"
3508 	<cdecl: void 'glConvolutionFilter2D' (ulong ulong long long ulong ulong void*) module: 'GL'>
3509 	^self externalCallFailed! !
3510 
3511 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3512 glConvolutionParameterf: target with: pname with: params
3513 	"This method was automatically generated."
3514 	"void glConvolutionParameterf(GLenum target, GLenum pname, GLfloat params);"
3515 	<cdecl: void 'glConvolutionParameterf' (ulong ulong float) module: 'GL'>
3516 	^self externalCallFailed! !
3517 
3518 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3519 glConvolutionParameterfv: target with: pname with: params
3520 	"This method was automatically generated."
3521 	"void glConvolutionParameterfv(GLenum target, GLenum pname, GLfloat* params);"
3522 	<cdecl: void 'glConvolutionParameterfv' (ulong ulong float*) module: 'GL'>
3523 	^self externalCallFailed! !
3524 
3525 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3526 glConvolutionParameteri: target with: pname with: params
3527 	"This method was automatically generated."
3528 	"void glConvolutionParameteri(GLenum target, GLenum pname, GLint params);"
3529 	<cdecl: void 'glConvolutionParameteri' (ulong ulong long) module: 'GL'>
3530 	^self externalCallFailed! !
3531 
3532 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3533 glConvolutionParameteriv: target with: pname with: params
3534 	"This method was automatically generated."
3535 	"void glConvolutionParameteriv(GLenum target, GLenum pname, GLint* params);"
3536 	<cdecl: void 'glConvolutionParameteriv' (ulong ulong long*) module: 'GL'>
3537 	^self externalCallFailed! !
3538 
3539 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3540 glCopyColorSubTable: target with: start with: x with: y with: width
3541 	"This method was automatically generated."
3542 	"void glCopyColorSubTable(GLenum target, GLsizei start, GLint x, GLint y, GLsizei width);"
3543 	<cdecl: void 'glCopyColorSubTable' (ulong long long long long) module: 'GL'>
3544 	^self externalCallFailed! !
3545 
3546 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3547 glCopyColorTable: target with: internalformat with: x with: y with: width
3548 	"This method was automatically generated."
3549 	"void glCopyColorTable(GLenum target, GLenum internalformat, GLint x, GLint y, GLsizei width);"
3550 	<cdecl: void 'glCopyColorTable' (ulong ulong long long long) module: 'GL'>
3551 	^self externalCallFailed! !
3552 
3553 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3554 glCopyConvolutionFilter1D: target with: internalformat with: x with: y with: width
3555 	"This method was automatically generated."
3556 	"void glCopyConvolutionFilter1D(GLenum target, GLenum internalformat, GLint x, GLint y, GLsizei width);"
3557 	<cdecl: void 'glCopyConvolutionFilter1D' (ulong ulong long long long) module: 'GL'>
3558 	^self externalCallFailed! !
3559 
3560 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3561 glCopyConvolutionFilter2D: target with: internalformat with: x with: y with: width with: height
3562 	"This method was automatically generated."
3563 	"void glCopyConvolutionFilter2D(GLenum target, GLenum internalformat, GLint x, GLint y, GLsizei width, GLsizei height);"
3564 	<cdecl: void 'glCopyConvolutionFilter2D' (ulong ulong long long long long) module: 'GL'>
3565 	^self externalCallFailed! !
3566 
3567 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3568 glCopyPixels: x with: y with: width with: height with: type
3569 	"This method was automatically generated."
3570 	"void glCopyPixels(GLint x, GLint y, GLsizei width, GLsizei height, GLenum type);"
3571 	<cdecl: void 'glCopyPixels' (long long long long ulong) module: 'GL'>
3572 	^self externalCallFailed! !
3573 
3574 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3575 glCopyTexImage1D: target with: level with: internalformat with: x with: y with: width with: border
3576 	"This method was automatically generated."
3577 	"void glCopyTexImage1D(GLenum target, GLint level, GLenum internalformat, GLint x, GLint y, GLsizei width, GLint border);"
3578 	<cdecl: void 'glCopyTexImage1D' (ulong long ulong long long long long) module: 'GL'>
3579 	^self externalCallFailed! !
3580 
3581 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3582 glCopyTexImage2D: target with: level with: internalformat with: x with: y with: width with: height with: border
3583 	"This method was automatically generated."
3584 	"void glCopyTexImage2D(GLenum target, GLint level, GLenum internalformat, GLint x, GLint y, GLsizei width, GLsizei height, GLint border);"
3585 	<cdecl: void 'glCopyTexImage2D' (ulong long ulong long long long long long) module: 'GL'>
3586 	^self externalCallFailed! !
3587 
3588 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3589 glCopyTexSubImage1D: target with: level with: xoffset with: x with: y with: width
3590 	"This method was automatically generated."
3591 	"void glCopyTexSubImage1D(GLenum target, GLint level, GLint xoffset, GLint x, GLint y, GLsizei width);"
3592 	<cdecl: void 'glCopyTexSubImage1D' (ulong long long long long long) module: 'GL'>
3593 	^self externalCallFailed! !
3594 
3595 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3596 glCopyTexSubImage2D: target with: level with: xoffset with: yoffset with: x with: y with: width with: height
3597 	"This method was automatically generated."
3598 	"void glCopyTexSubImage2D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLint x, GLint y, GLsizei width, GLsizei height);"
3599 	<cdecl: void 'glCopyTexSubImage2D' (ulong long long long long long long long) module: 'GL'>
3600 	^self externalCallFailed! !
3601 
3602 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3603 glCopyTexSubImage3D: target with: level with: xoffset with: yoffset with: zoffset with: x with: y with: width with: height
3604 	"This method was automatically generated."
3605 	"void glCopyTexSubImage3D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLint zoffset, GLint x, GLint y, GLsizei width, GLsizei height);"
3606 	<cdecl: void 'glCopyTexSubImage3D' (ulong long long long long long long long long) module: 'GL'>
3607 	^self externalCallFailed! !
3608 
3609 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3610 glCullFace: mode
3611 	"This method was automatically generated."
3612 	"void glCullFace(GLenum mode);"
3613 	<cdecl: void 'glCullFace' (ulong) module: 'GL'>
3614 	^self externalCallFailed! !
3615 
3616 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3617 glDeleteLists: list with: range
3618 	"This method was automatically generated."
3619 	"void glDeleteLists(GLuint list, GLsizei range);"
3620 	<cdecl: void 'glDeleteLists' (ulong long) module: 'GL'>
3621 	^self externalCallFailed! !
3622 
3623 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3624 glDeleteTextures: n with: textures
3625 	"This method was automatically generated."
3626 	"void glDeleteTextures(GLsizei n, GLuint* textures);"
3627 	<cdecl: void 'glDeleteTextures' (long ulong*) module: 'GL'>
3628 	^self externalCallFailed! !
3629 
3630 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3631 glDeleteTexturesEXT: n with: textures
3632 	"This method was automatically generated."
3633 	"void glDeleteTexturesEXT(GLsizei n, GLuint* textures);"
3634 	<cdecl: void 'glDeleteTexturesEXT' (long ulong*) module: 'GL'>
3635 	^self externalCallFailed! !
3636 
3637 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3638 glDepthFunc: func
3639 	"This method was automatically generated."
3640 	"void glDepthFunc(GLenum func);"
3641 	<cdecl: void 'glDepthFunc' (ulong) module: 'GL'>
3642 	^self externalCallFailed! !
3643 
3644 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3645 glDepthMask: flag
3646 	"This method was automatically generated."
3647 	"void glDepthMask(GLboolean flag);"
3648 	<cdecl: void 'glDepthMask' (bool) module: 'GL'>
3649 	^self externalCallFailed! !
3650 
3651 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3652 glDepthRange: zNear with: zFar
3653 	"This method was automatically generated."
3654 	"void glDepthRange(GLclampd zNear, GLclampd zFar);"
3655 	<cdecl: void 'glDepthRange' (double double) module: 'GL'>
3656 	^self externalCallFailed! !
3657 
3658 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3659 glDisable: cap
3660 	"This method was automatically generated."
3661 	"void glDisable(GLenum cap);"
3662 	<cdecl: void 'glDisable' (ulong) module: 'GL'>
3663 	^self externalCallFailed! !
3664 
3665 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3666 glDisableClientState: array
3667 	"This method was automatically generated."
3668 	"void glDisableClientState(GLenum array);"
3669 	<cdecl: void 'glDisableClientState' (ulong) module: 'GL'>
3670 	^self externalCallFailed! !
3671 
3672 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3673 glDrawArrays: mode with: first with: count
3674 	"This method was automatically generated."
3675 	"void glDrawArrays(GLenum mode, GLint first, GLsizei count);"
3676 	<cdecl: void 'glDrawArrays' (ulong long long) module: 'GL'>
3677 	^self externalCallFailed! !
3678 
3679 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3680 glDrawArraysEXT: mode with: first with: count
3681 	"This method was automatically generated."
3682 	"void glDrawArraysEXT(GLenum mode, GLint first, GLsizei count);"
3683 	<cdecl: void 'glDrawArraysEXT' (ulong long long) module: 'GL'>
3684 	^self externalCallFailed! !
3685 
3686 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3687 glDrawBuffer: mode
3688 	"This method was automatically generated."
3689 	"void glDrawBuffer(GLenum mode);"
3690 	<cdecl: void 'glDrawBuffer' (ulong) module: 'GL'>
3691 	^self externalCallFailed! !
3692 
3693 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3694 glDrawElements: mode with: count with: type with: indices
3695 	"This method was automatically generated."
3696 	"void glDrawElements(GLenum mode, GLsizei count, GLenum type, GLvoid* indices);"
3697 	<cdecl: void 'glDrawElements' (ulong long ulong void*) module: 'GL'>
3698 	^self externalCallFailed! !
3699 
3700 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3701 glDrawPixels: width with: height with: format with: type with: pixels
3702 	"This method was automatically generated."
3703 	"void glDrawPixels(GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* pixels);"
3704 	<cdecl: void 'glDrawPixels' (long long ulong ulong void*) module: 'GL'>
3705 	^self externalCallFailed! !
3706 
3707 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3708 glDrawRangeElements: mode with: start with: end with: count with: type with: indices
3709 	"This method was automatically generated."
3710 	"void glDrawRangeElements(GLenum mode, GLuint start, GLuint end, GLsizei count, GLenum type, GLvoid* indices);"
3711 	<cdecl: void 'glDrawRangeElements' (ulong ulong ulong long ulong void*) module: 'GL'>
3712 	^self externalCallFailed! !
3713 
3714 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3715 glEdgeFlag: flag
3716 	"This method was automatically generated."
3717 	"void glEdgeFlag(GLboolean flag);"
3718 	<cdecl: void 'glEdgeFlag' (bool) module: 'GL'>
3719 	^self externalCallFailed! !
3720 
3721 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3722 glEdgeFlagPointer: stride with: pointer
3723 	"This method was automatically generated."
3724 	"void glEdgeFlagPointer(GLsizei stride, GLboolean* pointer);"
3725 	<cdecl: void 'glEdgeFlagPointer' (long ulong*) module: 'GL'>
3726 	^self externalCallFailed! !
3727 
3728 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3729 glEdgeFlagPointerEXT: stride with: count with: pointer
3730 	"This method was automatically generated."
3731 	"void glEdgeFlagPointerEXT(GLsizei stride, GLsizei count, GLboolean* pointer);"
3732 	<cdecl: void 'glEdgeFlagPointerEXT' (long long ulong*) module: 'GL'>
3733 	^self externalCallFailed! !
3734 
3735 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3736 glEdgeFlagv: flag
3737 	"This method was automatically generated."
3738 	"void glEdgeFlagv(GLboolean* flag);"
3739 	<cdecl: void 'glEdgeFlagv' (ulong*) module: 'GL'>
3740 	^self externalCallFailed! !
3741 
3742 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3743 glEnable: cap
3744 	"This method was automatically generated."
3745 	"void glEnable(GLenum cap);"
3746 	<cdecl: void 'glEnable' (ulong) module: 'GL'>
3747 	^self externalCallFailed! !
3748 
3749 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3750 glEnableClientState: array
3751 	"This method was automatically generated."
3752 	"void glEnableClientState(GLenum array);"
3753 	<cdecl: void 'glEnableClientState' (ulong) module: 'GL'>
3754 	^self externalCallFailed! !
3755 
3756 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3757 glEnd
3758 	"This method was automatically generated."
3759 	"void glEnd();"
3760 	<cdecl: void 'glEnd' (void) module: 'GL'>
3761 	^self externalCallFailed! !
3762 
3763 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3764 glEndList
3765 	"This method was automatically generated."
3766 	"void glEndList();"
3767 	<cdecl: void 'glEndList' (void) module: 'GL'>
3768 	^self externalCallFailed! !
3769 
3770 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3771 glEvalCoord1d: u
3772 	"This method was automatically generated."
3773 	"void glEvalCoord1d(GLdouble u);"
3774 	<cdecl: void 'glEvalCoord1d' (double) module: 'GL'>
3775 	^self externalCallFailed! !
3776 
3777 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3778 glEvalCoord1dv: u
3779 	"This method was automatically generated."
3780 	"void glEvalCoord1dv(GLdouble* u);"
3781 	<cdecl: void 'glEvalCoord1dv' (double*) module: 'GL'>
3782 	^self externalCallFailed! !
3783 
3784 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3785 glEvalCoord1f: u
3786 	"This method was automatically generated."
3787 	"void glEvalCoord1f(GLfloat u);"
3788 	<cdecl: void 'glEvalCoord1f' (float) module: 'GL'>
3789 	^self externalCallFailed! !
3790 
3791 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3792 glEvalCoord1fv: u
3793 	"This method was automatically generated."
3794 	"void glEvalCoord1fv(GLfloat* u);"
3795 	<cdecl: void 'glEvalCoord1fv' (float*) module: 'GL'>
3796 	^self externalCallFailed! !
3797 
3798 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3799 glEvalCoord2d: u with: v
3800 	"This method was automatically generated."
3801 	"void glEvalCoord2d(GLdouble u, GLdouble v);"
3802 	<cdecl: void 'glEvalCoord2d' (double double) module: 'GL'>
3803 	^self externalCallFailed! !
3804 
3805 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3806 glEvalCoord2dv: u
3807 	"This method was automatically generated."
3808 	"void glEvalCoord2dv(GLdouble* u);"
3809 	<cdecl: void 'glEvalCoord2dv' (double*) module: 'GL'>
3810 	^self externalCallFailed! !
3811 
3812 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3813 glEvalCoord2f: u with: v
3814 	"This method was automatically generated."
3815 	"void glEvalCoord2f(GLfloat u, GLfloat v);"
3816 	<cdecl: void 'glEvalCoord2f' (float float) module: 'GL'>
3817 	^self externalCallFailed! !
3818 
3819 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3820 glEvalCoord2fv: u
3821 	"This method was automatically generated."
3822 	"void glEvalCoord2fv(GLfloat* u);"
3823 	<cdecl: void 'glEvalCoord2fv' (float*) module: 'GL'>
3824 	^self externalCallFailed! !
3825 
3826 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3827 glEvalMesh1: mode with: i1 with: i2
3828 	"This method was automatically generated."
3829 	"void glEvalMesh1(GLenum mode, GLint i1, GLint i2);"
3830 	<cdecl: void 'glEvalMesh1' (ulong long long) module: 'GL'>
3831 	^self externalCallFailed! !
3832 
3833 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3834 glEvalMesh2: mode with: i1 with: i2 with: j1 with: j2
3835 	"This method was automatically generated."
3836 	"void glEvalMesh2(GLenum mode, GLint i1, GLint i2, GLint j1, GLint j2);"
3837 	<cdecl: void 'glEvalMesh2' (ulong long long long long) module: 'GL'>
3838 	^self externalCallFailed! !
3839 
3840 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3841 glEvalPoint1: i
3842 	"This method was automatically generated."
3843 	"void glEvalPoint1(GLint i);"
3844 	<cdecl: void 'glEvalPoint1' (long) module: 'GL'>
3845 	^self externalCallFailed! !
3846 
3847 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3848 glEvalPoint2: i with: j
3849 	"This method was automatically generated."
3850 	"void glEvalPoint2(GLint i, GLint j);"
3851 	<cdecl: void 'glEvalPoint2' (long long) module: 'GL'>
3852 	^self externalCallFailed! !
3853 
3854 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3855 glFeedbackBuffer: size with: type with: buffer
3856 	"This method was automatically generated."
3857 	"void glFeedbackBuffer(GLsizei size, GLenum type, GLfloat* buffer);"
3858 	<cdecl: void 'glFeedbackBuffer' (long ulong float*) module: 'GL'>
3859 	^self externalCallFailed! !
3860 
3861 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3862 glFinish
3863 	"This method was automatically generated."
3864 	"void glFinish();"
3865 	<cdecl: void 'glFinish' (void) module: 'GL'>
3866 	^self externalCallFailed! !
3867 
3868 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3869 glFlush
3870 	"This method was automatically generated."
3871 	"void glFlush();"
3872 	<cdecl: void 'glFlush' (void) module: 'GL'>
3873 	^self externalCallFailed! !
3874 
3875 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3876 glFogf: pname with: param
3877 	"This method was automatically generated."
3878 	"void glFogf(GLenum pname, GLfloat param);"
3879 	<cdecl: void 'glFogf' (ulong float) module: 'GL'>
3880 	^self externalCallFailed! !
3881 
3882 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3883 glFogfv: pname with: params
3884 	"This method was automatically generated."
3885 	"void glFogfv(GLenum pname, GLfloat* params);"
3886 	<cdecl: void 'glFogfv' (ulong float*) module: 'GL'>
3887 	^self externalCallFailed! !
3888 
3889 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3890 glFogi: pname with: param
3891 	"This method was automatically generated."
3892 	"void glFogi(GLenum pname, GLint param);"
3893 	<cdecl: void 'glFogi' (ulong long) module: 'GL'>
3894 	^self externalCallFailed! !
3895 
3896 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3897 glFogiv: pname with: params
3898 	"This method was automatically generated."
3899 	"void glFogiv(GLenum pname, GLint* params);"
3900 	<cdecl: void 'glFogiv' (ulong long*) module: 'GL'>
3901 	^self externalCallFailed! !
3902 
3903 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3904 glFrontFace: mode
3905 	"This method was automatically generated."
3906 	"void glFrontFace(GLenum mode);"
3907 	<cdecl: void 'glFrontFace' (ulong) module: 'GL'>
3908 	^self externalCallFailed! !
3909 
3910 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3911 glFrustum: left with: right with: bottom with: top with: zNear with: zFar
3912 	"This method was automatically generated."
3913 	"void glFrustum(GLdouble left, GLdouble right, GLdouble bottom, GLdouble top, GLdouble zNear, GLdouble zFar);"
3914 	<cdecl: void 'glFrustum' (double double double double double double) module: 'GL'>
3915 	^self externalCallFailed! !
3916 
3917 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3918 glGenLists: range
3919 	"This method was automatically generated."
3920 	"GLuint glGenLists(GLsizei range);"
3921 	<cdecl: ulong 'glGenLists' (long) module: 'GL'>
3922 	^self externalCallFailed! !
3923 
3924 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3925 glGenTextures: n with: textures
3926 	"This method was automatically generated."
3927 	"void glGenTextures(GLsizei n, GLuint* textures);"
3928 	<cdecl: void 'glGenTextures' (long ulong*) module: 'GL'>
3929 	^self externalCallFailed! !
3930 
3931 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3932 glGenTexturesEXT: n with: textures
3933 	"This method was automatically generated."
3934 	"void glGenTexturesEXT(GLsizei n, GLuint* textures);"
3935 	<cdecl: void 'glGenTexturesEXT' (long ulong*) module: 'GL'>
3936 	^self externalCallFailed! !
3937 
3938 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3939 glGetBooleanv: pname with: params
3940 	"This method was automatically generated."
3941 	"void glGetBooleanv(GLenum pname, GLboolean* params);"
3942 	<cdecl: void 'glGetBooleanv' (ulong ulong*) module: 'GL'>
3943 	^self externalCallFailed! !
3944 
3945 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3946 glGetClipPlane: plane with: equation
3947 	"This method was automatically generated."
3948 	"void glGetClipPlane(GLenum plane, GLdouble* equation);"
3949 	<cdecl: void 'glGetClipPlane' (ulong double*) module: 'GL'>
3950 	^self externalCallFailed! !
3951 
3952 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3953 glGetColorTable: target with: format with: type with: table
3954 	"This method was automatically generated."
3955 	"void glGetColorTable(GLenum target, GLenum format, GLenum type, GLvoid* table);"
3956 	<cdecl: void 'glGetColorTable' (ulong ulong ulong void*) module: 'GL'>
3957 	^self externalCallFailed! !
3958 
3959 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3960 glGetColorTableParameterfv: target with: pname with: params
3961 	"This method was automatically generated."
3962 	"void glGetColorTableParameterfv(GLenum target, GLenum pname, GLfloat* params);"
3963 	<cdecl: void 'glGetColorTableParameterfv' (ulong ulong float*) module: 'GL'>
3964 	^self externalCallFailed! !
3965 
3966 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3967 glGetColorTableParameteriv: target with: pname with: params
3968 	"This method was automatically generated."
3969 	"void glGetColorTableParameteriv(GLenum target, GLenum pname, GLint* params);"
3970 	<cdecl: void 'glGetColorTableParameteriv' (ulong ulong long*) module: 'GL'>
3971 	^self externalCallFailed! !
3972 
3973 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3974 glGetConvolutionFilter: target with: format with: type with: image
3975 	"This method was automatically generated."
3976 	"void glGetConvolutionFilter(GLenum target, GLenum format, GLenum type, GLvoid* image);"
3977 	<cdecl: void 'glGetConvolutionFilter' (ulong ulong ulong void*) module: 'GL'>
3978 	^self externalCallFailed! !
3979 
3980 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3981 glGetConvolutionParameterfv: target with: pname with: params
3982 	"This method was automatically generated."
3983 	"void glGetConvolutionParameterfv(GLenum target, GLenum pname, GLfloat* params);"
3984 	<cdecl: void 'glGetConvolutionParameterfv' (ulong ulong float*) module: 'GL'>
3985 	^self externalCallFailed! !
3986 
3987 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3988 glGetConvolutionParameteriv: target with: pname with: params
3989 	"This method was automatically generated."
3990 	"void glGetConvolutionParameteriv(GLenum target, GLenum pname, GLint* params);"
3991 	<cdecl: void 'glGetConvolutionParameteriv' (ulong ulong long*) module: 'GL'>
3992 	^self externalCallFailed! !
3993 
3994 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
3995 glGetDoublev: pname with: params
3996 	"This method was automatically generated."
3997 	"void glGetDoublev(GLenum pname, GLdouble* params);"
3998 	<cdecl: void 'glGetDoublev' (ulong double*) module: 'GL'>
3999 	^self externalCallFailed! !
4000 
4001 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4002 glGetError
4003 	"This method was automatically generated."
4004 	"GLenum glGetError();"
4005 	<cdecl: ulong 'glGetError' (void) module: 'GL'>
4006 	^self externalCallFailed! !
4007 
4008 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4009 glGetFloatv: pname with: params
4010 	"This method was automatically generated."
4011 	"void glGetFloatv(GLenum pname, GLfloat* params);"
4012 	<cdecl: void 'glGetFloatv' (ulong float*) module: 'GL'>
4013 	^self externalCallFailed! !
4014 
4015 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4016 glGetHistogram: target with: reset with: format with: type with: values
4017 	"This method was automatically generated."
4018 	"void glGetHistogram(GLenum target, GLboolean reset, GLenum format, GLenum type, GLvoid* values);"
4019 	<cdecl: void 'glGetHistogram' (ulong bool ulong ulong void*) module: 'GL'>
4020 	^self externalCallFailed! !
4021 
4022 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4023 glGetHistogramParameterfv: target with: pname with: params
4024 	"This method was automatically generated."
4025 	"void glGetHistogramParameterfv(GLenum target, GLenum pname, GLfloat* params);"
4026 	<cdecl: void 'glGetHistogramParameterfv' (ulong ulong float*) module: 'GL'>
4027 	^self externalCallFailed! !
4028 
4029 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4030 glGetHistogramParameteriv: target with: pname with: params
4031 	"This method was automatically generated."
4032 	"void glGetHistogramParameteriv(GLenum target, GLenum pname, GLint* params);"
4033 	<cdecl: void 'glGetHistogramParameteriv' (ulong ulong long*) module: 'GL'>
4034 	^self externalCallFailed! !
4035 
4036 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4037 glGetIntegerv: pname with: params
4038 	"This method was automatically generated."
4039 	"void glGetIntegerv(GLenum pname, GLint* params);"
4040 	<cdecl: void 'glGetIntegerv' (ulong long*) module: 'GL'>
4041 	^self externalCallFailed! !
4042 
4043 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4044 glGetLightfv: light with: pname with: params
4045 	"This method was automatically generated."
4046 	"void glGetLightfv(GLenum light, GLenum pname, GLfloat* params);"
4047 	<cdecl: void 'glGetLightfv' (ulong ulong float*) module: 'GL'>
4048 	^self externalCallFailed! !
4049 
4050 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4051 glGetLightiv: light with: pname with: params
4052 	"This method was automatically generated."
4053 	"void glGetLightiv(GLenum light, GLenum pname, GLint* params);"
4054 	<cdecl: void 'glGetLightiv' (ulong ulong long*) module: 'GL'>
4055 	^self externalCallFailed! !
4056 
4057 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4058 glGetMapdv: target with: query with: v
4059 	"This method was automatically generated."
4060 	"void glGetMapdv(GLenum target, GLenum query, GLdouble* v);"
4061 	<cdecl: void 'glGetMapdv' (ulong ulong double*) module: 'GL'>
4062 	^self externalCallFailed! !
4063 
4064 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4065 glGetMapfv: target with: query with: v
4066 	"This method was automatically generated."
4067 	"void glGetMapfv(GLenum target, GLenum query, GLfloat* v);"
4068 	<cdecl: void 'glGetMapfv' (ulong ulong float*) module: 'GL'>
4069 	^self externalCallFailed! !
4070 
4071 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4072 glGetMapiv: target with: query with: v
4073 	"This method was automatically generated."
4074 	"void glGetMapiv(GLenum target, GLenum query, GLint* v);"
4075 	<cdecl: void 'glGetMapiv' (ulong ulong long*) module: 'GL'>
4076 	^self externalCallFailed! !
4077 
4078 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4079 glGetMaterialfv: face with: pname with: params
4080 	"This method was automatically generated."
4081 	"void glGetMaterialfv(GLenum face, GLenum pname, GLfloat* params);"
4082 	<cdecl: void 'glGetMaterialfv' (ulong ulong float*) module: 'GL'>
4083 	^self externalCallFailed! !
4084 
4085 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4086 glGetMaterialiv: face with: pname with: params
4087 	"This method was automatically generated."
4088 	"void glGetMaterialiv(GLenum face, GLenum pname, GLint* params);"
4089 	<cdecl: void 'glGetMaterialiv' (ulong ulong long*) module: 'GL'>
4090 	^self externalCallFailed! !
4091 
4092 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4093 glGetMinmax: target with: reset with: format with: type with: values
4094 	"This method was automatically generated."
4095 	"void glGetMinmax(GLenum target, GLboolean reset, GLenum format, GLenum type, GLvoid* values);"
4096 	<cdecl: void 'glGetMinmax' (ulong bool ulong ulong void*) module: 'GL'>
4097 	^self externalCallFailed! !
4098 
4099 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4100 glGetMinmaxParameterfv: target with: pname with: params
4101 	"This method was automatically generated."
4102 	"void glGetMinmaxParameterfv(GLenum target, GLenum pname, GLfloat* params);"
4103 	<cdecl: void 'glGetMinmaxParameterfv' (ulong ulong float*) module: 'GL'>
4104 	^self externalCallFailed! !
4105 
4106 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4107 glGetMinmaxParameteriv: target with: pname with: params
4108 	"This method was automatically generated."
4109 	"void glGetMinmaxParameteriv(GLenum target, GLenum pname, GLint* params);"
4110 	<cdecl: void 'glGetMinmaxParameteriv' (ulong ulong long*) module: 'GL'>
4111 	^self externalCallFailed! !
4112 
4113 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4114 glGetPixelMapfv: map with: values
4115 	"This method was automatically generated."
4116 	"void glGetPixelMapfv(GLenum map, GLfloat* values);"
4117 	<cdecl: void 'glGetPixelMapfv' (ulong float*) module: 'GL'>
4118 	^self externalCallFailed! !
4119 
4120 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4121 glGetPixelMapuiv: map with: values
4122 	"This method was automatically generated."
4123 	"void glGetPixelMapuiv(GLenum map, GLuint* values);"
4124 	<cdecl: void 'glGetPixelMapuiv' (ulong ulong*) module: 'GL'>
4125 	^self externalCallFailed! !
4126 
4127 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4128 glGetPixelMapusv: map with: values
4129 	"This method was automatically generated."
4130 	"void glGetPixelMapusv(GLenum map, GLushort* values);"
4131 	<cdecl: void 'glGetPixelMapusv' (ulong ushort*) module: 'GL'>
4132 	^self externalCallFailed! !
4133 
4134 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4135 glGetPointerv: pname with: params
4136 	"This method was automatically generated."
4137 	"void glGetPointerv(GLenum pname, GLvoid** params);"
4138 	<cdecl: void 'glGetPointerv' (ulong void*) module: 'GL'>
4139 	^self externalCallFailed! !
4140 
4141 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4142 glGetPointervEXT: pname with: params
4143 	"This method was automatically generated."
4144 	"void glGetPointervEXT(GLenum pname, GLvoid** params);"
4145 	<cdecl: void 'glGetPointervEXT' (ulong void*) module: 'GL'>
4146 	^self externalCallFailed! !
4147 
4148 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4149 glGetPolygonStipple: mask
4150 	"This method was automatically generated."
4151 	"void glGetPolygonStipple(GLubyte* mask);"
4152 	<cdecl: void 'glGetPolygonStipple' (byte*) module: 'GL'>
4153 	^self externalCallFailed! !
4154 
4155 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4156 glGetSeparableFilter: target with: format with: type with: row with: column with: span
4157 	"This method was automatically generated."
4158 	"void glGetSeparableFilter(GLenum target, GLenum format, GLenum type, GLvoid* row, GLvoid* column, GLvoid* span);"
4159 	<cdecl: void 'glGetSeparableFilter' (ulong ulong ulong void* void* void*) module: 'GL'>
4160 	^self externalCallFailed! !
4161 
4162 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4163 glGetString: name
4164 	"This method was automatically generated."
4165 	"GLubyte* glGetString(GLenum name);"
4166 	<cdecl: byte* 'glGetString' (ulong) module: 'GL'>
4167 	^self externalCallFailed! !
4168 
4169 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4170 glGetTexEnvfv: target with: pname with: params
4171 	"This method was automatically generated."
4172 	"void glGetTexEnvfv(GLenum target, GLenum pname, GLfloat* params);"
4173 	<cdecl: void 'glGetTexEnvfv' (ulong ulong float*) module: 'GL'>
4174 	^self externalCallFailed! !
4175 
4176 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4177 glGetTexEnviv: target with: pname with: params
4178 	"This method was automatically generated."
4179 	"void glGetTexEnviv(GLenum target, GLenum pname, GLint* params);"
4180 	<cdecl: void 'glGetTexEnviv' (ulong ulong long*) module: 'GL'>
4181 	^self externalCallFailed! !
4182 
4183 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4184 glGetTexGendv: coord with: pname with: params
4185 	"This method was automatically generated."
4186 	"void glGetTexGendv(GLenum coord, GLenum pname, GLdouble* params);"
4187 	<cdecl: void 'glGetTexGendv' (ulong ulong double*) module: 'GL'>
4188 	^self externalCallFailed! !
4189 
4190 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4191 glGetTexGenfv: coord with: pname with: params
4192 	"This method was automatically generated."
4193 	"void glGetTexGenfv(GLenum coord, GLenum pname, GLfloat* params);"
4194 	<cdecl: void 'glGetTexGenfv' (ulong ulong float*) module: 'GL'>
4195 	^self externalCallFailed! !
4196 
4197 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4198 glGetTexGeniv: coord with: pname with: params
4199 	"This method was automatically generated."
4200 	"void glGetTexGeniv(GLenum coord, GLenum pname, GLint* params);"
4201 	<cdecl: void 'glGetTexGeniv' (ulong ulong long*) module: 'GL'>
4202 	^self externalCallFailed! !
4203 
4204 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4205 glGetTexImage: target with: level with: format with: type with: pixels
4206 	"This method was automatically generated."
4207 	"void glGetTexImage(GLenum target, GLint level, GLenum format, GLenum type, GLvoid* pixels);"
4208 	<cdecl: void 'glGetTexImage' (ulong long ulong ulong void*) module: 'GL'>
4209 	^self externalCallFailed! !
4210 
4211 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4212 glGetTexLevelParameterfv: target with: level with: pname with: params
4213 	"This method was automatically generated."
4214 	"void glGetTexLevelParameterfv(GLenum target, GLint level, GLenum pname, GLfloat* params);"
4215 	<cdecl: void 'glGetTexLevelParameterfv' (ulong long ulong float*) module: 'GL'>
4216 	^self externalCallFailed! !
4217 
4218 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4219 glGetTexLevelParameteriv: target with: level with: pname with: params
4220 	"This method was automatically generated."
4221 	"void glGetTexLevelParameteriv(GLenum target, GLint level, GLenum pname, GLint* params);"
4222 	<cdecl: void 'glGetTexLevelParameteriv' (ulong long ulong long*) module: 'GL'>
4223 	^self externalCallFailed! !
4224 
4225 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4226 glGetTexParameterfv: target with: pname with: params
4227 	"This method was automatically generated."
4228 	"void glGetTexParameterfv(GLenum target, GLenum pname, GLfloat* params);"
4229 	<cdecl: void 'glGetTexParameterfv' (ulong ulong float*) module: 'GL'>
4230 	^self externalCallFailed! !
4231 
4232 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4233 glGetTexParameteriv: target with: pname with: params
4234 	"This method was automatically generated."
4235 	"void glGetTexParameteriv(GLenum target, GLenum pname, GLint* params);"
4236 	<cdecl: void 'glGetTexParameteriv' (ulong ulong long*) module: 'GL'>
4237 	^self externalCallFailed! !
4238 
4239 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4240 glHint: target with: mode
4241 	"This method was automatically generated."
4242 	"void glHint(GLenum target, GLenum mode);"
4243 	<cdecl: void 'glHint' (ulong ulong) module: 'GL'>
4244 	^self externalCallFailed! !
4245 
4246 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4247 glHistogram: target with: width with: internalformat with: sink
4248 	"This method was automatically generated."
4249 	"void glHistogram(GLenum target, GLsizei width, GLenum internalformat, GLboolean sink);"
4250 	<cdecl: void 'glHistogram' (ulong long ulong bool) module: 'GL'>
4251 	^self externalCallFailed! !
4252 
4253 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4254 glIndexMask: mask
4255 	"This method was automatically generated."
4256 	"void glIndexMask(GLuint mask);"
4257 	<cdecl: void 'glIndexMask' (ulong) module: 'GL'>
4258 	^self externalCallFailed! !
4259 
4260 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4261 glIndexPointer: type with: stride with: pointer
4262 	"This method was automatically generated."
4263 	"void glIndexPointer(GLenum type, GLsizei stride, GLvoid* pointer);"
4264 	<cdecl: void 'glIndexPointer' (ulong long void*) module: 'GL'>
4265 	^self externalCallFailed! !
4266 
4267 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4268 glIndexPointerEXT: type with: stride with: count with: pointer
4269 	"This method was automatically generated."
4270 	"void glIndexPointerEXT(GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
4271 	<cdecl: void 'glIndexPointerEXT' (ulong long long void*) module: 'GL'>
4272 	^self externalCallFailed! !
4273 
4274 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4275 glIndexd: c
4276 	"This method was automatically generated."
4277 	"void glIndexd(GLdouble c);"
4278 	<cdecl: void 'glIndexd' (double) module: 'GL'>
4279 	^self externalCallFailed! !
4280 
4281 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4282 glIndexdv: c
4283 	"This method was automatically generated."
4284 	"void glIndexdv(GLdouble* c);"
4285 	<cdecl: void 'glIndexdv' (double*) module: 'GL'>
4286 	^self externalCallFailed! !
4287 
4288 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4289 glIndexf: c
4290 	"This method was automatically generated."
4291 	"void glIndexf(GLfloat c);"
4292 	<cdecl: void 'glIndexf' (float) module: 'GL'>
4293 	^self externalCallFailed! !
4294 
4295 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4296 glIndexfv: c
4297 	"This method was automatically generated."
4298 	"void glIndexfv(GLfloat* c);"
4299 	<cdecl: void 'glIndexfv' (float*) module: 'GL'>
4300 	^self externalCallFailed! !
4301 
4302 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4303 glIndexi: c
4304 	"This method was automatically generated."
4305 	"void glIndexi(GLint c);"
4306 	<cdecl: void 'glIndexi' (long) module: 'GL'>
4307 	^self externalCallFailed! !
4308 
4309 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4310 glIndexiv: c
4311 	"This method was automatically generated."
4312 	"void glIndexiv(GLint* c);"
4313 	<cdecl: void 'glIndexiv' (long*) module: 'GL'>
4314 	^self externalCallFailed! !
4315 
4316 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4317 glIndexs: c
4318 	"This method was automatically generated."
4319 	"void glIndexs(GLshort c);"
4320 	<cdecl: void 'glIndexs' (short) module: 'GL'>
4321 	^self externalCallFailed! !
4322 
4323 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4324 glIndexsv: c
4325 	"This method was automatically generated."
4326 	"void glIndexsv(GLshort* c);"
4327 	<cdecl: void 'glIndexsv' (short*) module: 'GL'>
4328 	^self externalCallFailed! !
4329 
4330 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4331 glIndexub: c
4332 	"This method was automatically generated."
4333 	"void glIndexub(GLubyte c);"
4334 	<cdecl: void 'glIndexub' (byte) module: 'GL'>
4335 	^self externalCallFailed! !
4336 
4337 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4338 glIndexubv: c
4339 	"This method was automatically generated."
4340 	"void glIndexubv(GLubyte* c);"
4341 	<cdecl: void 'glIndexubv' (byte*) module: 'GL'>
4342 	^self externalCallFailed! !
4343 
4344 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4345 glInitNames
4346 	"This method was automatically generated."
4347 	"void glInitNames();"
4348 	<cdecl: void 'glInitNames' (void) module: 'GL'>
4349 	^self externalCallFailed! !
4350 
4351 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4352 glInterleavedArrays: format with: stride with: pointer
4353 	"This method was automatically generated."
4354 	"void glInterleavedArrays(GLenum format, GLsizei stride, GLvoid* pointer);"
4355 	<cdecl: void 'glInterleavedArrays' (ulong long void*) module: 'GL'>
4356 	^self externalCallFailed! !
4357 
4358 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4359 glIsEnabled: cap
4360 	"This method was automatically generated."
4361 	"GLboolean glIsEnabled(GLenum cap);"
4362 	<cdecl: bool 'glIsEnabled' (ulong) module: 'GL'>
4363 	^self externalCallFailed! !
4364 
4365 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4366 glIsList: list
4367 	"This method was automatically generated."
4368 	"GLboolean glIsList(GLuint list);"
4369 	<cdecl: bool 'glIsList' (ulong) module: 'GL'>
4370 	^self externalCallFailed! !
4371 
4372 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4373 glIsTexture: texture
4374 	"This method was automatically generated."
4375 	"GLboolean glIsTexture(GLuint texture);"
4376 	<cdecl: bool 'glIsTexture' (ulong) module: 'GL'>
4377 	^self externalCallFailed! !
4378 
4379 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4380 glIsTextureEXT: texture
4381 	"This method was automatically generated."
4382 	"GLboolean glIsTextureEXT(GLuint texture);"
4383 	<cdecl: bool 'glIsTextureEXT' (ulong) module: 'GL'>
4384 	^self externalCallFailed! !
4385 
4386 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4387 glLightModelf: pname with: param
4388 	"This method was automatically generated."
4389 	"void glLightModelf(GLenum pname, GLfloat param);"
4390 	<cdecl: void 'glLightModelf' (ulong float) module: 'GL'>
4391 	^self externalCallFailed! !
4392 
4393 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4394 glLightModelfv: pname with: params
4395 	"This method was automatically generated."
4396 	"void glLightModelfv(GLenum pname, GLfloat* params);"
4397 	<cdecl: void 'glLightModelfv' (ulong float*) module: 'GL'>
4398 	^self externalCallFailed! !
4399 
4400 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4401 glLightModeli: pname with: param
4402 	"This method was automatically generated."
4403 	"void glLightModeli(GLenum pname, GLint param);"
4404 	<cdecl: void 'glLightModeli' (ulong long) module: 'GL'>
4405 	^self externalCallFailed! !
4406 
4407 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4408 glLightModeliv: pname with: params
4409 	"This method was automatically generated."
4410 	"void glLightModeliv(GLenum pname, GLint* params);"
4411 	<cdecl: void 'glLightModeliv' (ulong long*) module: 'GL'>
4412 	^self externalCallFailed! !
4413 
4414 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4415 glLightf: light with: pname with: param
4416 	"This method was automatically generated."
4417 	"void glLightf(GLenum light, GLenum pname, GLfloat param);"
4418 	<cdecl: void 'glLightf' (ulong ulong float) module: 'GL'>
4419 	^self externalCallFailed! !
4420 
4421 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4422 glLightfv: light with: pname with: params
4423 	"This method was automatically generated."
4424 	"void glLightfv(GLenum light, GLenum pname, GLfloat* params);"
4425 	<cdecl: void 'glLightfv' (ulong ulong float*) module: 'GL'>
4426 	^self externalCallFailed! !
4427 
4428 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4429 glLighti: light with: pname with: param
4430 	"This method was automatically generated."
4431 	"void glLighti(GLenum light, GLenum pname, GLint param);"
4432 	<cdecl: void 'glLighti' (ulong ulong long) module: 'GL'>
4433 	^self externalCallFailed! !
4434 
4435 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4436 glLightiv: light with: pname with: params
4437 	"This method was automatically generated."
4438 	"void glLightiv(GLenum light, GLenum pname, GLint* params);"
4439 	<cdecl: void 'glLightiv' (ulong ulong long*) module: 'GL'>
4440 	^self externalCallFailed! !
4441 
4442 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4443 glLineStipple: factor with: pattern
4444 	"This method was automatically generated."
4445 	"void glLineStipple(GLint factor, GLushort pattern);"
4446 	<cdecl: void 'glLineStipple' (long ushort) module: 'GL'>
4447 	^self externalCallFailed! !
4448 
4449 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4450 glLineWidth: width
4451 	"This method was automatically generated."
4452 	"void glLineWidth(GLfloat width);"
4453 	<cdecl: void 'glLineWidth' (float) module: 'GL'>
4454 	^self externalCallFailed! !
4455 
4456 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4457 glListBase: base
4458 	"This method was automatically generated."
4459 	"void glListBase(GLuint base);"
4460 	<cdecl: void 'glListBase' (ulong) module: 'GL'>
4461 	^self externalCallFailed! !
4462 
4463 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4464 glLoadIdentity
4465 	"This method was automatically generated."
4466 	"void glLoadIdentity();"
4467 	<cdecl: void 'glLoadIdentity' (void) module: 'GL'>
4468 	^self externalCallFailed! !
4469 
4470 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4471 glLoadMatrixd: m
4472 	"This method was automatically generated."
4473 	"void glLoadMatrixd(GLdouble* m);"
4474 	<cdecl: void 'glLoadMatrixd' (double*) module: 'GL'>
4475 	^self externalCallFailed! !
4476 
4477 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4478 glLoadMatrixf: m
4479 	"This method was automatically generated."
4480 	"void glLoadMatrixf(GLfloat* m);"
4481 	<cdecl: void 'glLoadMatrixf' (float*) module: 'GL'>
4482 	^self externalCallFailed! !
4483 
4484 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4485 glLoadName: name
4486 	"This method was automatically generated."
4487 	"void glLoadName(GLuint name);"
4488 	<cdecl: void 'glLoadName' (ulong) module: 'GL'>
4489 	^self externalCallFailed! !
4490 
4491 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4492 glLockArraysEXT: first with: count
4493 	"This method was automatically generated."
4494 	"void glLockArraysEXT(GLint first, GLsizei count);"
4495 	<cdecl: void 'glLockArraysEXT' (long long) module: 'GL'>
4496 	^self externalCallFailed! !
4497 
4498 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4499 glLogicOp: opcode
4500 	"This method was automatically generated."
4501 	"void glLogicOp(GLenum opcode);"
4502 	<cdecl: void 'glLogicOp' (ulong) module: 'GL'>
4503 	^self externalCallFailed! !
4504 
4505 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4506 glMap1d: target with: u1 with: u2 with: stride with: order with: points
4507 	"This method was automatically generated."
4508 	"void glMap1d(GLenum target, GLdouble u1, GLdouble u2, GLint stride, GLint order, GLdouble* points);"
4509 	<cdecl: void 'glMap1d' (ulong double double long long double*) module: 'GL'>
4510 	^self externalCallFailed! !
4511 
4512 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4513 glMap1f: target with: u1 with: u2 with: stride with: order with: points
4514 	"This method was automatically generated."
4515 	"void glMap1f(GLenum target, GLfloat u1, GLfloat u2, GLint stride, GLint order, GLfloat* points);"
4516 	<cdecl: void 'glMap1f' (ulong float float long long float*) module: 'GL'>
4517 	^self externalCallFailed! !
4518 
4519 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4520 glMap2d: target with: u1 with: u2 with: ustride with: uorder with: v1 with: v2 with: vstride with: vorder with: points
4521 	"This method was automatically generated."
4522 	"void glMap2d(GLenum target, GLdouble u1, GLdouble u2, GLint ustride, GLint uorder, GLdouble v1, GLdouble v2, GLint vstride, GLint vorder, GLdouble* points);"
4523 	<cdecl: void 'glMap2d' (ulong double double long long double double long long double*) module: 'GL'>
4524 	^self externalCallFailed! !
4525 
4526 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4527 glMap2f: target with: u1 with: u2 with: ustride with: uorder with: v1 with: v2 with: vstride with: vorder with: points
4528 	"This method was automatically generated."
4529 	"void glMap2f(GLenum target, GLfloat u1, GLfloat u2, GLint ustride, GLint uorder, GLfloat v1, GLfloat v2, GLint vstride, GLint vorder, GLfloat* points);"
4530 	<cdecl: void 'glMap2f' (ulong float float long long float float long long float*) module: 'GL'>
4531 	^self externalCallFailed! !
4532 
4533 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4534 glMapGrid1d: un with: u1 with: u2
4535 	"This method was automatically generated."
4536 	"void glMapGrid1d(GLint un, GLdouble u1, GLdouble u2);"
4537 	<cdecl: void 'glMapGrid1d' (long double double) module: 'GL'>
4538 	^self externalCallFailed! !
4539 
4540 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4541 glMapGrid1f: un with: u1 with: u2
4542 	"This method was automatically generated."
4543 	"void glMapGrid1f(GLint un, GLfloat u1, GLfloat u2);"
4544 	<cdecl: void 'glMapGrid1f' (long float float) module: 'GL'>
4545 	^self externalCallFailed! !
4546 
4547 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4548 glMapGrid2d: un with: u1 with: u2 with: vn with: v1 with: v2
4549 	"This method was automatically generated."
4550 	"void glMapGrid2d(GLint un, GLdouble u1, GLdouble u2, GLint vn, GLdouble v1, GLdouble v2);"
4551 	<cdecl: void 'glMapGrid2d' (long double double long double double) module: 'GL'>
4552 	^self externalCallFailed! !
4553 
4554 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4555 glMapGrid2f: un with: u1 with: u2 with: vn with: v1 with: v2
4556 	"This method was automatically generated."
4557 	"void glMapGrid2f(GLint un, GLfloat u1, GLfloat u2, GLint vn, GLfloat v1, GLfloat v2);"
4558 	<cdecl: void 'glMapGrid2f' (long float float long float float) module: 'GL'>
4559 	^self externalCallFailed! !
4560 
4561 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4562 glMaterialf: face with: pname with: param
4563 	"This method was automatically generated."
4564 	"void glMaterialf(GLenum face, GLenum pname, GLfloat param);"
4565 	<cdecl: void 'glMaterialf' (ulong ulong float) module: 'GL'>
4566 	^self externalCallFailed! !
4567 
4568 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4569 glMaterialfv: face with: pname with: params
4570 	"This method was automatically generated."
4571 	"void glMaterialfv(GLenum face, GLenum pname, GLfloat* params);"
4572 	<cdecl: void 'glMaterialfv' (ulong ulong float*) module: 'GL'>
4573 	^self externalCallFailed! !
4574 
4575 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4576 glMateriali: face with: pname with: param
4577 	"This method was automatically generated."
4578 	"void glMateriali(GLenum face, GLenum pname, GLint param);"
4579 	<cdecl: void 'glMateriali' (ulong ulong long) module: 'GL'>
4580 	^self externalCallFailed! !
4581 
4582 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4583 glMaterialiv: face with: pname with: params
4584 	"This method was automatically generated."
4585 	"void glMaterialiv(GLenum face, GLenum pname, GLint* params);"
4586 	<cdecl: void 'glMaterialiv' (ulong ulong long*) module: 'GL'>
4587 	^self externalCallFailed! !
4588 
4589 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4590 glMatrixMode: mode
4591 	"This method was automatically generated."
4592 	"void glMatrixMode(GLenum mode);"
4593 	<cdecl: void 'glMatrixMode' (ulong) module: 'GL'>
4594 	^self externalCallFailed! !
4595 
4596 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4597 glMinmax: target with: internalformat with: sink
4598 	"This method was automatically generated."
4599 	"void glMinmax(GLenum target, GLenum internalformat, GLboolean sink);"
4600 	<cdecl: void 'glMinmax' (ulong ulong bool) module: 'GL'>
4601 	^self externalCallFailed! !
4602 
4603 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4604 glMultMatrixd: m
4605 	"This method was automatically generated."
4606 	"void glMultMatrixd(GLdouble* m);"
4607 	<cdecl: void 'glMultMatrixd' (double*) module: 'GL'>
4608 	^self externalCallFailed! !
4609 
4610 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4611 glMultMatrixf: m
4612 	"This method was automatically generated."
4613 	"void glMultMatrixf(GLfloat* m);"
4614 	<cdecl: void 'glMultMatrixf' (float*) module: 'GL'>
4615 	^self externalCallFailed! !
4616 
4617 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4618 glMultiTexCoord1dARB: target with: s
4619 	"This method was automatically generated."
4620 	"void glMultiTexCoord1dARB(GLenum target, GLdouble s);"
4621 	<cdecl: void 'glMultiTexCoord1dARB' (ulong double) module: 'GL'>
4622 	^self externalCallFailed! !
4623 
4624 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4625 glMultiTexCoord1dvARB: target with: v
4626 	"This method was automatically generated."
4627 	"void glMultiTexCoord1dvARB(GLenum target, GLdouble* v);"
4628 	<cdecl: void 'glMultiTexCoord1dvARB' (ulong double*) module: 'GL'>
4629 	^self externalCallFailed! !
4630 
4631 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4632 glMultiTexCoord1fARB: target with: s
4633 	"This method was automatically generated."
4634 	"void glMultiTexCoord1fARB(GLenum target, GLfloat s);"
4635 	<cdecl: void 'glMultiTexCoord1fARB' (ulong float) module: 'GL'>
4636 	^self externalCallFailed! !
4637 
4638 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4639 glMultiTexCoord1fvARB: target with: v
4640 	"This method was automatically generated."
4641 	"void glMultiTexCoord1fvARB(GLenum target, GLfloat* v);"
4642 	<cdecl: void 'glMultiTexCoord1fvARB' (ulong float*) module: 'GL'>
4643 	^self externalCallFailed! !
4644 
4645 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4646 glMultiTexCoord1iARB: target with: s
4647 	"This method was automatically generated."
4648 	"void glMultiTexCoord1iARB(GLenum target, GLint s);"
4649 	<cdecl: void 'glMultiTexCoord1iARB' (ulong long) module: 'GL'>
4650 	^self externalCallFailed! !
4651 
4652 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4653 glMultiTexCoord1ivARB: target with: v
4654 	"This method was automatically generated."
4655 	"void glMultiTexCoord1ivARB(GLenum target, GLint* v);"
4656 	<cdecl: void 'glMultiTexCoord1ivARB' (ulong long*) module: 'GL'>
4657 	^self externalCallFailed! !
4658 
4659 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4660 glMultiTexCoord1sARB: target with: s
4661 	"This method was automatically generated."
4662 	"void glMultiTexCoord1sARB(GLenum target, GLshort s);"
4663 	<cdecl: void 'glMultiTexCoord1sARB' (ulong short) module: 'GL'>
4664 	^self externalCallFailed! !
4665 
4666 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4667 glMultiTexCoord1svARB: target with: v
4668 	"This method was automatically generated."
4669 	"void glMultiTexCoord1svARB(GLenum target, GLshort* v);"
4670 	<cdecl: void 'glMultiTexCoord1svARB' (ulong short*) module: 'GL'>
4671 	^self externalCallFailed! !
4672 
4673 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4674 glMultiTexCoord2dARB: target with: s with: t
4675 	"This method was automatically generated."
4676 	"void glMultiTexCoord2dARB(GLenum target, GLdouble s, GLdouble t);"
4677 	<cdecl: void 'glMultiTexCoord2dARB' (ulong double double) module: 'GL'>
4678 	^self externalCallFailed! !
4679 
4680 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4681 glMultiTexCoord2dvARB: target with: v
4682 	"This method was automatically generated."
4683 	"void glMultiTexCoord2dvARB(GLenum target, GLdouble* v);"
4684 	<cdecl: void 'glMultiTexCoord2dvARB' (ulong double*) module: 'GL'>
4685 	^self externalCallFailed! !
4686 
4687 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4688 glMultiTexCoord2fARB: target with: s with: t
4689 	"This method was automatically generated."
4690 	"void glMultiTexCoord2fARB(GLenum target, GLfloat s, GLfloat t);"
4691 	<cdecl: void 'glMultiTexCoord2fARB' (ulong float float) module: 'GL'>
4692 	^self externalCallFailed! !
4693 
4694 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4695 glMultiTexCoord2fvARB: target with: v
4696 	"This method was automatically generated."
4697 	"void glMultiTexCoord2fvARB(GLenum target, GLfloat* v);"
4698 	<cdecl: void 'glMultiTexCoord2fvARB' (ulong float*) module: 'GL'>
4699 	^self externalCallFailed! !
4700 
4701 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4702 glMultiTexCoord2iARB: target with: s with: t
4703 	"This method was automatically generated."
4704 	"void glMultiTexCoord2iARB(GLenum target, GLint s, GLint t);"
4705 	<cdecl: void 'glMultiTexCoord2iARB' (ulong long long) module: 'GL'>
4706 	^self externalCallFailed! !
4707 
4708 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4709 glMultiTexCoord2ivARB: target with: v
4710 	"This method was automatically generated."
4711 	"void glMultiTexCoord2ivARB(GLenum target, GLint* v);"
4712 	<cdecl: void 'glMultiTexCoord2ivARB' (ulong long*) module: 'GL'>
4713 	^self externalCallFailed! !
4714 
4715 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4716 glMultiTexCoord2sARB: target with: s with: t
4717 	"This method was automatically generated."
4718 	"void glMultiTexCoord2sARB(GLenum target, GLshort s, GLshort t);"
4719 	<cdecl: void 'glMultiTexCoord2sARB' (ulong short short) module: 'GL'>
4720 	^self externalCallFailed! !
4721 
4722 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4723 glMultiTexCoord2svARB: target with: v
4724 	"This method was automatically generated."
4725 	"void glMultiTexCoord2svARB(GLenum target, GLshort* v);"
4726 	<cdecl: void 'glMultiTexCoord2svARB' (ulong short*) module: 'GL'>
4727 	^self externalCallFailed! !
4728 
4729 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4730 glMultiTexCoord3dARB: target with: s with: t with: r
4731 	"This method was automatically generated."
4732 	"void glMultiTexCoord3dARB(GLenum target, GLdouble s, GLdouble t, GLdouble r);"
4733 	<cdecl: void 'glMultiTexCoord3dARB' (ulong double double double) module: 'GL'>
4734 	^self externalCallFailed! !
4735 
4736 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4737 glMultiTexCoord3dvARB: target with: v
4738 	"This method was automatically generated."
4739 	"void glMultiTexCoord3dvARB(GLenum target, GLdouble* v);"
4740 	<cdecl: void 'glMultiTexCoord3dvARB' (ulong double*) module: 'GL'>
4741 	^self externalCallFailed! !
4742 
4743 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4744 glMultiTexCoord3fARB: target with: s with: t with: r
4745 	"This method was automatically generated."
4746 	"void glMultiTexCoord3fARB(GLenum target, GLfloat s, GLfloat t, GLfloat r);"
4747 	<cdecl: void 'glMultiTexCoord3fARB' (ulong float float float) module: 'GL'>
4748 	^self externalCallFailed! !
4749 
4750 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4751 glMultiTexCoord3fvARB: target with: v
4752 	"This method was automatically generated."
4753 	"void glMultiTexCoord3fvARB(GLenum target, GLfloat* v);"
4754 	<cdecl: void 'glMultiTexCoord3fvARB' (ulong float*) module: 'GL'>
4755 	^self externalCallFailed! !
4756 
4757 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4758 glMultiTexCoord3iARB: target with: s with: t with: r
4759 	"This method was automatically generated."
4760 	"void glMultiTexCoord3iARB(GLenum target, GLint s, GLint t, GLint r);"
4761 	<cdecl: void 'glMultiTexCoord3iARB' (ulong long long long) module: 'GL'>
4762 	^self externalCallFailed! !
4763 
4764 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4765 glMultiTexCoord3ivARB: target with: v
4766 	"This method was automatically generated."
4767 	"void glMultiTexCoord3ivARB(GLenum target, GLint* v);"
4768 	<cdecl: void 'glMultiTexCoord3ivARB' (ulong long*) module: 'GL'>
4769 	^self externalCallFailed! !
4770 
4771 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4772 glMultiTexCoord3sARB: target with: s with: t with: r
4773 	"This method was automatically generated."
4774 	"void glMultiTexCoord3sARB(GLenum target, GLshort s, GLshort t, GLshort r);"
4775 	<cdecl: void 'glMultiTexCoord3sARB' (ulong short short short) module: 'GL'>
4776 	^self externalCallFailed! !
4777 
4778 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4779 glMultiTexCoord3svARB: target with: v
4780 	"This method was automatically generated."
4781 	"void glMultiTexCoord3svARB(GLenum target, GLshort* v);"
4782 	<cdecl: void 'glMultiTexCoord3svARB' (ulong short*) module: 'GL'>
4783 	^self externalCallFailed! !
4784 
4785 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4786 glMultiTexCoord4dARB: target with: s with: t with: r with: q
4787 	"This method was automatically generated."
4788 	"void glMultiTexCoord4dARB(GLenum target, GLdouble s, GLdouble t, GLdouble r, GLdouble q);"
4789 	<cdecl: void 'glMultiTexCoord4dARB' (ulong double double double double) module: 'GL'>
4790 	^self externalCallFailed! !
4791 
4792 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4793 glMultiTexCoord4dvARB: target with: v
4794 	"This method was automatically generated."
4795 	"void glMultiTexCoord4dvARB(GLenum target, GLdouble* v);"
4796 	<cdecl: void 'glMultiTexCoord4dvARB' (ulong double*) module: 'GL'>
4797 	^self externalCallFailed! !
4798 
4799 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4800 glMultiTexCoord4fARB: target with: s with: t with: r with: q
4801 	"This method was automatically generated."
4802 	"void glMultiTexCoord4fARB(GLenum target, GLfloat s, GLfloat t, GLfloat r, GLfloat q);"
4803 	<cdecl: void 'glMultiTexCoord4fARB' (ulong float float float float) module: 'GL'>
4804 	^self externalCallFailed! !
4805 
4806 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4807 glMultiTexCoord4fvARB: target with: v
4808 	"This method was automatically generated."
4809 	"void glMultiTexCoord4fvARB(GLenum target, GLfloat* v);"
4810 	<cdecl: void 'glMultiTexCoord4fvARB' (ulong float*) module: 'GL'>
4811 	^self externalCallFailed! !
4812 
4813 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4814 glMultiTexCoord4iARB: target with: s with: t with: r with: q
4815 	"This method was automatically generated."
4816 	"void glMultiTexCoord4iARB(GLenum target, GLint s, GLint t, GLint r, GLint q);"
4817 	<cdecl: void 'glMultiTexCoord4iARB' (ulong long long long long) module: 'GL'>
4818 	^self externalCallFailed! !
4819 
4820 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4821 glMultiTexCoord4ivARB: target with: v
4822 	"This method was automatically generated."
4823 	"void glMultiTexCoord4ivARB(GLenum target, GLint* v);"
4824 	<cdecl: void 'glMultiTexCoord4ivARB' (ulong long*) module: 'GL'>
4825 	^self externalCallFailed! !
4826 
4827 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4828 glMultiTexCoord4sARB: target with: s with: t with: r with: q
4829 	"This method was automatically generated."
4830 	"void glMultiTexCoord4sARB(GLenum target, GLshort s, GLshort t, GLshort r, GLshort q);"
4831 	<cdecl: void 'glMultiTexCoord4sARB' (ulong short short short short) module: 'GL'>
4832 	^self externalCallFailed! !
4833 
4834 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4835 glMultiTexCoord4svARB: target with: v
4836 	"This method was automatically generated."
4837 	"void glMultiTexCoord4svARB(GLenum target, GLshort* v);"
4838 	<cdecl: void 'glMultiTexCoord4svARB' (ulong short*) module: 'GL'>
4839 	^self externalCallFailed! !
4840 
4841 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4842 glNewList: list with: mode
4843 	"This method was automatically generated."
4844 	"void glNewList(GLuint list, GLenum mode);"
4845 	<cdecl: void 'glNewList' (ulong ulong) module: 'GL'>
4846 	^self externalCallFailed! !
4847 
4848 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4849 glNormal3b: nx with: ny with: nz
4850 	"This method was automatically generated."
4851 	"void glNormal3b(GLbyte nx, GLbyte ny, GLbyte nz);"
4852 	<cdecl: void 'glNormal3b' (byte byte byte) module: 'GL'>
4853 	^self externalCallFailed! !
4854 
4855 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:48'!
4856 glNormal3bv: v
4857 	"This method was automatically generated."
4858 	"void glNormal3bv(GLbyte* v);"
4859 	<cdecl: void 'glNormal3bv' (byte*) module: 'GL'>
4860 	^self externalCallFailed! !
4861 
4862 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4863 glNormal3d: nx with: ny with: nz
4864 	"This method was automatically generated."
4865 	"void glNormal3d(GLdouble nx, GLdouble ny, GLdouble nz);"
4866 	<cdecl: void 'glNormal3d' (double double double) module: 'GL'>
4867 	^self externalCallFailed! !
4868 
4869 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4870 glNormal3dv: v
4871 	"This method was automatically generated."
4872 	"void glNormal3dv(GLdouble* v);"
4873 	<cdecl: void 'glNormal3dv' (double*) module: 'GL'>
4874 	^self externalCallFailed! !
4875 
4876 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4877 glNormal3f: nx with: ny with: nz
4878 	"This method was automatically generated."
4879 	"void glNormal3f(GLfloat nx, GLfloat ny, GLfloat nz);"
4880 	<cdecl: void 'glNormal3f' (float float float) module: 'GL'>
4881 	^self externalCallFailed! !
4882 
4883 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4884 glNormal3fv: v
4885 	"This method was automatically generated."
4886 	"void glNormal3fv(GLfloat* v);"
4887 	<cdecl: void 'glNormal3fv' (float*) module: 'GL'>
4888 	^self externalCallFailed! !
4889 
4890 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4891 glNormal3i: nx with: ny with: nz
4892 	"This method was automatically generated."
4893 	"void glNormal3i(GLint nx, GLint ny, GLint nz);"
4894 	<cdecl: void 'glNormal3i' (long long long) module: 'GL'>
4895 	^self externalCallFailed! !
4896 
4897 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4898 glNormal3iv: v
4899 	"This method was automatically generated."
4900 	"void glNormal3iv(GLint* v);"
4901 	<cdecl: void 'glNormal3iv' (long*) module: 'GL'>
4902 	^self externalCallFailed! !
4903 
4904 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4905 glNormal3s: nx with: ny with: nz
4906 	"This method was automatically generated."
4907 	"void glNormal3s(GLshort nx, GLshort ny, GLshort nz);"
4908 	<cdecl: void 'glNormal3s' (short short short) module: 'GL'>
4909 	^self externalCallFailed! !
4910 
4911 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4912 glNormal3sv: v
4913 	"This method was automatically generated."
4914 	"void glNormal3sv(GLshort* v);"
4915 	<cdecl: void 'glNormal3sv' (short*) module: 'GL'>
4916 	^self externalCallFailed! !
4917 
4918 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4919 glNormalPointer: type with: stride with: pointer
4920 	"This method was automatically generated."
4921 	"void glNormalPointer(GLenum type, GLsizei stride, GLvoid* pointer);"
4922 	<cdecl: void 'glNormalPointer' (ulong long void*) module: 'GL'>
4923 	^self externalCallFailed! !
4924 
4925 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4926 glNormalPointerEXT: type with: stride with: count with: pointer
4927 	"This method was automatically generated."
4928 	"void glNormalPointerEXT(GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
4929 	<cdecl: void 'glNormalPointerEXT' (ulong long long void*) module: 'GL'>
4930 	^self externalCallFailed! !
4931 
4932 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4933 glOrtho: left with: right with: bottom with: top with: zNear with: zFar
4934 	"This method was automatically generated."
4935 	"void glOrtho(GLdouble left, GLdouble right, GLdouble bottom, GLdouble top, GLdouble zNear, GLdouble zFar);"
4936 	<cdecl: void 'glOrtho' (double double double double double double) module: 'GL'>
4937 	^self externalCallFailed! !
4938 
4939 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4940 glPassThrough: token
4941 	"This method was automatically generated."
4942 	"void glPassThrough(GLfloat token);"
4943 	<cdecl: void 'glPassThrough' (float) module: 'GL'>
4944 	^self externalCallFailed! !
4945 
4946 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4947 glPixelMapfv: map with: mapsize with: values
4948 	"This method was automatically generated."
4949 	"void glPixelMapfv(GLenum map, GLint mapsize, GLfloat* values);"
4950 	<cdecl: void 'glPixelMapfv' (ulong long float*) module: 'GL'>
4951 	^self externalCallFailed! !
4952 
4953 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4954 glPixelMapuiv: map with: mapsize with: values
4955 	"This method was automatically generated."
4956 	"void glPixelMapuiv(GLenum map, GLint mapsize, GLuint* values);"
4957 	<cdecl: void 'glPixelMapuiv' (ulong long ulong*) module: 'GL'>
4958 	^self externalCallFailed! !
4959 
4960 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4961 glPixelMapusv: map with: mapsize with: values
4962 	"This method was automatically generated."
4963 	"void glPixelMapusv(GLenum map, GLint mapsize, GLushort* values);"
4964 	<cdecl: void 'glPixelMapusv' (ulong long ushort*) module: 'GL'>
4965 	^self externalCallFailed! !
4966 
4967 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4968 glPixelStoref: pname with: param
4969 	"This method was automatically generated."
4970 	"void glPixelStoref(GLenum pname, GLfloat param);"
4971 	<cdecl: void 'glPixelStoref' (ulong float) module: 'GL'>
4972 	^self externalCallFailed! !
4973 
4974 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4975 glPixelStorei: pname with: param
4976 	"This method was automatically generated."
4977 	"void glPixelStorei(GLenum pname, GLint param);"
4978 	<cdecl: void 'glPixelStorei' (ulong long) module: 'GL'>
4979 	^self externalCallFailed! !
4980 
4981 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4982 glPixelTransferf: pname with: param
4983 	"This method was automatically generated."
4984 	"void glPixelTransferf(GLenum pname, GLfloat param);"
4985 	<cdecl: void 'glPixelTransferf' (ulong float) module: 'GL'>
4986 	^self externalCallFailed! !
4987 
4988 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4989 glPixelTransferi: pname with: param
4990 	"This method was automatically generated."
4991 	"void glPixelTransferi(GLenum pname, GLint param);"
4992 	<cdecl: void 'glPixelTransferi' (ulong long) module: 'GL'>
4993 	^self externalCallFailed! !
4994 
4995 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
4996 glPixelZoom: xfactor with: yfactor
4997 	"This method was automatically generated."
4998 	"void glPixelZoom(GLfloat xfactor, GLfloat yfactor);"
4999 	<cdecl: void 'glPixelZoom' (float float) module: 'GL'>
5000 	^self externalCallFailed! !
5001 
5002 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5003 glPointSize: size
5004 	"This method was automatically generated."
5005 	"void glPointSize(GLfloat size);"
5006 	<cdecl: void 'glPointSize' (float) module: 'GL'>
5007 	^self externalCallFailed! !
5008 
5009 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5010 glPolygonMode: face with: mode
5011 	"This method was automatically generated."
5012 	"void glPolygonMode(GLenum face, GLenum mode);"
5013 	<cdecl: void 'glPolygonMode' (ulong ulong) module: 'GL'>
5014 	^self externalCallFailed! !
5015 
5016 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5017 glPolygonOffset: factor with: units
5018 	"This method was automatically generated."
5019 	"void glPolygonOffset(GLfloat factor, GLfloat units);"
5020 	<cdecl: void 'glPolygonOffset' (float float) module: 'GL'>
5021 	^self externalCallFailed! !
5022 
5023 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5024 glPolygonStipple: mask
5025 	"This method was automatically generated."
5026 	"void glPolygonStipple(GLubyte* mask);"
5027 	<cdecl: void 'glPolygonStipple' (byte*) module: 'GL'>
5028 	^self externalCallFailed! !
5029 
5030 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5031 glPopAttrib
5032 	"This method was automatically generated."
5033 	"void glPopAttrib();"
5034 	<cdecl: void 'glPopAttrib' (void) module: 'GL'>
5035 	^self externalCallFailed! !
5036 
5037 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5038 glPopClientAttrib
5039 	"This method was automatically generated."
5040 	"void glPopClientAttrib();"
5041 	<cdecl: void 'glPopClientAttrib' (void) module: 'GL'>
5042 	^self externalCallFailed! !
5043 
5044 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5045 glPopMatrix
5046 	"This method was automatically generated."
5047 	"void glPopMatrix();"
5048 	<cdecl: void 'glPopMatrix' (void) module: 'GL'>
5049 	^self externalCallFailed! !
5050 
5051 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5052 glPopName
5053 	"This method was automatically generated."
5054 	"void glPopName();"
5055 	<cdecl: void 'glPopName' (void) module: 'GL'>
5056 	^self externalCallFailed! !
5057 
5058 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5059 glPrioritizeTextures: n with: textures with: priorities
5060 	"This method was automatically generated."
5061 	"void glPrioritizeTextures(GLsizei n, GLuint* textures, GLclampf* priorities);"
5062 	<cdecl: void 'glPrioritizeTextures' (long ulong* float*) module: 'GL'>
5063 	^self externalCallFailed! !
5064 
5065 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5066 glPushAttrib: mask
5067 	"This method was automatically generated."
5068 	"void glPushAttrib(GLbitfield mask);"
5069 	<cdecl: void 'glPushAttrib' (ulong) module: 'GL'>
5070 	^self externalCallFailed! !
5071 
5072 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5073 glPushClientAttrib: mask
5074 	"This method was automatically generated."
5075 	"void glPushClientAttrib(GLbitfield mask);"
5076 	<cdecl: void 'glPushClientAttrib' (ulong) module: 'GL'>
5077 	^self externalCallFailed! !
5078 
5079 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5080 glPushMatrix
5081 	"This method was automatically generated."
5082 	"void glPushMatrix();"
5083 	<cdecl: void 'glPushMatrix' (void) module: 'GL'>
5084 	^self externalCallFailed! !
5085 
5086 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5087 glPushName: name
5088 	"This method was automatically generated."
5089 	"void glPushName(GLuint name);"
5090 	<cdecl: void 'glPushName' (ulong) module: 'GL'>
5091 	^self externalCallFailed! !
5092 
5093 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5094 glRasterPos2d: x with: y
5095 	"This method was automatically generated."
5096 	"void glRasterPos2d(GLdouble x, GLdouble y);"
5097 	<cdecl: void 'glRasterPos2d' (double double) module: 'GL'>
5098 	^self externalCallFailed! !
5099 
5100 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5101 glRasterPos2dv: v
5102 	"This method was automatically generated."
5103 	"void glRasterPos2dv(GLdouble* v);"
5104 	<cdecl: void 'glRasterPos2dv' (double*) module: 'GL'>
5105 	^self externalCallFailed! !
5106 
5107 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5108 glRasterPos2f: x with: y
5109 	"This method was automatically generated."
5110 	"void glRasterPos2f(GLfloat x, GLfloat y);"
5111 	<cdecl: void 'glRasterPos2f' (float float) module: 'GL'>
5112 	^self externalCallFailed! !
5113 
5114 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5115 glRasterPos2fv: v
5116 	"This method was automatically generated."
5117 	"void glRasterPos2fv(GLfloat* v);"
5118 	<cdecl: void 'glRasterPos2fv' (float*) module: 'GL'>
5119 	^self externalCallFailed! !
5120 
5121 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5122 glRasterPos2i: x with: y
5123 	"This method was automatically generated."
5124 	"void glRasterPos2i(GLint x, GLint y);"
5125 	<cdecl: void 'glRasterPos2i' (long long) module: 'GL'>
5126 	^self externalCallFailed! !
5127 
5128 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5129 glRasterPos2iv: v
5130 	"This method was automatically generated."
5131 	"void glRasterPos2iv(GLint* v);"
5132 	<cdecl: void 'glRasterPos2iv' (long*) module: 'GL'>
5133 	^self externalCallFailed! !
5134 
5135 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5136 glRasterPos2s: x with: y
5137 	"This method was automatically generated."
5138 	"void glRasterPos2s(GLshort x, GLshort y);"
5139 	<cdecl: void 'glRasterPos2s' (short short) module: 'GL'>
5140 	^self externalCallFailed! !
5141 
5142 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5143 glRasterPos2sv: v
5144 	"This method was automatically generated."
5145 	"void glRasterPos2sv(GLshort* v);"
5146 	<cdecl: void 'glRasterPos2sv' (short*) module: 'GL'>
5147 	^self externalCallFailed! !
5148 
5149 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5150 glRasterPos3d: x with: y with: z
5151 	"This method was automatically generated."
5152 	"void glRasterPos3d(GLdouble x, GLdouble y, GLdouble z);"
5153 	<cdecl: void 'glRasterPos3d' (double double double) module: 'GL'>
5154 	^self externalCallFailed! !
5155 
5156 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5157 glRasterPos3dv: v
5158 	"This method was automatically generated."
5159 	"void glRasterPos3dv(GLdouble* v);"
5160 	<cdecl: void 'glRasterPos3dv' (double*) module: 'GL'>
5161 	^self externalCallFailed! !
5162 
5163 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5164 glRasterPos3f: x with: y with: z
5165 	"This method was automatically generated."
5166 	"void glRasterPos3f(GLfloat x, GLfloat y, GLfloat z);"
5167 	<cdecl: void 'glRasterPos3f' (float float float) module: 'GL'>
5168 	^self externalCallFailed! !
5169 
5170 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5171 glRasterPos3fv: v
5172 	"This method was automatically generated."
5173 	"void glRasterPos3fv(GLfloat* v);"
5174 	<cdecl: void 'glRasterPos3fv' (float*) module: 'GL'>
5175 	^self externalCallFailed! !
5176 
5177 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5178 glRasterPos3i: x with: y with: z
5179 	"This method was automatically generated."
5180 	"void glRasterPos3i(GLint x, GLint y, GLint z);"
5181 	<cdecl: void 'glRasterPos3i' (long long long) module: 'GL'>
5182 	^self externalCallFailed! !
5183 
5184 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5185 glRasterPos3iv: v
5186 	"This method was automatically generated."
5187 	"void glRasterPos3iv(GLint* v);"
5188 	<cdecl: void 'glRasterPos3iv' (long*) module: 'GL'>
5189 	^self externalCallFailed! !
5190 
5191 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5192 glRasterPos3s: x with: y with: z
5193 	"This method was automatically generated."
5194 	"void glRasterPos3s(GLshort x, GLshort y, GLshort z);"
5195 	<cdecl: void 'glRasterPos3s' (short short short) module: 'GL'>
5196 	^self externalCallFailed! !
5197 
5198 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5199 glRasterPos3sv: v
5200 	"This method was automatically generated."
5201 	"void glRasterPos3sv(GLshort* v);"
5202 	<cdecl: void 'glRasterPos3sv' (short*) module: 'GL'>
5203 	^self externalCallFailed! !
5204 
5205 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5206 glRasterPos4d: x with: y with: z with: w
5207 	"This method was automatically generated."
5208 	"void glRasterPos4d(GLdouble x, GLdouble y, GLdouble z, GLdouble w);"
5209 	<cdecl: void 'glRasterPos4d' (double double double double) module: 'GL'>
5210 	^self externalCallFailed! !
5211 
5212 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5213 glRasterPos4dv: v
5214 	"This method was automatically generated."
5215 	"void glRasterPos4dv(GLdouble* v);"
5216 	<cdecl: void 'glRasterPos4dv' (double*) module: 'GL'>
5217 	^self externalCallFailed! !
5218 
5219 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5220 glRasterPos4f: x with: y with: z with: w
5221 	"This method was automatically generated."
5222 	"void glRasterPos4f(GLfloat x, GLfloat y, GLfloat z, GLfloat w);"
5223 	<cdecl: void 'glRasterPos4f' (float float float float) module: 'GL'>
5224 	^self externalCallFailed! !
5225 
5226 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5227 glRasterPos4fv: v
5228 	"This method was automatically generated."
5229 	"void glRasterPos4fv(GLfloat* v);"
5230 	<cdecl: void 'glRasterPos4fv' (float*) module: 'GL'>
5231 	^self externalCallFailed! !
5232 
5233 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5234 glRasterPos4i: x with: y with: z with: w
5235 	"This method was automatically generated."
5236 	"void glRasterPos4i(GLint x, GLint y, GLint z, GLint w);"
5237 	<cdecl: void 'glRasterPos4i' (long long long long) module: 'GL'>
5238 	^self externalCallFailed! !
5239 
5240 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5241 glRasterPos4iv: v
5242 	"This method was automatically generated."
5243 	"void glRasterPos4iv(GLint* v);"
5244 	<cdecl: void 'glRasterPos4iv' (long*) module: 'GL'>
5245 	^self externalCallFailed! !
5246 
5247 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5248 glRasterPos4s: x with: y with: z with: w
5249 	"This method was automatically generated."
5250 	"void glRasterPos4s(GLshort x, GLshort y, GLshort z, GLshort w);"
5251 	<cdecl: void 'glRasterPos4s' (short short short short) module: 'GL'>
5252 	^self externalCallFailed! !
5253 
5254 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5255 glRasterPos4sv: v
5256 	"This method was automatically generated."
5257 	"void glRasterPos4sv(GLshort* v);"
5258 	<cdecl: void 'glRasterPos4sv' (short*) module: 'GL'>
5259 	^self externalCallFailed! !
5260 
5261 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5262 glReadBuffer: mode
5263 	"This method was automatically generated."
5264 	"void glReadBuffer(GLenum mode);"
5265 	<cdecl: void 'glReadBuffer' (ulong) module: 'GL'>
5266 	^self externalCallFailed! !
5267 
5268 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5269 glReadPixels: x with: y with: width with: height with: format with: type with: pixels
5270 	"This method was automatically generated."
5271 	"void glReadPixels(GLint x, GLint y, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* pixels);"
5272 	<cdecl: void 'glReadPixels' (long long long long ulong ulong void*) module: 'GL'>
5273 	^self externalCallFailed! !
5274 
5275 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5276 glRectd: x1 with: y1 with: x2 with: y2
5277 	"This method was automatically generated."
5278 	"void glRectd(GLdouble x1, GLdouble y1, GLdouble x2, GLdouble y2);"
5279 	<cdecl: void 'glRectd' (double double double double) module: 'GL'>
5280 	^self externalCallFailed! !
5281 
5282 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5283 glRectdv: v1 with: v2
5284 	"This method was automatically generated."
5285 	"void glRectdv(GLdouble* v1, GLdouble* v2);"
5286 	<cdecl: void 'glRectdv' (double* double*) module: 'GL'>
5287 	^self externalCallFailed! !
5288 
5289 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5290 glRectf: x1 with: y1 with: x2 with: y2
5291 	"This method was automatically generated."
5292 	"void glRectf(GLfloat x1, GLfloat y1, GLfloat x2, GLfloat y2);"
5293 	<cdecl: void 'glRectf' (float float float float) module: 'GL'>
5294 	^self externalCallFailed! !
5295 
5296 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5297 glRectfv: v1 with: v2
5298 	"This method was automatically generated."
5299 	"void glRectfv(GLfloat* v1, GLfloat* v2);"
5300 	<cdecl: void 'glRectfv' (float* float*) module: 'GL'>
5301 	^self externalCallFailed! !
5302 
5303 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5304 glRecti: x1 with: y1 with: x2 with: y2
5305 	"This method was automatically generated."
5306 	"void glRecti(GLint x1, GLint y1, GLint x2, GLint y2);"
5307 	<cdecl: void 'glRecti' (long long long long) module: 'GL'>
5308 	^self externalCallFailed! !
5309 
5310 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5311 glRectiv: v1 with: v2
5312 	"This method was automatically generated."
5313 	"void glRectiv(GLint* v1, GLint* v2);"
5314 	<cdecl: void 'glRectiv' (long* long*) module: 'GL'>
5315 	^self externalCallFailed! !
5316 
5317 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5318 glRects: x1 with: y1 with: x2 with: y2
5319 	"This method was automatically generated."
5320 	"void glRects(GLshort x1, GLshort y1, GLshort x2, GLshort y2);"
5321 	<cdecl: void 'glRects' (short short short short) module: 'GL'>
5322 	^self externalCallFailed! !
5323 
5324 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5325 glRectsv: v1 with: v2
5326 	"This method was automatically generated."
5327 	"void glRectsv(GLshort* v1, GLshort* v2);"
5328 	<cdecl: void 'glRectsv' (short* short*) module: 'GL'>
5329 	^self externalCallFailed! !
5330 
5331 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5332 glRenderMode: mode
5333 	"This method was automatically generated."
5334 	"GLint glRenderMode(GLenum mode);"
5335 	<cdecl: long 'glRenderMode' (ulong) module: 'GL'>
5336 	^self externalCallFailed! !
5337 
5338 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5339 glResetHistogram: target
5340 	"This method was automatically generated."
5341 	"void glResetHistogram(GLenum target);"
5342 	<cdecl: void 'glResetHistogram' (ulong) module: 'GL'>
5343 	^self externalCallFailed! !
5344 
5345 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5346 glResetMinmax: target
5347 	"This method was automatically generated."
5348 	"void glResetMinmax(GLenum target);"
5349 	<cdecl: void 'glResetMinmax' (ulong) module: 'GL'>
5350 	^self externalCallFailed! !
5351 
5352 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5353 glRotated: angle with: x with: y with: z
5354 	"This method was automatically generated."
5355 	"void glRotated(GLdouble angle, GLdouble x, GLdouble y, GLdouble z);"
5356 	<cdecl: void 'glRotated' (double double double double) module: 'GL'>
5357 	^self externalCallFailed! !
5358 
5359 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5360 glRotatef: angle with: x with: y with: z
5361 	"This method was automatically generated."
5362 	"void glRotatef(GLfloat angle, GLfloat x, GLfloat y, GLfloat z);"
5363 	<cdecl: void 'glRotatef' (float float float float) module: 'GL'>
5364 	^self externalCallFailed! !
5365 
5366 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5367 glScaled: x with: y with: z
5368 	"This method was automatically generated."
5369 	"void glScaled(GLdouble x, GLdouble y, GLdouble z);"
5370 	<cdecl: void 'glScaled' (double double double) module: 'GL'>
5371 	^self externalCallFailed! !
5372 
5373 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5374 glScalef: x with: y with: z
5375 	"This method was automatically generated."
5376 	"void glScalef(GLfloat x, GLfloat y, GLfloat z);"
5377 	<cdecl: void 'glScalef' (float float float) module: 'GL'>
5378 	^self externalCallFailed! !
5379 
5380 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5381 glScissor: x with: y with: width with: height
5382 	"This method was automatically generated."
5383 	"void glScissor(GLint x, GLint y, GLsizei width, GLsizei height);"
5384 	<cdecl: void 'glScissor' (long long long long) module: 'GL'>
5385 	^self externalCallFailed! !
5386 
5387 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5388 glSelectBuffer: size with: buffer
5389 	"This method was automatically generated."
5390 	"void glSelectBuffer(GLsizei size, GLuint* buffer);"
5391 	<cdecl: void 'glSelectBuffer' (long ulong*) module: 'GL'>
5392 	^self externalCallFailed! !
5393 
5394 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5395 glSeparableFilter2D: target with: internalformat with: width with: height with: format with: type with: row with: column
5396 	"This method was automatically generated."
5397 	"void glSeparableFilter2D(GLenum target, GLenum internalformat, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* row, GLvoid* column);"
5398 	<cdecl: void 'glSeparableFilter2D' (ulong ulong long long ulong ulong void* void*) module: 'GL'>
5399 	^self externalCallFailed! !
5400 
5401 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5402 glShadeModel: mode
5403 	"This method was automatically generated."
5404 	"void glShadeModel(GLenum mode);"
5405 	<cdecl: void 'glShadeModel' (ulong) module: 'GL'>
5406 	^self externalCallFailed! !
5407 
5408 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5409 glStencilFunc: func with: ref with: mask
5410 	"This method was automatically generated."
5411 	"void glStencilFunc(GLenum func, GLint ref, GLuint mask);"
5412 	<cdecl: void 'glStencilFunc' (ulong long ulong) module: 'GL'>
5413 	^self externalCallFailed! !
5414 
5415 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5416 glStencilMask: mask
5417 	"This method was automatically generated."
5418 	"void glStencilMask(GLuint mask);"
5419 	<cdecl: void 'glStencilMask' (ulong) module: 'GL'>
5420 	^self externalCallFailed! !
5421 
5422 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5423 glStencilOp: fail with: zfail with: zpass
5424 	"This method was automatically generated."
5425 	"void glStencilOp(GLenum fail, GLenum zfail, GLenum zpass);"
5426 	<cdecl: void 'glStencilOp' (ulong ulong ulong) module: 'GL'>
5427 	^self externalCallFailed! !
5428 
5429 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5430 glTexCoord1d: s
5431 	"This method was automatically generated."
5432 	"void glTexCoord1d(GLdouble s);"
5433 	<cdecl: void 'glTexCoord1d' (double) module: 'GL'>
5434 	^self externalCallFailed! !
5435 
5436 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5437 glTexCoord1dv: v
5438 	"This method was automatically generated."
5439 	"void glTexCoord1dv(GLdouble* v);"
5440 	<cdecl: void 'glTexCoord1dv' (double*) module: 'GL'>
5441 	^self externalCallFailed! !
5442 
5443 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5444 glTexCoord1f: s
5445 	"This method was automatically generated."
5446 	"void glTexCoord1f(GLfloat s);"
5447 	<cdecl: void 'glTexCoord1f' (float) module: 'GL'>
5448 	^self externalCallFailed! !
5449 
5450 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5451 glTexCoord1fv: v
5452 	"This method was automatically generated."
5453 	"void glTexCoord1fv(GLfloat* v);"
5454 	<cdecl: void 'glTexCoord1fv' (float*) module: 'GL'>
5455 	^self externalCallFailed! !
5456 
5457 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5458 glTexCoord1i: s
5459 	"This method was automatically generated."
5460 	"void glTexCoord1i(GLint s);"
5461 	<cdecl: void 'glTexCoord1i' (long) module: 'GL'>
5462 	^self externalCallFailed! !
5463 
5464 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5465 glTexCoord1iv: v
5466 	"This method was automatically generated."
5467 	"void glTexCoord1iv(GLint* v);"
5468 	<cdecl: void 'glTexCoord1iv' (long*) module: 'GL'>
5469 	^self externalCallFailed! !
5470 
5471 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5472 glTexCoord1s: s
5473 	"This method was automatically generated."
5474 	"void glTexCoord1s(GLshort s);"
5475 	<cdecl: void 'glTexCoord1s' (short) module: 'GL'>
5476 	^self externalCallFailed! !
5477 
5478 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5479 glTexCoord1sv: v
5480 	"This method was automatically generated."
5481 	"void glTexCoord1sv(GLshort* v);"
5482 	<cdecl: void 'glTexCoord1sv' (short*) module: 'GL'>
5483 	^self externalCallFailed! !
5484 
5485 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5486 glTexCoord2d: s with: t
5487 	"This method was automatically generated."
5488 	"void glTexCoord2d(GLdouble s, GLdouble t);"
5489 	<cdecl: void 'glTexCoord2d' (double double) module: 'GL'>
5490 	^self externalCallFailed! !
5491 
5492 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5493 glTexCoord2dv: v
5494 	"This method was automatically generated."
5495 	"void glTexCoord2dv(GLdouble* v);"
5496 	<cdecl: void 'glTexCoord2dv' (double*) module: 'GL'>
5497 	^self externalCallFailed! !
5498 
5499 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5500 glTexCoord2f: s with: t
5501 	"This method was automatically generated."
5502 	"void glTexCoord2f(GLfloat s, GLfloat t);"
5503 	<cdecl: void 'glTexCoord2f' (float float) module: 'GL'>
5504 	^self externalCallFailed! !
5505 
5506 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5507 glTexCoord2fv: v
5508 	"This method was automatically generated."
5509 	"void glTexCoord2fv(GLfloat* v);"
5510 	<cdecl: void 'glTexCoord2fv' (float*) module: 'GL'>
5511 	^self externalCallFailed! !
5512 
5513 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5514 glTexCoord2i: s with: t
5515 	"This method was automatically generated."
5516 	"void glTexCoord2i(GLint s, GLint t);"
5517 	<cdecl: void 'glTexCoord2i' (long long) module: 'GL'>
5518 	^self externalCallFailed! !
5519 
5520 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5521 glTexCoord2iv: v
5522 	"This method was automatically generated."
5523 	"void glTexCoord2iv(GLint* v);"
5524 	<cdecl: void 'glTexCoord2iv' (long*) module: 'GL'>
5525 	^self externalCallFailed! !
5526 
5527 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5528 glTexCoord2s: s with: t
5529 	"This method was automatically generated."
5530 	"void glTexCoord2s(GLshort s, GLshort t);"
5531 	<cdecl: void 'glTexCoord2s' (short short) module: 'GL'>
5532 	^self externalCallFailed! !
5533 
5534 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5535 glTexCoord2sv: v
5536 	"This method was automatically generated."
5537 	"void glTexCoord2sv(GLshort* v);"
5538 	<cdecl: void 'glTexCoord2sv' (short*) module: 'GL'>
5539 	^self externalCallFailed! !
5540 
5541 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5542 glTexCoord3d: s with: t with: r
5543 	"This method was automatically generated."
5544 	"void glTexCoord3d(GLdouble s, GLdouble t, GLdouble r);"
5545 	<cdecl: void 'glTexCoord3d' (double double double) module: 'GL'>
5546 	^self externalCallFailed! !
5547 
5548 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5549 glTexCoord3dv: v
5550 	"This method was automatically generated."
5551 	"void glTexCoord3dv(GLdouble* v);"
5552 	<cdecl: void 'glTexCoord3dv' (double*) module: 'GL'>
5553 	^self externalCallFailed! !
5554 
5555 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5556 glTexCoord3f: s with: t with: r
5557 	"This method was automatically generated."
5558 	"void glTexCoord3f(GLfloat s, GLfloat t, GLfloat r);"
5559 	<cdecl: void 'glTexCoord3f' (float float float) module: 'GL'>
5560 	^self externalCallFailed! !
5561 
5562 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5563 glTexCoord3fv: v
5564 	"This method was automatically generated."
5565 	"void glTexCoord3fv(GLfloat* v);"
5566 	<cdecl: void 'glTexCoord3fv' (float*) module: 'GL'>
5567 	^self externalCallFailed! !
5568 
5569 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5570 glTexCoord3i: s with: t with: r
5571 	"This method was automatically generated."
5572 	"void glTexCoord3i(GLint s, GLint t, GLint r);"
5573 	<cdecl: void 'glTexCoord3i' (long long long) module: 'GL'>
5574 	^self externalCallFailed! !
5575 
5576 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5577 glTexCoord3iv: v
5578 	"This method was automatically generated."
5579 	"void glTexCoord3iv(GLint* v);"
5580 	<cdecl: void 'glTexCoord3iv' (long*) module: 'GL'>
5581 	^self externalCallFailed! !
5582 
5583 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5584 glTexCoord3s: s with: t with: r
5585 	"This method was automatically generated."
5586 	"void glTexCoord3s(GLshort s, GLshort t, GLshort r);"
5587 	<cdecl: void 'glTexCoord3s' (short short short) module: 'GL'>
5588 	^self externalCallFailed! !
5589 
5590 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5591 glTexCoord3sv: v
5592 	"This method was automatically generated."
5593 	"void glTexCoord3sv(GLshort* v);"
5594 	<cdecl: void 'glTexCoord3sv' (short*) module: 'GL'>
5595 	^self externalCallFailed! !
5596 
5597 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5598 glTexCoord4d: s with: t with: r with: q
5599 	"This method was automatically generated."
5600 	"void glTexCoord4d(GLdouble s, GLdouble t, GLdouble r, GLdouble q);"
5601 	<cdecl: void 'glTexCoord4d' (double double double double) module: 'GL'>
5602 	^self externalCallFailed! !
5603 
5604 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5605 glTexCoord4dv: v
5606 	"This method was automatically generated."
5607 	"void glTexCoord4dv(GLdouble* v);"
5608 	<cdecl: void 'glTexCoord4dv' (double*) module: 'GL'>
5609 	^self externalCallFailed! !
5610 
5611 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5612 glTexCoord4f: s with: t with: r with: q
5613 	"This method was automatically generated."
5614 	"void glTexCoord4f(GLfloat s, GLfloat t, GLfloat r, GLfloat q);"
5615 	<cdecl: void 'glTexCoord4f' (float float float float) module: 'GL'>
5616 	^self externalCallFailed! !
5617 
5618 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5619 glTexCoord4fv: v
5620 	"This method was automatically generated."
5621 	"void glTexCoord4fv(GLfloat* v);"
5622 	<cdecl: void 'glTexCoord4fv' (float*) module: 'GL'>
5623 	^self externalCallFailed! !
5624 
5625 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5626 glTexCoord4i: s with: t with: r with: q
5627 	"This method was automatically generated."
5628 	"void glTexCoord4i(GLint s, GLint t, GLint r, GLint q);"
5629 	<cdecl: void 'glTexCoord4i' (long long long long) module: 'GL'>
5630 	^self externalCallFailed! !
5631 
5632 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5633 glTexCoord4iv: v
5634 	"This method was automatically generated."
5635 	"void glTexCoord4iv(GLint* v);"
5636 	<cdecl: void 'glTexCoord4iv' (long*) module: 'GL'>
5637 	^self externalCallFailed! !
5638 
5639 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5640 glTexCoord4s: s with: t with: r with: q
5641 	"This method was automatically generated."
5642 	"void glTexCoord4s(GLshort s, GLshort t, GLshort r, GLshort q);"
5643 	<cdecl: void 'glTexCoord4s' (short short short short) module: 'GL'>
5644 	^self externalCallFailed! !
5645 
5646 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5647 glTexCoord4sv: v
5648 	"This method was automatically generated."
5649 	"void glTexCoord4sv(GLshort* v);"
5650 	<cdecl: void 'glTexCoord4sv' (short*) module: 'GL'>
5651 	^self externalCallFailed! !
5652 
5653 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5654 glTexCoordPointer: size with: type with: stride with: pointer
5655 	"This method was automatically generated."
5656 	"void glTexCoordPointer(GLint size, GLenum type, GLsizei stride, GLvoid* pointer);"
5657 	<cdecl: void 'glTexCoordPointer' (long ulong long void*) module: 'GL'>
5658 	^self externalCallFailed! !
5659 
5660 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5661 glTexCoordPointerEXT: size with: type with: stride with: count with: pointer
5662 	"This method was automatically generated."
5663 	"void glTexCoordPointerEXT(GLint size, GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
5664 	<cdecl: void 'glTexCoordPointerEXT' (long ulong long long void*) module: 'GL'>
5665 	^self externalCallFailed! !
5666 
5667 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5668 glTexEnvf: target with: pname with: param
5669 	"This method was automatically generated."
5670 	"void glTexEnvf(GLenum target, GLenum pname, GLfloat param);"
5671 	<cdecl: void 'glTexEnvf' (ulong ulong float) module: 'GL'>
5672 	^self externalCallFailed! !
5673 
5674 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5675 glTexEnvfv: target with: pname with: params
5676 	"This method was automatically generated."
5677 	"void glTexEnvfv(GLenum target, GLenum pname, GLfloat* params);"
5678 	<cdecl: void 'glTexEnvfv' (ulong ulong float*) module: 'GL'>
5679 	^self externalCallFailed! !
5680 
5681 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5682 glTexEnvi: target with: pname with: param
5683 	"This method was automatically generated."
5684 	"void glTexEnvi(GLenum target, GLenum pname, GLint param);"
5685 	<cdecl: void 'glTexEnvi' (ulong ulong long) module: 'GL'>
5686 	^self externalCallFailed! !
5687 
5688 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5689 glTexEnviv: target with: pname with: params
5690 	"This method was automatically generated."
5691 	"void glTexEnviv(GLenum target, GLenum pname, GLint* params);"
5692 	<cdecl: void 'glTexEnviv' (ulong ulong long*) module: 'GL'>
5693 	^self externalCallFailed! !
5694 
5695 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5696 glTexGend: coord with: pname with: param
5697 	"This method was automatically generated."
5698 	"void glTexGend(GLenum coord, GLenum pname, GLdouble param);"
5699 	<cdecl: void 'glTexGend' (ulong ulong double) module: 'GL'>
5700 	^self externalCallFailed! !
5701 
5702 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5703 glTexGendv: coord with: pname with: params
5704 	"This method was automatically generated."
5705 	"void glTexGendv(GLenum coord, GLenum pname, GLdouble* params);"
5706 	<cdecl: void 'glTexGendv' (ulong ulong double*) module: 'GL'>
5707 	^self externalCallFailed! !
5708 
5709 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5710 glTexGenf: coord with: pname with: param
5711 	"This method was automatically generated."
5712 	"void glTexGenf(GLenum coord, GLenum pname, GLfloat param);"
5713 	<cdecl: void 'glTexGenf' (ulong ulong float) module: 'GL'>
5714 	^self externalCallFailed! !
5715 
5716 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5717 glTexGenfv: coord with: pname with: params
5718 	"This method was automatically generated."
5719 	"void glTexGenfv(GLenum coord, GLenum pname, GLfloat* params);"
5720 	<cdecl: void 'glTexGenfv' (ulong ulong float*) module: 'GL'>
5721 	^self externalCallFailed! !
5722 
5723 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5724 glTexGeni: coord with: pname with: param
5725 	"This method was automatically generated."
5726 	"void glTexGeni(GLenum coord, GLenum pname, GLint param);"
5727 	<cdecl: void 'glTexGeni' (ulong ulong long) module: 'GL'>
5728 	^self externalCallFailed! !
5729 
5730 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5731 glTexGeniv: coord with: pname with: params
5732 	"This method was automatically generated."
5733 	"void glTexGeniv(GLenum coord, GLenum pname, GLint* params);"
5734 	<cdecl: void 'glTexGeniv' (ulong ulong long*) module: 'GL'>
5735 	^self externalCallFailed! !
5736 
5737 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5738 glTexImage1D: target with: level with: internalformat with: width with: border with: format with: type with: pixels
5739 	"This method was automatically generated."
5740 	"void glTexImage1D(GLenum target, GLint level, GLint internalformat, GLsizei width, GLint border, GLenum format, GLenum type, GLvoid* pixels);"
5741 	<cdecl: void 'glTexImage1D' (ulong long long long long ulong ulong void*) module: 'GL'>
5742 	^self externalCallFailed! !
5743 
5744 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5745 glTexImage2D: target with: level with: internalformat with: width with: height with: border with: format with: type with: pixels
5746 	"This method was automatically generated."
5747 	"void glTexImage2D(GLenum target, GLint level, GLint internalformat, GLsizei width, GLsizei height, GLint border, GLenum format, GLenum type, GLvoid* pixels);"
5748 	<cdecl: void 'glTexImage2D' (ulong long long long long long ulong ulong void*) module: 'GL'>
5749 	^self externalCallFailed! !
5750 
5751 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5752 glTexImage3D: target with: level with: internalformat with: width with: height with: depth with: border with: format with: type with: pixels
5753 	"This method was automatically generated."
5754 	"void glTexImage3D(GLenum target, GLint level, GLenum internalformat, GLsizei width, GLsizei height, GLsizei depth, GLint border, GLenum format, GLenum type, GLvoid* pixels);"
5755 	<cdecl: void 'glTexImage3D' (ulong long ulong long long long long ulong ulong void*) module: 'GL'>
5756 	^self externalCallFailed! !
5757 
5758 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5759 glTexParameterf: target with: pname with: param
5760 	"This method was automatically generated."
5761 	"void glTexParameterf(GLenum target, GLenum pname, GLfloat param);"
5762 	<cdecl: void 'glTexParameterf' (ulong ulong float) module: 'GL'>
5763 	^self externalCallFailed! !
5764 
5765 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5766 glTexParameterfv: target with: pname with: params
5767 	"This method was automatically generated."
5768 	"void glTexParameterfv(GLenum target, GLenum pname, GLfloat* params);"
5769 	<cdecl: void 'glTexParameterfv' (ulong ulong float*) module: 'GL'>
5770 	^self externalCallFailed! !
5771 
5772 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5773 glTexParameteri: target with: pname with: param
5774 	"This method was automatically generated."
5775 	"void glTexParameteri(GLenum target, GLenum pname, GLint param);"
5776 	<cdecl: void 'glTexParameteri' (ulong ulong long) module: 'GL'>
5777 	^self externalCallFailed! !
5778 
5779 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5780 glTexParameteriv: target with: pname with: params
5781 	"This method was automatically generated."
5782 	"void glTexParameteriv(GLenum target, GLenum pname, GLint* params);"
5783 	<cdecl: void 'glTexParameteriv' (ulong ulong long*) module: 'GL'>
5784 	^self externalCallFailed! !
5785 
5786 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5787 glTexSubImage1D: target with: level with: xoffset with: width with: format with: type with: pixels
5788 	"This method was automatically generated."
5789 	"void glTexSubImage1D(GLenum target, GLint level, GLint xoffset, GLsizei width, GLenum format, GLenum type, GLvoid* pixels);"
5790 	<cdecl: void 'glTexSubImage1D' (ulong long long long ulong ulong void*) module: 'GL'>
5791 	^self externalCallFailed! !
5792 
5793 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5794 glTexSubImage2D: target with: level with: xoffset with: yoffset with: width with: height with: format with: type with: pixels
5795 	"This method was automatically generated."
5796 	"void glTexSubImage2D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLsizei width, GLsizei height, GLenum format, GLenum type, GLvoid* pixels);"
5797 	<cdecl: void 'glTexSubImage2D' (ulong long long long long long ulong ulong void*) module: 'GL'>
5798 	^self externalCallFailed! !
5799 
5800 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5801 glTexSubImage3D: target with: level with: xoffset with: yoffset with: zoffset with: width with: height with: depth with: format with: type with: pixels
5802 	"This method was automatically generated."
5803 	"void glTexSubImage3D(GLenum target, GLint level, GLint xoffset, GLint yoffset, GLint zoffset, GLsizei width, GLsizei height, GLsizei depth, GLenum format, GLenum type, GLvoid* pixels);"
5804 	<cdecl: void 'glTexSubImage3D' (ulong long long long long long long long ulong ulong void*) module: 'GL'>
5805 	^self externalCallFailed! !
5806 
5807 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5808 glTranslated: x with: y with: z
5809 	"This method was automatically generated."
5810 	"void glTranslated(GLdouble x, GLdouble y, GLdouble z);"
5811 	<cdecl: void 'glTranslated' (double double double) module: 'GL'>
5812 	^self externalCallFailed! !
5813 
5814 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5815 glTranslatef: x with: y with: z
5816 	"This method was automatically generated."
5817 	"void glTranslatef(GLfloat x, GLfloat y, GLfloat z);"
5818 	<cdecl: void 'glTranslatef' (float float float) module: 'GL'>
5819 	^self externalCallFailed! !
5820 
5821 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5822 glUnlockArraysEXT
5823 	"This method was automatically generated."
5824 	"void glUnlockArraysEXT();"
5825 	<cdecl: void 'glUnlockArraysEXT' (void) module: 'GL'>
5826 	^self externalCallFailed! !
5827 
5828 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5829 glVertex2d: x with: y
5830 	"This method was automatically generated."
5831 	"void glVertex2d(GLdouble x, GLdouble y);"
5832 	<cdecl: void 'glVertex2d' (double double) module: 'GL'>
5833 	^self externalCallFailed! !
5834 
5835 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5836 glVertex2dv: v
5837 	"This method was automatically generated."
5838 	"void glVertex2dv(GLdouble* v);"
5839 	<cdecl: void 'glVertex2dv' (double*) module: 'GL'>
5840 	^self externalCallFailed! !
5841 
5842 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5843 glVertex2f: x with: y
5844 	"This method was automatically generated."
5845 	"void glVertex2f(GLfloat x, GLfloat y);"
5846 	<cdecl: void 'glVertex2f' (float float) module: 'GL'>
5847 	^self externalCallFailed! !
5848 
5849 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5850 glVertex2fv: v
5851 	"This method was automatically generated."
5852 	"void glVertex2fv(GLfloat* v);"
5853 	<cdecl: void 'glVertex2fv' (float*) module: 'GL'>
5854 	^self externalCallFailed! !
5855 
5856 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5857 glVertex2i: x with: y
5858 	"This method was automatically generated."
5859 	"void glVertex2i(GLint x, GLint y);"
5860 	<cdecl: void 'glVertex2i' (long long) module: 'GL'>
5861 	^self externalCallFailed! !
5862 
5863 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5864 glVertex2iv: v
5865 	"This method was automatically generated."
5866 	"void glVertex2iv(GLint* v);"
5867 	<cdecl: void 'glVertex2iv' (long*) module: 'GL'>
5868 	^self externalCallFailed! !
5869 
5870 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5871 glVertex2s: x with: y
5872 	"This method was automatically generated."
5873 	"void glVertex2s(GLshort x, GLshort y);"
5874 	<cdecl: void 'glVertex2s' (short short) module: 'GL'>
5875 	^self externalCallFailed! !
5876 
5877 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5878 glVertex2sv: v
5879 	"This method was automatically generated."
5880 	"void glVertex2sv(GLshort* v);"
5881 	<cdecl: void 'glVertex2sv' (short*) module: 'GL'>
5882 	^self externalCallFailed! !
5883 
5884 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5885 glVertex3d: x with: y with: z
5886 	"This method was automatically generated."
5887 	"void glVertex3d(GLdouble x, GLdouble y, GLdouble z);"
5888 	<cdecl: void 'glVertex3d' (double double double) module: 'GL'>
5889 	^self externalCallFailed! !
5890 
5891 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5892 glVertex3dv: v
5893 	"This method was automatically generated."
5894 	"void glVertex3dv(GLdouble* v);"
5895 	<cdecl: void 'glVertex3dv' (double*) module: 'GL'>
5896 	^self externalCallFailed! !
5897 
5898 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5899 glVertex3f: x with: y with: z
5900 	"This method was automatically generated."
5901 	"void glVertex3f(GLfloat x, GLfloat y, GLfloat z);"
5902 	<cdecl: void 'glVertex3f' (float float float) module: 'GL'>
5903 	^self externalCallFailed! !
5904 
5905 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5906 glVertex3fv: v
5907 	"This method was automatically generated."
5908 	"void glVertex3fv(GLfloat* v);"
5909 	<cdecl: void 'glVertex3fv' (float*) module: 'GL'>
5910 	^self externalCallFailed! !
5911 
5912 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5913 glVertex3i: x with: y with: z
5914 	"This method was automatically generated."
5915 	"void glVertex3i(GLint x, GLint y, GLint z);"
5916 	<cdecl: void 'glVertex3i' (long long long) module: 'GL'>
5917 	^self externalCallFailed! !
5918 
5919 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5920 glVertex3iv: v
5921 	"This method was automatically generated."
5922 	"void glVertex3iv(GLint* v);"
5923 	<cdecl: void 'glVertex3iv' (long*) module: 'GL'>
5924 	^self externalCallFailed! !
5925 
5926 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5927 glVertex3s: x with: y with: z
5928 	"This method was automatically generated."
5929 	"void glVertex3s(GLshort x, GLshort y, GLshort z);"
5930 	<cdecl: void 'glVertex3s' (short short short) module: 'GL'>
5931 	^self externalCallFailed! !
5932 
5933 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5934 glVertex3sv: v
5935 	"This method was automatically generated."
5936 	"void glVertex3sv(GLshort* v);"
5937 	<cdecl: void 'glVertex3sv' (short*) module: 'GL'>
5938 	^self externalCallFailed! !
5939 
5940 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5941 glVertex4d: x with: y with: z with: w
5942 	"This method was automatically generated."
5943 	"void glVertex4d(GLdouble x, GLdouble y, GLdouble z, GLdouble w);"
5944 	<cdecl: void 'glVertex4d' (double double double double) module: 'GL'>
5945 	^self externalCallFailed! !
5946 
5947 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5948 glVertex4dv: v
5949 	"This method was automatically generated."
5950 	"void glVertex4dv(GLdouble* v);"
5951 	<cdecl: void 'glVertex4dv' (double*) module: 'GL'>
5952 	^self externalCallFailed! !
5953 
5954 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5955 glVertex4f: x with: y with: z with: w
5956 	"This method was automatically generated."
5957 	"void glVertex4f(GLfloat x, GLfloat y, GLfloat z, GLfloat w);"
5958 	<cdecl: void 'glVertex4f' (float float float float) module: 'GL'>
5959 	^self externalCallFailed! !
5960 
5961 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5962 glVertex4fv: v
5963 	"This method was automatically generated."
5964 	"void glVertex4fv(GLfloat* v);"
5965 	<cdecl: void 'glVertex4fv' (float*) module: 'GL'>
5966 	^self externalCallFailed! !
5967 
5968 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5969 glVertex4i: x with: y with: z with: w
5970 	"This method was automatically generated."
5971 	"void glVertex4i(GLint x, GLint y, GLint z, GLint w);"
5972 	<cdecl: void 'glVertex4i' (long long long long) module: 'GL'>
5973 	^self externalCallFailed! !
5974 
5975 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5976 glVertex4iv: v
5977 	"This method was automatically generated."
5978 	"void glVertex4iv(GLint* v);"
5979 	<cdecl: void 'glVertex4iv' (long*) module: 'GL'>
5980 	^self externalCallFailed! !
5981 
5982 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5983 glVertex4s: x with: y with: z with: w
5984 	"This method was automatically generated."
5985 	"void glVertex4s(GLshort x, GLshort y, GLshort z, GLshort w);"
5986 	<cdecl: void 'glVertex4s' (short short short short) module: 'GL'>
5987 	^self externalCallFailed! !
5988 
5989 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5990 glVertex4sv: v
5991 	"This method was automatically generated."
5992 	"void glVertex4sv(GLshort* v);"
5993 	<cdecl: void 'glVertex4sv' (short*) module: 'GL'>
5994 	^self externalCallFailed! !
5995 
5996 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
5997 glVertexPointer: size with: type with: stride with: pointer
5998 	"This method was automatically generated."
5999 	"void glVertexPointer(GLint size, GLenum type, GLsizei stride, GLvoid* pointer);"
6000 	<cdecl: void 'glVertexPointer' (long ulong long void*) module: 'GL'>
6001 	^self externalCallFailed! !
6002 
6003 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
6004 glVertexPointerEXT: size with: type with: stride with: count with: pointer
6005 	"This method was automatically generated."
6006 	"void glVertexPointerEXT(GLint size, GLenum type, GLsizei stride, GLsizei count, GLvoid* pointer);"
6007 	<cdecl: void 'glVertexPointerEXT' (long ulong long long void*) module: 'GL'>
6008 	^self externalCallFailed! !
6009 
6010 !GLXUnixX11BE methodsFor: 'OpenGL API' stamp: 'bf 10/21/2002 19:49'!
6011 glViewport: x with: y with: width with: height
6012 	"This method was automatically generated."
6013 	"void glViewport(GLint x, GLint y, GLsizei width, GLsizei height);"
6014 	<cdecl: void 'glViewport' (long long long long) module: 'GL'>
6015 	^self externalCallFailed! !
6016 
6017 
6018 !GLXUnixX11LE methodsFor: 'intitialize' stamp: 'ikp 2/3/2003 17:00'!
6019 beginFrame
6020 	super beginFrame.
6021 	self glPixelStorei: GLUnpackLsbFirst with: 0.
6022 ! !
6023 
6024 !GLXUnixX11LE methodsFor: 'accessing' stamp: 'ikp 2/3/2003 17:01'!
6025 imagePixelType32
6026 	^GLUnsignedByte! !
6027 
6028 !GLXUnixX11LE methodsFor: 'accessing' stamp: 'ikp 2/3/2003 17:02'!
6029 texturePixelType
6030 	^GLUnsignedByte! !
6031 
6032 
6033 !SystemDictionary methodsFor: 'miscellaneous' stamp: 'ikp 2/3/2003 16:56'!
6034 windowSystemName			"Smalltalk windowSystemName"
6035 
6036 	"Answer the name of the window system currently being used for display."
6037 	^self getSystemAttribute: 1005! !
6038 
6039