1:- module(plGL,
    2	  [
    3	   glAccum/2,
    4	   glActiveTextureARB/1,
    5	   glAlphaFunc/2,
    6	   glArrayElement/1,
    7	   glBegin/1,
    8	   glBindTexture/2,
    9	   glBitmap/7,
   10	   glBlendFunc/2,
   11	   glCallList/1,
   12	   glClear/1,
   13	   glClearAccum/4,
   14	   glClearColor/4,
   15	   glClearDepth/1,
   16	   glClearIndex/1,
   17	   glClearStencil/1,
   18	   glClipPlane/2,
   19	   glColor3b/3,
   20	   glColor3bv/1,
   21	   glColor3d/3,
   22	   glColor3d/3,
   23	   glColor3dv/1,
   24	   glColor3f/3,
   25	   glColor3fv/1,
   26	   glColor3i/3,
   27	   glColor3iv/1,
   28	   glColor3s/3,
   29	   glColor3sv/1,
   30	   glColor3ub/3,
   31	   glColor3ubv/1,
   32	   glColor3ui/3,
   33	   glColor3uiv/1,
   34	   glColor3us/3,
   35	   glColor3usv/1,
   36	   glColor4b/4,
   37	   glColor4bv/1,
   38	   glColor4d/4,
   39	   glColor4dv/1,
   40	   glColor4f/4,
   41	   glColor4fv/1,
   42	   glColor4i/4,
   43	   glColor4iv/1,
   44	   glColor4s/4,
   45	   glColor4sv/1,
   46	   glColor4ub/4,
   47	   glColor4ubv/1,
   48	   glColor4ui/4,
   49	   glColor4uiv/1,
   50	   glColor4us/4,
   51	   glColor4usv/1,
   52	   glColorMask/4,
   53	   glColorMaterial/2,
   54	   glCopyColorTable/5,
   55	   glCopyPixels/5,
   56	   glCopyTexImage1D/7,
   57	   glCopyTexImage2D/8,
   58	   glCopyTexSubImage1D/6,
   59	   glCopyTexSubImage2D/8,
   60	   glCullFace/1,
   61	   glDepthFunc/1,
   62	   glDepthMask/1,
   63	   glDepthRange/2,
   64	   glDisable/1,
   65	   glDisableClientState/1,
   66	   glDrawArrays/3,
   67	   glDrawBuffer/1,
   68	   glDrawElements/4,
   69	   glDrawPixels/5,
   70	   glEnable/1,
   71	   glEnableClientState/1,
   72	   glEnd/0,
   73	   glEndList/0,
   74	   glEvalCoord1d/1,
   75	   glEvalCoord1dv/1,
   76	   glEvalCoord1f/1,
   77	   glEvalCoord1fv/1,
   78	   glEvalCoord2d/2,
   79	   glEvalCoord2dv/1,
   80	   glEvalCoord2f/2,
   81	   glEvalCoord2fv/1,
   82	   glEvalMesh1/3,
   83	   glEvalMesh2/5,
   84	   glEvalPoint1/1,
   85	   glEvalPoint2/2,
   86	   glFinish/0,
   87	   glFlush/0,
   88	   glFogf/2,
   89	   glFogi/2,
   90	   glFrontFace/1,
   91	   glFrustum/6,
   92	   glGenLists/1,
   93	   glGenTextures/2,
   94	   glGetLightfv/3,
   95	   glGetLightiv/3,
   96	   glGetMaterialfv/3,
   97	   glGetMaterialiv/3,
   98	   glHint/2,
   99	   glIndexi/1,
  100	   glIndexf/1,
  101	   glIndexMask/1,
  102	   glLightf/3,
  103	   glLighti/3,
  104	   glLightfv/3,
  105	   glLightiv/3,
  106	   glLightModelfv/2,
  107	   glLineStipple/2,
  108	   glLineWidth/1,
  109	   glLoadIdentity/0,
  110	   glLogicOp/1,
  111	   glLoadName/1,
  112	   glMaterialfv/3,
  113	   glMaterialiv/3,
  114	   glMatrixMode/1,
  115	   glMinmax/3,
  116	   glNewList/2,
  117	   glNormal3b/3,
  118	   glNormal3bv/1,
  119	   glNormal3d/3,
  120	   glNormal3dv/1,
  121	   glNormal3f/3,
  122	   glNormal3fv/1,
  123	   glNormal3i/3,
  124	   glNormal3iv/1,
  125	   glNormal3s/3,
  126	   glNormal3sv/1,
  127	   glOrtho/6,
  128	   glPixelStoref/2,
  129	   glPixelStorei/2,
  130	   glPointSize/1,
  131	   glPolygonMode/2,
  132	   glPolygonOffset/2,
  133	   glPopAttrib/0,
  134	   glPopClientAttrib/0,
  135	   glPopMatrix/0,
  136	   glPopName/0,
  137	   glPushAttrib/1,
  138	   glPushClientAttrib/1,
  139	   glPushMatrix/0,
  140	   glPushName/1,
  141	   glRasterPos2d/2,
  142	   glRasterPos2dv/1,
  143	   glRasterPos2f/2,
  144	   glRasterPos2fv/1,
  145	   glRasterPos2i/2,
  146	   glRasterPos2iv/1,
  147	   glRasterPos2s/2,
  148	   glRasterPos2sv/1,
  149	   glRasterPos3d/3,
  150	   glRasterPos3dv/1,
  151	   glRasterPos3f/3,
  152	   glRasterPos3fv/1,
  153	   glRasterPos3i/3,
  154	   glRasterPos3iv/1,
  155	   glRasterPos3s/3,
  156	   glRasterPos3sv/1,
  157	   glRasterPos4d/4,
  158	   glRasterPos4dv/1,
  159	   glRasterPos4f/4,
  160	   glRasterPos4fv/1,
  161	   glRasterPos4i/4,
  162	   glRasterPos4iv/1,
  163	   glRasterPos4s/4,
  164	   glRasterPos4sv/1,
  165	   glReadBuffer/1,
  166	   glRectf/4,
  167	   glRenderMode/1,
  168	   glResetMinmax/1,
  169	   glRotated/4,
  170	   glRotatef/4,
  171	   glScaled/3,
  172	   glScalef/3,
  173	   glScissor/4,
  174	   glShadeModel/1,
  175	   glStencilFunc/3,
  176	   glStencilMask/1,
  177	   glStencilOp/3,
  178	   glTexCoord1d/1,
  179	   glTexCoord1dv/1,
  180	   glTexCoord1f/1,
  181	   glTexCoord1fv/1,
  182	   glTexCoord1i/1,
  183	   glTexCoord1iv/1,
  184	   glTexCoord1s/1,
  185	   glTexCoord1sv/1,
  186	   glTexCoord2d/2,
  187	   glTexCoord2dv/1,
  188	   glTexCoord2f/2,
  189	   glTexCoord2fv/1,
  190	   glTexCoord2i/2,
  191	   glTexCoord2iv/1,
  192	   glTexCoord2s/2,
  193	   glTexCoord2sv/1,
  194	   glTexCoord3d/3,
  195	   glTexCoord3dv/1,
  196	   glTexCoord3f/3,
  197	   glTexCoord3fv/1,
  198	   glTexCoord3i/3,
  199	   glTexCoord3iv/1,
  200	   glTexCoord3s/3,
  201	   glTexCoord3sv/1,
  202	   glTexCoord4d/4,
  203	   glTexCoord4dv/1,
  204	   glTexCoord4f/4,
  205	   glTexCoord4fv/1,
  206	   glTexCoord4i/4,
  207	   glTexCoord4iv/1,
  208	   glTexCoord4s/4,
  209	   glTexCoord4sv/1,
  210	   glTexImage1D/8,
  211	   glTexImage2D/9,
  212	   glTexParameteri/3,
  213	   glTexSubImage1D/7,
  214	   glTexSubImage2D/9,
  215	   glTexSubImage3D/11,
  216	   glTranslated/3,
  217	   glTranslatef/3,
  218	   glVertex2d/2,
  219	   glVertex2dv/1,
  220	   glVertex2f/2,
  221	   glVertex2fv/1,
  222	   glVertex2i/2,
  223	   glVertex2iv/1,
  224	   glVertex2s/2,
  225	   glVertex2sv/1,
  226	   glVertex3d/3,
  227	   glVertex3dv/1,
  228	   glVertex3f/3,
  229	   glVertex3fv/1,
  230	   glVertex3i/3,
  231	   glVertex3iv/1,
  232	   glVertex3s/3,
  233	   glVertex3sv/1,
  234	   glVertex4d/4,
  235	   glVertex4dv/1,
  236	   glVertex4f/4,
  237	   glVertex4fv/1,
  238	   glVertex4i/4,
  239	   glVertex4iv/1,
  240	   glVertex4s/4,
  241	   glVertex4sv/1,
  242	   glVertexPointer/4,
  243	   glViewport/4
  244	  ]).

OpenGL Interface

This module is the opengl extension of the Prolog OpenGL Interface (plOpengL)

author
- Jan Tatham
version
- 0.5.0
license
- LGPL */
 glAccum(+Operation, +Value)
Operates on the accumulation buffer.
Operation
Specifies the accumulation buffer operation. Symbolic constants kGL_LOAD, kGL_ACCUM, kGL_MULT, kGL_ADD, and kGL_RETURN are accepted.
Value
Specifies a floating-point value used in the accumulation buffer operation. The Operation parameter determines how Value is used.
  269glAccum(Operation,Value):-
  270	float(Value),
  271	c_glAccum(Operation,Value).
 glActiveTextureARB(+Texture)
Specify which texture unit is active.
Texture
Specifies which texture unit to make active.
  279glActiveTextureARB(Texture):-
  280	c_glActiveTextureARB(Texture).
 glAlphaFunc(+Func, +Ref)
Specify the alpha test function.
Func
Specifies the alpha comparison function. Symbolic constants kGL_NEVER, kGL_LESS, kGL_EQUAL, kGL_LEQUAL, kGL_GREATER, kGL_NOTEQUAL, kGL_GEQUAL, and kGL_ALWAYS are accepted. The default function is kGL_ALWAYS.
Ref
Specifies the reference value to which incoming alpha values are compared. This value is clamped to the range 0 (zero) through 1 (one), where 0 represents the lowest possible alpha value, and 1 the highest possible value. The default reference is 0.
  297glAlphaFunc(Func, Ref):-
  298	float(Ref),
  299	c_glAlphaFunc(Func, Ref).
 glArrayElement(+Index)
Render a vertex using the specified vertex array element.
Index
Specifies an index into the enabled vertex data arrays.
  307glArrayElement(Index):-
  308	c_glArrayElement(Index).
 glBegin(+Mode)
Delimits the vertices of a primitive or group of like primitives.
Mode
Specifies the primitive or primitives that will be created from vertices presented between glBegin and the subsequent glEnd. Ten symbolic constants are accepted: kGL_POINTS, kGL_LINES, kGL_LINE_STRIP, kGL_LINE_LOOP, kGL_TRIANGLES, kGL_TRIANGLE_STRIP, kGL_TRIANGLE_FAN, kGL_QUADS, kGL_QUAD_STRIP, and kGL_POLYGON.
  320glBegin(Mode):-
  321	c_glBegin(Mode).
 glBindTexture(+Target, +Texture)
Binds a named texture to a texturing target.
Target
Specifies the target to which the texture is bound. Must be either kGL_TEXTURE_1D, kGL_TEXTURE_2D, kGL_TEXTURE_3D, or kGL_TEXTURE_3D_EXT.
Texture
Specifies the name of a texture.
  334glBindTexture(Target,Texture):-
  335	c_glBindTexture(Target,Texture).
 glBitmap(+W, +H, +X1, +Y1, +X2, +Y2, +Bitmap)
Draws a Bitmap
W
Specifies the pixel width of the bitmap image.
H
Specifies the pixel height of the bitmap image.
X1
Specifies the location of the x origin in the bitmap image. The x origin is measured from the lower left corner of the bitmap, with right and up being the positive axes.
Y1
Specifies the location of the y origin in the bitmap image. The y origin is measured from the lower left corner of the bitmap, with right and up being the positive axes.
X2
Specifies the x offset to be added to the current raster position after the bitmap is drawn.
Y2
Specifies the y offset to be added to the current raster position after the bitmap is drawn.
Bitmap
Specifies the address of the bitmap image.
  367glBitmap(W,H,X1,Y1,X2,Y2,Bitmap):-
  368	size(Bitmap,N),
  369	float(X1),
  370	float(Y1),
  371	float(X2),
  372	float(Y2),
  373	c_glBitmap(W,H,X1,Y1,X2,Y2,Bitmap,N).
 glBlendFunc(+SFactor, +DFactor)
Specifies pixel arithmetic.
SFactor
Specifies how the RGBA source-blending factors are computed. kGL_ONE, kGL_DST_COLOR, kGL_ONE_MINUS_DST_COLOR, kGL_SRC_ALPHA, kGL_ONE_MINUS_SRC_ALPHA, kGL_DST_ALPHA, kGL_ONE_MINUS_DST_ALPHA, kGL_CONSTANT_COLOR, kGL_CONSTANT_COLOR_EXT, kGL_ONE_MINUS_CONSTANT_COLOR, kGL_ONE_MINUS_CONSTANT_COLOR_EXT, kGL_CONSTANT_ALPHA, kGL_CONSTANT_ALPHA_EXT, kGL_ONE_MINUS_CONSTANT_ALPHA, kGL_ONE_MINUS_CONSTANT_ALPHA_EXT, and kGL_SRC_ALPHA_SATURATE. These symbolic constants are defined in the Description section. The initial value is kGL_ONE.
DFactor
Specifies how the RGBA destination-blending factors are computed. Twelve symbolic constants are accepted: kGL_ZERO, kGL_ONE, kGL_SRC_COLOR, kGL_ONE_MINUS_SRC_COLOR, kGL_SRC_ALPHA, kGL_ONE_MINUS_SRC_ALPHA, kGL_DST_ALPHA , kGL_ONE_MINUS_DST_ALPHA, kGL_CONSTANT_COLOR, kGL_CONSTANT_COLOR_EXT, kGL_ONE_MINUS_CONSTANT_COLOR, kGL_ONE_MINUS_CONSTANT_COLOR_EXT, kGL_CONSTANT_ALPHA, kGL_CONSTANT_ALPHA_EXT, kGL_ONE_MINUS_CONSTANT_ALPHA, and kGL_ONE_MINUS_CONSTANT_ALPHA_EXT. These symbolic constants are defined in the Description section. The initial value is kGL_ZERO.
  403glBlendFunc(SFactor,DFactor):-
  404	c_glBlendFunc(SFactor,DFactor).
 glCallList(+OptionList)
Execute a display list
OptionList
Specifies the integer name of the display list to be executed.
  412glCallList(OptionList) :-
  413	c_glCallList(OptionList).
 glClear(+OptionList)
Clear buffers to preset values
OptionList
Bitwise OR of masks that indicate the buffers to be cleared. The four masks are kGL_COLOR_BUFFER_BIT, kGL_DEPTH_BUFFER_BIT, kGL_ACCUM_BUFFER_BIT, and kGL_STENCIL_BUFFER_BIT.
  422glClear(OptionList):-
  423	Applied_options is OptionList,
  424	c_glClear(Applied_options).
 glClearAccum(+R, +G, +B, +A)
Specify clear values for the accumulation buffer
R
Specifies the red value used when the accumulation buffer is cleared. The default value is 0 (zero).
G
Specifies the green value used when the accumulation buffer is cleared. The default value is 0.
B
Specifies the blue value used when the accumulation buffer is cleared. The default value is 0.
A
Specifies the alpha value used when the accumulation buffer is cleared. The default value is 0.
  445glClearAccum(R,G,B,A) :-
  446	float(R),
  447	float(G),
  448	float(B),
  449	float(A),
  450	c_glClearAccum(R,G,B,A).
 glClearColor(+R, +G, +B, +A)
Specify clear values for the color buffers
R
Specifies the red value used when the accumulation buffer is cleared. The default value is 0 (zero).
G
Specifies the green value used when the accumulation buffer is cleared. The default value is 0.
B
Specifies the blue value used when the accumulation buffer is cleared. The default value is 0.
A
Specifies the alpha value used when the accumulation buffer is cleared. The default value is 0.
  471glClearColor(R,G,B,A) :-
  472	float(R),
  473	float(G),
  474	float(B),
  475	float(A),
  476	c_glClearColor(R,G,B,A).
 glClearDepth(+Depth)
Specify the clear value for the depth buffer
  480glClearDepth(Depth) :-
  481	float(Depth),
  482	c_glClearDepth(Depth).
 glClearIndex(+Index)
Specify the clear value for the color index buffers
  486glClearIndex(Index) :-
  487	float(Index),
  488	c_glClearIndex(Index).
 glClearStencil(+S)
Specify the clear value for the stencil buffer
  492glClearStencil(S):-
  493	c_glClearStencil(S).
 glClipPlane(+Plane, +Equation)
Specify a plane against which all geometry is clipped
  497glClipPlane(Plane,Equation) :-
  498	size(Equation,N),
  499	c_glClipPlane(Plane,Equation,N).
 glColor3b(+Red, +Green, +Blue)
Sets the current color.
  503glColor3b(Red,Green,Blue):-
  504	c_glColor3b(Red,Green,Blue).
 glColor3bv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  512glColor3bv(X):-
  513	c_glColor3bv(X).
 glColor3d(+Red, +Green, +Blue)
Sets the current color.
  517glColor3d(Red,Green,Blue):-
  518	float(Red),
  519	float(Green),
  520	float(Blue),
  521	c_glColor3d(Red,Green,Blue).
 glColor3dv(+X:list(float))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  529glColor3dv(X):-
  530	c_glColor3dv(X).
 glColor3f(+Red, +Green, +Blue)
Sets the current color.
  534glColor3f(Red,Green,Blue):-
  535	float(Red),
  536	float(Green),
  537	float(Blue),
  538	c_glColor3f(Red,Green,Blue).
 glColor3fv(+X:list(float))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  547glColor3fv(X):-
  548	c_glColor3fv(X).
 glColor3i(+Red, +Green, +Blue)
Sets the current color.
  552glColor3i(Red,Green,Blue):-
  553	c_glColor3i(Red,Green,Blue).
 glColor3iv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  562glColor3iv(X):-
  563	c_glColor3iv(X).
 glColor3s(+Red, +Green, +Blue)
Sets the current color.
  567glColor3s(Red,Green,Blue):-
  568	c_glColor3s(Red,Green,Blue).
 glColor3sv(+X)
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  577glColor3sv(X):-
  578	c_glColor3sv(X).
 glColor3ub(+Red, +Green, +Blue)
Sets the current color.
  582glColor3ub(Red,Green,Blue):-
  583	c_glColor3ub(Red,Green,Blue).
 glColor3ubv(+X)
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  592glColor3ubv(X):-
  593	c_glColor3ubv(X).
 glColor3ui(+Red, +Green, +Blue)
Sets the current color.
  597glColor3ui(Red,Green,Blue):-
  598	c_glColor3ui(Red,Green,Blue).
 glColor3uiv(+X)
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  607glColor3uiv(X):-
  608	c_glColor3uiv(X).
 glColor3us(+Red, +Green, +Blue)
Sets the current color.
  612glColor3us(Red,Green,Blue):-
  613	c_glColor3us(Red,Green,Blue).
 glColor3usv(+X)
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue values.
  622glColor3usv(X):-
  623	c_glColor3usv(X).
 glColor4b(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  627glColor4b(Red,Green,Blue, Alpha):-
  628	c_glColor4b(Red,Green,Blue,Alpha).
 glColor4bv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  638glColor4bv(X):-
  639	c_glColor4bv(X).
 glColor4d(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  643glColor4d(Red,Green,Blue, Alpha):-
  644	c_glColor4d(Red,Green,Blue,Alpha).
 glColor4dv(+X:list(float))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  653glColor4dv(X):-
  654	c_glColor4dv(X).
 glColor4f(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  658glColor4f(Red,Green,Blue,Alpha):-
  659	float(Red),
  660	float(Green),
  661	float(Blue),
  662	float(Alpha),
  663	c_glColor4f(Red,Green,Blue,Alpha).
 glColor4fv(+X:list(float))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  672glColor4fv(X):-
  673	c_glColor4fv(X).
 glColor4i(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  677glColor4i(Red,Green,Blue, Alpha):-
  678	c_glColor4i(Red,Green,Blue,Alpha).
 glColor4iv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  688glColor4iv(X):-
  689	c_glColor4iv(X).
 glColor4s(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  693glColor4s(Red,Green,Blue, Alpha):-
  694	c_glColor4s(Red,Green,Blue,Alpha).
 glColor4sv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  703glColor4sv(X):-
  704	c_glColor4sv(X).
 glColor4ub(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  708glColor4ub(Red,Green,Blue,Alpha):-
  709	c_glColor4ub(Red,Green,Blue,Alpha).
 glColor4ubv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  718glColor4ubv(X):-
  719	c_glColor4ubv(X).
 glColor4ui(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  723glColor4ui(Red,Green,Blue, Alpha):-
  724	c_glColor4ui(Red,Green,Blue,Alpha).
 glColor4uiv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  733glColor4uiv(X):-
  734	c_glColor4uiv(X).
 glColor4us(+Red, +Green, +Blue, +Alpha)
Sets the current color.
  738glColor4us(Red,Green,Blue, Alpha):-
  739	c_glColor4us(Red,Green,Blue,Alpha).
 glColor4usv(+X:list(number))
Sets the current color.
X
Specifies a pointer to an array that contains red, green, blue, and alpha values.
  748glColor4usv(X):-
  749	c_glColor4usv(X).
 glColorMask(+Red, +Green, +Blue, +Alpha)
Enable and disable writing of frame buffer color components
  753glColorMask(Red,Green,Blue,Alpha):-
  754	c_glColorMask(Red,Green,Blue,Alpha).
 glColorMaterial(+Face, +Mode)
Cause a material color to track the current color
  758glColorMaterial(Face, Mode):-
  759	c_glColorMaterial(Face,Mode).
 glCopyColorTable(+Target, +Format, +X, +Y, +Width)
Copy pixels into a color table
  763glCopyColorTable(Target, Format, X, Y, Width):-
  764    c_glCopyColorTable(Target, Format, X, Y, Width).
 glCopyPixels(+X, +Y, +Width, +Height, +Type)
Copy pixels in the frame buffer
  768glCopyPixels(X, Y, Width, Height, Type):-
  769    c_glCopyPixels(X, Y, Width, Height, Type).
 glCopyTexImage1D(+Target, +Level, +Internal, +X, +Y, +Width, +Border)
Copy pixels into a 1D texture image
  774glCopyTexImage1D(Target, Level, Internal, X, Y, Width, Border):-
  775    c_glCopyTexImage1D(Target, Level, Internal, X, Y, Width, Border).
 glCopyTexImage2D(+Target, +Level, +Internal, +X, +Y, +Width, +Height, +Border)
Copy pixels into a 2D texture image
  779glCopyTexImage2D(Target, Level, Internal, X, Y, Width, Height, Border):-
  780    c_glCopyTexImage2D(Target, Level, Internal, X, Y, Width, Height, Border).
 glCopyTexSubImage1D(+Target, +Level, +XOffset, +X, +Y, +Width)
Copy a one-dimensional texture subimage
  784glCopyTexSubImage1D(Target, Level, XOffset, X, Y, Width):-
  785    c_glCopyTexSubImage1D(Target, Level, XOffset, X, Y, Width).
 glCopyTexSubImage2D(+Target, +Level, +XOffset, +YOffset, +X, +Y, +Width, +Height)
Copy a two-dimensional texture subimage
  789glCopyTexSubImage2D(Target, Level, XOffset, YOffset, X, Y, Width, Height):-
  790    c_glCopyTexSubImage2D(Target, Level, XOffset, YOffset, X, Y, Width, Height).
 glCullFace(+Mode)
Specify whether front- or back-facing facets can be culled
  794glCullFace(Mode):-
  795	Mode_Eval is Mode,
  796	c_glCullFace(Mode_Eval).
 glDepthFunc(+Mode)
Specify the value used for depth buffer comparisons
  800glDepthFunc(Mode):-
  801	Mode_Eval is Mode,
  802	c_glDepthFunc(Mode_Eval).
 glDepthMask(+Flag)
Enable or disable writing into the depth buffer
  806glDepthMask(Flag):-
  807    c_glDepthMask(Flag).
 glDepthRange(+NEar, +Far)
Specify mapping of depth values from normalized device coordinates to window coordinates
  811glDepthRange(Near, Far) :-
  812    float(Near),
  813    float(Far),
  814    c_glDepthRange(Near, Far).
 glDisable(+Mode)
Enable or disable server-side GL capabilities
  818glDisable(Mode):-
  819	Mode_Eval is Mode,
  820	c_glDisable(Mode_Eval).
 glDisableClientState(+Cap)
Enables or disables an array.
  824glDisableClientState(Cap):-
  825    c_glDisableClientState(Cap).
 glDrawArrays(+Mode, +First, +Count)
Render primitives from array data
  829glDrawArrays(Mode, First, Count):-
  830    c_glDrawArrays(Mode, First, Count).
 glDrawBuffer(+Mode)
Specify which color buffers are to be drawn into
  834glDrawBuffer(Mode):-
  835    c_glDrawBuffer(Mode).
 glDrawElements(+Mode, +Count, +Type, +Indices)
Render primitives from array data
  839glDrawElements(Mode, Count, Type, Indices):-
  840    c_glDrawElements(Mode, Count, Type, Indices).
 glDrawPixels(+Width, +Height, +Format, +Type, +Data)
Write a block of pixels to the frame buffer
  844glDrawPixels(Width, Height, Format, Type, Data):-
  845    c_glDrawPixels(Width, Height, Format, Type, Data).
 glEnable(+Mode)
Enables GL capability.
  849glEnable(Mode):-
  850	Mode_Eval is Mode,
  851	c_glEnable(Mode_Eval).
 glEnableClientState(+Cap)
Enables an array.
  855glEnableClientState(Cap):-
  856    c_glEnableClientState(Cap).
 glEnd
Delimits the vertices of a primitive or group of like primitives.
  860glEnd:-
  861	c_glEnd.
 glEndList
Create or replace a display list
  865glEndList :-
  866	c_glEndList.
 glEvalCoord1d(+U)
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  870glEvalCoord1d(U) :-
  871    float(U),
  872    c_glEvalCoord1d(U).
 glEvalCoord1dv(+U)
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  876glEvalCoord1dv(U) :-
  877    c_glEvalCoord1dv(U).
 glEvalCoord1f(+U)
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  881glEvalCoord1f(U) :-
  882    float(U),
  883    c_glEvalCoord1f(U).
 glEvalCoord1fv(+U)
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  887glEvalCoord1fv(U) :-
  888    c_glEvalCoord1fv(U).
 glEvalCoord2d(+U, +V)
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  892glEvalCoord2d(U,V) :-
  893    float(U),
  894    float(V),
  895    c_glEvalCoord2d(U,V).
 glEvalCoord2dv(+U:list(float))
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  899glEvalCoord2dv(U) :-
  900    c_glEvalCoord2dv(U).
 glEvalCoord2f(+U, +V)
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  904glEvalCoord2f(U,V) :-
  905    float(U),
  906    float(V),
  907    c_glEvalCoord2f(U,V).
 glEvalCoord2fv(+U:list(float))
Evaluates enabled one-dimensional (1D) and two-dimensional (2D) maps.
  911glEvalCoord2fv(U) :-
  912    c_glEvalCoord2fv(U).
 glEvalMesh1(+Mode, +I1, +I2)
Compute a one- or two-dimensional grid of points or lines
  916glEvalMesh1(Mode,I1,I2) :-
  917    c_glEvalMesh1(Mode,I1,I2).
 glEvalMesh2(+Mode, +I1, +I2, +J1, +J2)
Compute a one- or two-dimensional grid of points or lines
  921glEvalMesh2(Mode,I1,I2,J1,J2) :-
  922    c_glEvalMesh2(Mode,I1,I2,J1,J2).
 glEvalPoint1(+I)
Generate and evaluate a single point in a mesh
  926glEvalPoint1(I) :-
  927    c_glEvalPoint1(I).
 glEvalPoint2(+I, +J)
Generate and evaluate a single point in a mesh
  931glEvalPoint2(I,J) :-
  932    c_glEvalPoint2(I,J).
 glFinish
block until all GL execution is complete
  936glFinish:-
  937	c_glFinish.
 glFlush
Force execution of GL commands in finite time
  941glFlush:-
  942	c_glFlush.
 glFogf(+PName, +Param:list(float))
Specify fog parameters
  946glFogf(PName, Param):-
  947	float(Param),
  948	c_glFogf(PName, Param).
 glFogi(+PName, +Param:list(number))
Specify fog parameters
  952glFogi(PName, Param):-
  953	c_glFogi(PName, Param).
 glFrontFace(+Mode)
Define front- and back-facing polygons
  957glFrontFace(Mode):-
  958	c_glFrontFace(Mode).
 glFrustum(+Left, +Right, +Top, +Bottom, +Near, +Far)
Multiply the current matrix by a perspective matrix
  962glFrustum(Left,Right,Top,Bottom,Near,Far):-
  963	float(Left),
  964	float(Right),
  965	float(Top),
  966	float(Bottom),
  967	float(Near),
  968	float(Far),
  969	c_glFrustum(Left,Right,Top,Bottom,Near,Far).
 glGenLists(+Range)
Generate a contiguous set of empty display lists.
  973glGenLists(Range):-
  974    c_glGenLists(Range).
 glGenTextures(+N, +TextureNames:list(number))
Generate texture names
N
Specifies the number of texture names to be generated.
TextureNames
Specifies an array in which the generated texture names are stored.
  984glGenTextures(N,TextureNames):-
  985    c_glGenTextures(N,TextureNames).
 glGetLightfv(+Light, +PName, -Params:list(float))
Return light source parameter values
  989glGetLightfv(Light, PName, Params) :-
  990    c_glGetLightfv(Light, PName, Params).
 glGetLightiv(+Light, +PName, -Params:list(number))
Return light source parameter values
  994glGetLightiv(Light, PName, Params) :-
  995    c_glGetLightiv(Light, PName, Params).
 glGetMaterialfv(+Light, +PName, -Params:list(float))
Return material parameters
  999glGetMaterialfv(Light, PName, Params) :-
 1000    c_glGetMaterialfv(Light, PName, Params).
 glGetMaterialiv(+Light, +PName, -Params:list(number))
Return material parameters
 1004glGetMaterialiv(Light, PName, Params) :-
 1005    c_glGetMaterialiv(Light, PName, Params).
 glHint(+Target, +Hint)
Specify implementation-specific hints
 1009glHint(Target,Hint):-
 1010	T is Target,
 1011	H is Hint,
 1012	c_glHint(T,H).
 glIndexi(+Index)
set the current color index.
 1016glIndexi(Index):-
 1017    c_glIndexi(Index).
 glIndexf(+Index)
set the current color index.
 1021glIndexf(Index):-
 1022    float(Index),
 1023    c_glIndexf(Index).
 glIndexMask(+Mask)
Control the writing of individual bits in the color index buffers.
 1027glIndexMask(Mask):-
 1028    c_glIndexMask(Mask).
 glLightf(+Light, +PName, +Param)
Set light source parameters.
 1032glLightf(Light, PName, Params):-
 1033	float(Light),
 1034	float(PName),
 1035	float(Params),
 1036	c_glLightf(Light, PName, Params).
 glLighti(+Light, +PName, +Param)
Set light source parameters.
 1040glLighti(Light, PName, Params):-
 1041	c_glLighti(Light, PName, Params).
 glLightfv(+Light, +PName, +Param:list(float))
Set light source parameters.
 1045glLightfv(Light, PName, Params):-
 1046	size(Params,N),
 1047	c_glLightfv(Light, PName, Params, N).
 glLightiv(+Light, +PName, +Param:list(number))
Set light source parameters.
 1051glLightiv(Light, PName, Params):-
 1052	size(Params,N),
 1053	c_glLightiv(Light, PName, Params, N).
 glLightModelfv(+PName, +Params)
Sets lighting model parameters.
 1058glLightModelfv(PName, Params:list(float)):-
 1059	size(Params,N),
 1060	c_glLightModelfv(PName, Params, N).
 glLineStipple(+Factor, +Pattern)
Specify the line stipple pattern.
 1064glLineStipple(Factor,Pattern):-
 1065	F is Factor,
 1066	P is Pattern,
 1067	c_glLineStipple(F,P).
 glLineWidth(+Width)
Specify the width of rasterized lines.
 1071glLineWidth(Width) :-
 1072	float(Width),
 1073	c_glLineWidth(Width).
 glLoadIdentity
Replaces the current matrix with the identity matrix.
 1077glLoadIdentity:-
 1078	c_glLoadIdentity.
 glLogicOp(+Opcode)
Specify a logical pixel operation for rendering.
 1082glLogicOp(Opcode) :-
 1083        c_glLogicOp(Opcode).
 glLoadName(+Name)
Load a name onto the name stack
 1087glLoadName(Name):-
 1088    c_glLoadName(Name).
 glMaterialfv(+Face, +PName, +Params:list(float))
Specifies material parameters for the lighting model.
 1092glMaterialfv(Face, PName, Params):-
 1093	size(Params,N),
 1094	c_glMaterialfv(Face, PName, Params, N).
 glMaterialiv(+Face, +PName, +Params:list(number))
Specifies material parameters for the lighting model.
 1098glMaterialiv(Face, PName, Params):-
 1099	size(Params,N),
 1100	c_glMaterialiv(Face, PName, Params, N).
 glMatrixMode(+Mode)
Specify which matrix is the current matrix.
 1104glMatrixMode(Mode):-
 1105	c_glMatrixMode(Mode).
 glMinmax(+Target, +InternalFormat, +Sink)
Define minmax table
 1109glMinmax(Target, InternalFormat, Sink):-
 1110	c_glMinmax(Target, InternalFormat, Sink).
 glNewList(+List, +Mode)
Create a display list.
 1114glNewList(List,Mode) :-
 1115	c_glNewList(List,Mode).
 glNormal3b(+X, +Y, +Z)
Set the current normal vector.
 1119glNormal3b(X,Y,Z):-
 1120	c_glNormal3b(X,Y,Z).
 glNormal3bv(+V:list(number))
Set the current normal vector
 1124glNormal3bv(V) :-
 1125	c_glNormal3bv(V).
 glNormal3d(+X, +Y, +Z)
Set the current normal vector.
 1129glNormal3d(X,Y,Z):-
 1130	float(X),
 1131	float(Y),
 1132	float(Z),
 1133	c_glNormal3d(X,Y,Z).
 glNormal3dv(+V:list(float))
Set the current normal vector
 1137glNormal3dv(V) :-
 1138	c_glNormal3dv(V).
 glNormal3f(+X, +Y, +Z)
Set the current normal vector.
 1142glNormal3f(X,Y,Z):-
 1143	float(X),
 1144	float(Y),
 1145	float(Z),
 1146	c_glNormal3f(X,Y,Z).
 glNormal3fv(+V:list(float))
Set the current normal vector
 1150glNormal3fv(V) :-
 1151	c_glNormal3fv(V).
 glNormal3i(+X, +Y, +Z)
Set the current normal vector.
 1155glNormal3i(X,Y,Z):-
 1156	c_glNormal3i(X,Y,Z).
 glNormal3iv(+V:list(number))
Set the current normal vector
 1160glNormal3iv(V) :-
 1161	c_glNormal3iv(V).
 glNormal3s(+X, +Y, +Z)
Set the current normal vector.
 1165glNormal3s(X,Y,Z):-
 1166	c_glNormal3s(X,Y,Z).
 glNormal3sv(+V:list(number))
Set the current normal vector
 1170glNormal3sv(V) :-
 1171	c_glNormal3sv(V).
 glOrtho(+Left, +Right, +Top, +Bottom, +Near, +Far)
Multiply the current matrix with an orthographic matrix.
 1175glOrtho(Left,Right,Top,Bottom,Near,Far):-
 1176	float(Left),
 1177	float(Right),
 1178	float(Top),
 1179	float(Bottom),
 1180	float(Near),
 1181	float(Far),
 1182	c_glOrtho(Left,Right,Top,Bottom,Near,Far).
 glPixelStoref(+Mode, +Param)
Set pixel storage modes.
 1186glPixelStoref(Mode,Param) :-
 1187	float(Param),
 1188        c_glPixelStoref(Mode,Param).
 glPixelStorei(+Mode, +Param)
Set pixel storage modes.
 1192glPixelStorei(Mode,Param) :-
 1193        c_glPixelStorei(Mode,Param).
 glPointSize(+Size)
Specify the diameter of rasterized points.
 1197glPointSize(Size):-
 1198	float(Size),
 1199	c_glPointSize(Size).
 glPolygonMode(+Face, +Mode)
Select a polygon rasterization mode.
 1203glPolygonMode(Face, Mode):-
 1204        c_glPolygonMode(Face, Mode).
 glPolygonOffset(+Factor, +Units)
Set the scale and units used to calculate depth values
 1208glPolygonOffset(Factor, Units):-
 1209	float(Factor),
 1210	float(Units),
 1211	c_glPolygonOffset(Factor, Units).
 glPopAttrib
Pop the server attribute stack
 1215glPopAttrib:-
 1216	c_glPopAttrib.
 glPopClientAttrib
Pop the client attribute stack.
 1220glPopClientAttrib:-
 1221	c_glPopClientAttrib.
 glPopMatrix
Pop the current matrix stack.
 1225glPopMatrix:-
 1226	c_glPopMatrix.
 glPopName
Pop the name stack.
 1230glPopName:-
 1231	c_glPopName.
 glPushAttrib(+Mask)
Push the server attribute stack.
 1235glPushAttrib(Mask):-
 1236    c_glPushAttrib(Mask).
 glPushClientAttrib(+Mask)
Push the client attribute stack.
 1240glPushClientAttrib(Mask):-
 1241    c_glPushClientAttrib(Mask).
 glPushMatrix
Push the current matrix stack.
 1245glPushMatrix:-
 1246	c_glPushMatrix.
 glPushName(+Name)
Push the name stack.
 1250glPushName(Name):-
 1251    c_glPushName(Name).
 glRasterPos2d(+X, +Y)
Specify the raster position for pixel operations.
 1255glRasterPos2d(X,Y):-
 1256    float(X),
 1257    float(Y),
 1258    c_glRasterPos2d(X,Y).
 glRasterPos2dv(+V:list(float))
Specify the raster position for pixel operations.
 1262glRasterPos2dv(V):-
 1263    c_glRasterPos2dv(V).
 glRasterPos2f(+X, +Y)
Specify the raster position for pixel operations.
 1267glRasterPos2f(X,Y):-
 1268    float(X),
 1269    float(Y),
 1270    c_glRasterPos2f(X,Y).
 glRasterPos2fv(+V:list(float))
Specify the raster position for pixel operations.
 1274glRasterPos2fv(V):-
 1275    c_glRasterPos2fv(V).
 glRasterPos2i(+X, +Y)
Specify the raster position for pixel operations.
 1279glRasterPos2i(X,Y):-
 1280    c_glRasterPos2i(X,Y).
 glRasterPos2iv(+V:list(number))
Specify the raster position for pixel operations.
 1284glRasterPos2iv(V):-
 1285    c_glRasterPos2iv(V).
 glRasterPos2s(+X, +Y)
Specify the raster position for pixel operations.
 1289glRasterPos2s(X,Y):-
 1290    c_glRasterPos2s(X,Y).
 glRasterPos2sv(+V:list(number))
Specify the raster position for pixel operations.
 1294glRasterPos2sv(V):-
 1295    c_glRasterPos2sv(V).
 glRasterPos3d(+X, +Y, +Z)
Specify the raster position for pixel operations.
 1299glRasterPos3d(X,Y,Z):-
 1300    float(X),
 1301    float(Y),
 1302    float(Z),
 1303    c_glRasterPos3d(X,Y,Z).
 glRasterPos3dv(+V:list(float))
Specify the raster position for pixel operations.
 1307glRasterPos3dv(V):-
 1308    c_glRasterPos3dv(V).
 glRasterPos3f(+X, +Y, +Z)
Specify the raster position for pixel operations.
 1312glRasterPos3f(X,Y,Z):-
 1313    float(X),
 1314    float(Y),
 1315    float(Z),
 1316    c_glRasterPos3f(X,Y,Z).
 glRasterPos3fv(+V:list(float))
Specify the raster position for pixel operations.
 1320glRasterPos3fv(V):-
 1321    c_glRasterPos3fv(V).
 glRasterPos3i(+X, +Y, +Z)
Specify the raster position for pixel operations.
 1325glRasterPos3i(X,Y,Z):-
 1326    c_glRasterPos3i(X,Y,Z).
 glRasterPos3iv(+V:list(number))
Specify the raster position for pixel operations.
 1330glRasterPos3iv(V):-
 1331    c_glRasterPos3iv(V).
 glRasterPos3s(+X, +Y, +Z)
Specify the raster position for pixel operations.
 1335glRasterPos3s(X,Y,Z):-
 1336    c_glRasterPos3s(X,Y,Z).
 glRasterPos3sv(+V:list(number))
Specify the raster position for pixel operations.
 1340glRasterPos3sv(V):-
 1341    c_glRasterPos3sv(V).
 glRasterPos4d(+X, +Y, +Z, +W)
Specify the raster position for pixel operations.
 1345glRasterPos4d(X,Y,Z,W):-
 1346    float(X),
 1347    float(Y),
 1348    float(Z),
 1349    float(W),
 1350    c_glRasterPos4d(X,Y,Z,W).
 glRasterPos4dv(+V:list(float))
Specify the raster position for pixel operations.
 1354glRasterPos4dv(V):-
 1355    c_glRasterPos4dv(V).
 glRasterPos4f(+X, +Y, +Z, +W)
Specify the raster position for pixel operations.
 1359glRasterPos4f(X,Y,Z,W):-
 1360    float(X),
 1361    float(Y),
 1362    float(Z),
 1363    float(W),
 1364    c_glRasterPos4f(X,Y,Z,W).
 glRasterPos4fv(+V:list(float))
Specify the raster position for pixel operations.
 1368glRasterPos4fv(V):-
 1369    c_glRasterPos4fv(V).
 glRasterPos4i(+X, +Y, +Z, +W)
Specify the raster position for pixel operations.
 1373glRasterPos4i(X,Y,Z,W):-
 1374    c_glRasterPos4i(X,Y,Z,W).
 glRasterPos4iv(+V:list(number))
Specify the raster position for pixel operations.
 1378glRasterPos4iv(V):-
 1379    c_glRasterPos4iv(V).
 glRasterPos4s(+X, +Y, +Z, W)
Specify the raster position for pixel operations.
 1383glRasterPos4s(X,Y,Z,W):-
 1384    c_glRasterPos4s(X,Y,Z,W).
 glRasterPos4sv(+V:list(number))
Specify the raster position for pixel operations.
 1388glRasterPos4sv(V):-
 1389    c_glRasterPos4sv(V).
 glReadBuffer(+Mode)
Select a color buffer source for pixels
 1393glReadBuffer(Mode):-
 1394    c_glReadBuffer(Mode).
 glRectf(+X1, +Y1, +X2, +Y2)
Draw a rectangle
 1398glRectf(X1,Y1,X2,Y2) :-
 1399	float(X1),
 1400	float(Y1),
 1401	float(X2),
 1402	float(Y2),
 1403	c_glRectf(X1,Y1,X2,Y2).
 glRenderMode(+Mode)
Set rasterization mode
 1407glRenderMode(Mode):-
 1408    c_glRenderMode(Mode).
 glResetMinmax(+Target)
Reset minmax table entries to initial values
 1412glResetMinmax(Target):-
 1413    c_glResetMinmax(Target).
 glRotated(+Angle, +X, +Y, +Z)
Multiply the current matrix by a rotation matrix
 1417glRotated(Angle,X,Y,Z) :-
 1418	float(Angle),
 1419	float(X),
 1420	float(Y),
 1421	float(Z),
 1422	c_glRotated(Angle,X,Y,Z).
 glRotatef(+Angle, +X, +Y, +Z)
Multiply the current matrix by a rotation matrix
 1426glRotatef(Angle,X,Y,Z) :-
 1427	float(Angle),
 1428	float(X),
 1429	float(Y),
 1430	float(Z),
 1431	c_glRotatef(Angle,X,Y,Z).
 glScaled(+X, +Y, +Z)
Multiply the current matrix by a general scaling matrix
 1435glScaled(X,Y,Z):-
 1436	float(X),
 1437	float(Y),
 1438	float(Z),
 1439	c_glScaled(X,Y,Z).
 glScalef(+X, +Y, +Z)
Multiply the current matrix by a general scaling matrix
 1443glScalef(X,Y,Z):-
 1444	float(X),
 1445	float(Y),
 1446	float(Z),
 1447	c_glScalef(X,Y,Z).
 glScissor(+X, +Y, Width, +Height)
Define the scissor box.
 1451glScissor(X,Y,Width,Height) :-
 1452    c_glScissor(X,Y,Width,Height).
 glShadeModel(+Mode)
Select flat or smooth shading.
 1456glShadeModel(Mode):-
 1457	c_glShadeModel(Mode).
 glStencilFunc(+Func, +Ref, +Mask)
Set front and back function and reference value for stencil testing/
 1461glStencilFunc(Func, Ref, Mask):-
 1462	c_glStencilFunc(Func, Ref, Mask).
 glStencilMask(+Mask)
Control the front and back writing of individual bits in the stencil planes
 1466glStencilMask(Mask):-
 1467	c_glStencilMask(Mask).
 glStencilOp(+Fail, +ZFail, +ZPass)
Set front and back stencil test actions.
 1471glStencilOp(Fail, ZFail, ZPass):-
 1472	c_glStencilOp(Fail, ZFail, ZPass).
 glTexCoord1d(+S)
Set the current texture coordinates.
 1476glTexCoord1d(S):-
 1477	float(S),
 1478	c_glTexCoord1d(S).
 glTexCoord1dv(+V:list(float))
Set the current texture coordinates.
 1482glTexCoord1dv(V):-
 1483	c_glTexCoord1dv(V).
 glTexCoord1f(+S)
Set the current texture coordinates.
 1487glTexCoord1f(S):-
 1488	float(S),
 1489	c_glTexCoord1f(S).
 glTexCoord1fv(+V:list(float))
Set the current texture coordinates.
 1493glTexCoord1fv(V):-
 1494	c_glTexCoord1fv(V).
 glTexCoord1i(+S)
Set the current texture coordinates.
 1498glTexCoord1i(S):-
 1499	c_glTexCoord1i(S).
 glTexCoord1iv(+V:list(number))
Set the current texture coordinates.
 1503glTexCoord1iv(V):-
 1504	c_glTexCoord1iv(V).
 glTexCoord1s(+S)
Set the current texture coordinates.
 1508glTexCoord1s(S):-
 1509	c_glTexCoord1s(S).
 glTexCoord1sv(+V:list(number))
Set the current texture coordinates.
 1513glTexCoord1sv(V):-
 1514	c_glTexCoord1sv(V).
 glTexCoord2d(+S, +T)
Set the current texture coordinates.
 1518glTexCoord2d(S,T):-
 1519	float(S),
 1520	float(T),
 1521	c_glTexCoord2d(S,T).
 glTexCoord2dv(+V:list(float))
Set the current texture coordinates.
 1525glTexCoord2dv(V):-
 1526	c_glTexCoord2dv(V).
 glTexCoord2f(+S, +T)
Set the current texture coordinates.
 1530glTexCoord2f(S,T):-
 1531	float(S),
 1532	float(T),
 1533	c_glTexCoord2f(S,T).
 glTexCoord2fv(+V:list(float))
Set the current texture coordinates.
 1537glTexCoord2fv(V):-
 1538	c_glTexCoord2fv(V).
 glTexCoord2i(+S, +T)
Set the current texture coordinates.
 1542glTexCoord2i(S,T):-
 1543	c_glTexCoord2i(S,T).
 glTexCoord2iv(+V:list(number))
Set the current texture coordinates.
 1547glTexCoord2iv(V):-
 1548	c_glTexCoord2iv(V).
 glTexCoord2s(+S, +T)
Set the current texture coordinates.
 1552glTexCoord2s(S,T):-
 1553	c_glTexCoord2s(S,T).
 glTexCoord2sv(+V:list(number))
Set the current texture coordinates.
 1557glTexCoord2sv(V):-
 1558	c_glTexCoord2sv(V).
 glTexCoord3d(+S, +T, +R)
Set the current texture coordinates.
 1562glTexCoord3d(S,T,R):-
 1563	float(S),
 1564	float(T),
 1565        float(R),
 1566	c_glTexCoord3d(S,T,R).
 glTexCoord3dv(+V:list(float))
Set the current texture coordinates.
 1570glTexCoord3dv(V):-
 1571	c_glTexCoord3dv(V).
 glTexCoord3f(+S, +T, +R)
Set the current texture coordinates.
 1575glTexCoord3f(S,T,R):-
 1576	float(S),
 1577	float(T),
 1578        float(R),
 1579	c_glTexCoord3f(S,T,R).
 glTexCoord3fv(+V:list(float))
Set the current texture coordinates.
 1583glTexCoord3fv(V):-
 1584	c_glTexCoord3fv(V).
 glTexCoord3i(+S, +T, +R)
Set the current texture coordinates.
 1588glTexCoord3i(S,T,R):-
 1589	c_glTexCoord3i(S,T,R).
 glTexCoord3iv(+V:list(number))
Set the current texture coordinates.
 1593glTexCoord3iv(V):-
 1594	c_glTexCoord3iv(V).
 glTexCoord3s(+S, +T, +R)
Set the current texture coordinates.
 1598glTexCoord3s(S,T,R):-
 1599	c_glTexCoord3s(S,T,R).
 glTexCoord3sv(+V:list(number))
Set the current texture coordinates.
 1603glTexCoord3sv(V):-
 1604	c_glTexCoord3sv(V).
 glTexCoord4d(+S, +T, +R, +Q)
Set the current texture coordinates.
 1608glTexCoord4d(S,T,R,Q):-
 1609	float(S),
 1610	float(T),
 1611        float(R),
 1612        float(Q),
 1613	c_glTexCoord4d(S,T,R,Q).
 glTexCoord4dv(+V:list(float))
Set the current texture coordinates.
 1617glTexCoord4dv(V):-
 1618	c_glTexCoord4dv(V).
 glTexCoord4f(+S, +T, +R, +Q)
Set the current texture coordinates.
 1622glTexCoord4f(S,T,R,Q):-
 1623	float(S),
 1624	float(T),
 1625        float(R),
 1626        float(Q),
 1627	c_glTexCoord4f(S,T,R,Q).
 glTexCoord4fv(+V:list(float))
Set the current texture coordinates.
 1631glTexCoord4fv(V):-
 1632	c_glTexCoord4fv(V).
 glTexCoord4i(+S, +T, +R, +Q)
Set the current texture coordinates.
 1636glTexCoord4i(S,T,R,Q):-
 1637	c_glTexCoord4i(S,T,R,Q).
 glTexCoord4iv(+V:list(number))
Set the current texture coordinates.
 1641glTexCoord4iv(V):-
 1642	c_glTexCoord4iv(V).
 glTexCoord4s(+S, +T, +R, +Q)
Set the current texture coordinates.
 1646glTexCoord4s(S,T,R,Q):-
 1647	c_glTexCoord4s(S,T,R,Q).
 glTexCoord4sv(+V:list(number))
Set the current texture coordinates.
 1651glTexCoord4sv(V):-
 1652	c_glTexCoord4sv(V).
 glTexImage1D(+Target, +Level, +Internal, +Width, +Border, +Format, +Type, +Texels)
Specify a one-dimensional texture image.
 1656glTexImage1D(Target,Level,Internal,Width,Border,Format,Type,Texels):-
 1657	c_glTexImage1D(Target,Level,Internal,Width,Border,Format,Type,Texels).
 glTexImage2D(+Target, +Level, +Internal, +Width, +Height, Border, +Format, +Type, +Texels)
Specify a two-dimensional texture image.
 1661glTexImage2D(Target,Level,Internal,Width,Height,Border,Format,Type,Texels):-
 1662	c_glTexImage2D(Target,Level,Internal,Width,Height,Border,Format,Type,Texels).
 1663
 1664% Temporarily Disabled due to FFI Limitation
 1665% glTexImage3D(Target,Level,Internal,Width,Height,Depth,Border,Format,Type,Texels):-
 1666%	c_glTexImage3D(Target,Level,Internal,Width,Height,Depth,Border,Format,Type,Texels).
 1667%
 glTexParameteri(+Target, +PName, +Param)
Set the texture parameters.
 1671glTexParameteri(Target,PName,Param):-
 1672	c_glTexParameteri(Target,PName,Param).
 glTexSubImage1D(+Target, +Level, +XOffset, +Width, +Format, +Type, +Texels)
Specify a one-dimensional texture subimage.
 1676glTexSubImage1D(Target,Level,XOffset,Width,Format,Type,Texels):-
 1677	c_glTexSubImage1D(Target,Level,XOffset,Width,Format,Type,Texels).
 glTexSubImage2D(+Target, +Level, +XOffset, +YOffset, +Width, +Height, +Format, +Type, +Texels)
Specify a two-dimensional texture subimage.
 1681glTexSubImage2D(Target,Level,XOffset,YOffset,Width,Height,Format,Type,Texels):-
 1682	c_glTexSubImage2D(Target,Level,XOffset,YOffset,Width,Height,Format,Type,Texels).
 1683
 1684% TODO
 1685glTexSubImage3D(Target,Level,XOffset,YOffset,ZOffset,Width,Height,Depth,Format,Type,Texels):-
 1686	c_glTexSubImage3D(Target,Level,XOffset,YOffset,ZOffset,Width,Height,Depth,Format,Type,Texels).
 glTranslated(+X, +Y, +Z)
Multiplies the current matrix by a translation matrix.
 1690glTranslated(X,Y,Z):-
 1691	float(X),
 1692	float(Y),
 1693	float(Z),
 1694	c_glTranslated(X,Y,Z).
 glTranslatef(+X, +Y, +Z)
Multiplies the current matrix by a translation matrix.
 1698glTranslatef(X,Y,Z):-
 1699	float(X),
 1700	float(Y),
 1701	float(Z),
 1702	c_glTranslatef(X,Y,Z).
 glVertex2d(+X, +Y)
Specify a vertex
 1706glVertex2d(X,Y):-
 1707	float(X),
 1708	float(Y),
 1709	c_glVertex2d(X,Y).
 glVertex2dv(+X:list(float))
Specify a vertex
 1713glVertex2dv(X):-
 1714	c_glVertex2dv(X).
 glVertex2f(+X, +Y)
Specify a vertex
 1718glVertex2f(X,Y):-
 1719	float(X),
 1720	float(Y),
 1721	c_glVertex2f(X,Y).
 glVertex2fv(+X:list(float))
Specify a vertex
 1725glVertex2fv(X):-
 1726	c_glVertex2fv(X).
 glVertex2i(+X, +Y)
Specify a vertex
 1730glVertex2i(X,Y):-
 1731	c_glVertex2i(X,Y).
 glVertex2iv(+X:list(number))
Specify a vertex
 1735glVertex2iv(X):-
 1736	c_glVertex2iv(X).
 glVertex2s(+X, +Y)
Specify a vertex
 1740glVertex2s(X,Y):-
 1741	float(X),
 1742	float(Y),
 1743	c_glVertex2s(X,Y).
 glVertex2sv(+X:list(number))
Specify a vertex
 1747glVertex2sv(X):-
 1748	c_glVertex2sv(X).
 glVertex3d(+X, +Y, +Z)
Specify a vertex
 1752glVertex3d(X,Y,Z):-
 1753	float(X),
 1754	float(Y),
 1755	float(Z),
 1756	c_glVertex3d(X,Y,Z).
 glVertex3dv(+X:list(float))
Specify a vertex
 1760glVertex3dv(X):-
 1761	c_glVertex3dv(X).
 glVertex3f(+X, +Y, +Z)
Specify a vertex
 1765glVertex3f(X,Y,Z):-
 1766	float(X),
 1767	float(Y),
 1768	float(Z),
 1769	c_glVertex3f(X,Y,Z).
 glVertex3fv(+X:list(float))
Specify a vertex
 1773glVertex3fv(X):-
 1774	c_glVertex3fv(X).
 glVertex3i(+X, +Y, +Z)
Specify a vertex
 1778glVertex3i(X,Y,Z):-
 1779	c_glVertex3i(X,Y,Z).
 glVertex3iv(+X:list(number))
Specify a vertex
 1783glVertex3iv(X):-
 1784	c_glVertex3iv(X).
 glVertex3s(+X, +Y, +Z)
Specify a vertex
 1788glVertex3s(X,Y,Z):-
 1789	c_glVertex3s(X,Y,Z).
 glVertex3sv(+X:list(number))
Specify a vertex
 1793glVertex3sv(X):-
 1794	c_glVertex3sv(X).
 glVertex4d(+X, +Y, +Z, +W)
Specify a vertex
 1798glVertex4d(X,Y,Z,W):-
 1799	float(X),
 1800	float(Y),
 1801	float(Z),
 1802	float(W),
 1803	c_glVertex4d(X,Y,Z,W).
 glVertex4dv(+X:list(float))
Specify a vertex
 1807glVertex4dv(X):-
 1808	c_glVertex4dv(X).
 glVertex4f(+X, +Y, +Z, +W)
Specify a vertex
 1812glVertex4f(X,Y,Z,W):-
 1813	float(X),
 1814	float(Y),
 1815	float(Z),
 1816	float(W),
 1817	c_glVertex4f(X,Y,Z,W).
 glVertex4fv(+X:list(float))
Specify a vertex
 1821glVertex4fv(X):-
 1822	c_glVertex4fv(X).
 glVertex4i(+X, +Y, +Z, +W)
Specify a vertex
 1826glVertex4i(X,Y,Z,W):-
 1827	c_glVertex4i(X,Y,Z,W).
 glVertex4iv(+X:list(number))
Specify a vertex
 1831glVertex4iv(X):-
 1832	c_glVertex4iv(X).
 glVertex4s(+X, +Y, +Z, +W)
Specify a vertex
 1836glVertex4s(X,Y,Z,W):-
 1837	c_glVertex4s(X,Y,Z,W).
 glVertex4sv(+X:list(number))
Specify a vertex
 1841glVertex4sv(X):-
 1842	c_glVertex4sv(X).
 glVertexPointer(+Size, +Type, +Stride, +Pointer)
Define an array of vertex data.
 1846glVertexPointer(Size, Type, Stride, Pointer):-
 1847    c_glVertexPointer(Size, Type, Stride, Pointer).
 glViewport(+X, +Y, +W, +H)
Set the viewport.
 1851glViewport(X,Y,W,H):-
 1852	c_glViewport(X,Y,W,H).
 1853
 1854
 1855eq(X,X)