GLXWorkstation.st
author claus
Mon, 21 Nov 1994 17:44:08 +0100
changeset 82 98a70bce6d51
parent 77 da4678fae5c8
child 89 ea2bf46eb669
permissions -rw-r--r--
*** empty log message ***

"
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

XWorkstation subclass:#GLXWorkstation
       instanceVariableNames:'activeWindow'
       classVariableNames:   ''
       poolDictionaries:''
       category:'Interface-Graphics'
!

GLXWorkstation comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/GLXWorkstation.st,v 1.16 1994-11-21 16:43:13 claus Exp $
'!

!GLXWorkstation class methodsFor:'documentation'!

copyright
"
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libview/GLXWorkstation.st,v 1.16 1994-11-21 16:43:13 claus Exp $
"
!

documentation
"
    this class was originally written as a demo on how an interface to
    a c graphics library could be implemented. In the mean time, it has become
    quite complete ...

    It provides an interface to either a real GL (on SGI workstations)
    or a simulated VGL (i.e. GL-light; low nicotine).
    The GL simulation is derived from the PD vogl library, with slight
    modifictions to support multiple GL views.

    Most of the hard work was done by Jeff (thanks indeed) ...


    Some notes:

    I do not really know what most of these functions do - for more
    detail, see the GL man pages (on SGI) or the doc provided with VGL.

    The interface offered here provides a very very low level (i.e one-to-one)
    interface to GL functions. More high-level stuff is required, to make
    3D drawing be more object-oriented. 
    (see a bit of this in 'clients/IRIS-specials')

    Some functions are duplicated, Jeff and I developed those in parallel -
    those will be merged and duplicates removed ...

    Also, in a hurry to implement all those methods, many do no or only
    limited argument checking - make certain, that you pass the correct
    arguments.

    There might be some confusion in the v3[sifd] functions: basically they
    all do the same, and could be mapped onto one st-method (such as vertex3).
    However, the C-functions expect different argument types - I dont know if
    one or another of these functions suffers from any performance penalties.
    Therefore, I leave the direct 1-to-1 mapping; GL experts might know more
    about this (I use v3f in all of my code).

    written june 93 by claus
    VGL stuff dec 93
    many many additions jan 94 by Jeff McAffer <jeff@is.s.u-tokyo.ac.jp>

    Since this is a demo (consider it a free add-on goody) there is 
    *** NO WARRANTY ** for this.

    Notice: this should be rewritten to use the openGL library functions
"
! !

!GLXWorkstation class primitiveDefinitions!

%{
/*
 * on SGI, this class is compiled with -DGLX, while
 * for simulation (using vogl), this is compiled with -DVGL
 */

/*
 * define this to enable:
 *    blendcolor getgconfig getmultisample leftbuffer rightbuffer monobuffer
 *    msalpha msmask mspattern mssize multisample stereobuffer
 *    t3s t3i t3f t3d t4s t4i t4f t4d tlutbind zbsize
 *
 * these are not available on all gl's
 */

/* #define FULL_GLX */

/*
 * this is stupid, GLX defines String, which is also defined here ...
 */
# define String GLX_String

#ifdef GLX
# include <gl/glws.h>
# include <gl/sphere.h>
#else
# undef memset
# include <vogl.h>
# include <X11/Xlib.h>
#endif

#ifndef NULL
# define NULL (char *)0         /* sigh */
#endif

typedef enum {
    GLXcolorIndexSingleBuffer,
    GLXcolorIndexDoubleBuffer,
    GLXrgbSingleBuffer,
    GLXrgbDoubleBuffer
} GLXWindowType;

extern Window GLXCreateWindow();

#undef String

/*
 * some defines - tired of typing ...
 * most of these macros/functions extract values from smalltalk objects and
 * put/pack them into corresponding c variables.
 *
 */
#if defined(hpux) && defined(POSITIVE_ADDRESSES)
# define MKDPY(o)       (Display *)((int)(o) & ~TAG_INT)
# define MKWIN(o)        (Window)((int)(o) & ~TAG_INT)
#else
# define MKDPY(o)       (Display *)(_intVal(o))
# define MKWIN(o)       (Window)(_intVal(o))
#endif

#define myDpy MKDPY(_INST(displayId))

#define SETWIN(aGLXWindowId)                             \
    if (_INST(activeWindow) != aGLXWindowId) {           \
	if (! _isSmallInteger(aGLXWindowId)) {           \
	    RETURN (false);                              \
	}                                                \
	if (GLXwinset(myDpy, MKWIN(aGLXWindowId)) < 0) { \
	    RETURN (false);                              \
	}                                                \
	_INST(activeWindow) = aGLXWindowId;              \
    }

/*
 * check for and fetch a boolean from ST-arg into C-dst
 * ST-object must be true or false
 */
#define _MKBOOLEAN(b)   ((b==FALSE) ? false : true)
#define _booleanVal(b)  ((b==false) ? (Boolean)FALSE : (Boolean)TRUE)
#define _BOOLEAN_(arg, dst)             \
    if (arg==true)                      \
	dst = (Boolean)TRUE;            \
    else if (arg==false)                \
	dst = (Boolean)FALSE;           \
    else { RETURN(false); }

/*
 * check for and fetch a coord from ST-arg into C-dst
 * ST-object must be Float, SmallInteger or Fraction
 */
#define _coordVal(c)                            \
    ((__isFloat(c)) ? (Coord)(_floatVal(c))      \
		   : (Coord)(_intVal(c)))

#define _COORD_(arg, dst)               \
    if (__isFloat(arg))                  \
	dst = (Coord)(_floatVal(arg));  \
    else if (_isSmallInteger(arg))      \
	dst = (Coord)(_intVal(arg));    \
    else if (__isFraction(arg)           \
	  && _isSmallInteger(_FractionInstPtr(arg)->f_numerator)        \
	  && _isSmallInteger(_FractionInstPtr(arg)->f_denominator)) {   \
	float n, d;                                                     \
									\
	n = (float)(_intVal(_FractionInstPtr(arg)->f_numerator));       \
	d = (float)(_intVal(_FractionInstPtr(arg)->f_denominator));     \
	dst = (Coord)(n / d);                                           \
    } else { RETURN(false); }

/*
 * check for and fetch an icoord from ST-arg into C-dst
 * ST-object must be SmallInteger 
 */
#define _icoordVal(c) ((Icoord)(_intVal(c)))
#define _ICOORD_(arg, dst)              \
    if (_isSmallInteger(arg))           \
      dst = (Icoord)(_intVal(arg));     \
    else { RETURN(false); }

/*
 * check for and fetch an icoord from ST-arg into C-dst
 * ST-object must be SmallInteger 
 */
#define _scoordVal(c) ((Scoord)(_intVal(c)))
#define _SCOORD_(arg, dst)              \
    if (_isSmallInteger(arg))           \
      dst = (Scoord)(_intVal(arg));     \
    else { RETURN(false); }

#define _screencoordVal(c) ((Screencoord)(_intVal(c)))
#define _SCREENCOORD_(arg, dst)          \
    if (_isSmallInteger(arg))            \
      dst = (Screencoord)(_intVal(arg)); \
    else { RETURN(false); }

#define _colorindexVal(c) ((Colorindex)(_intVal(c)))
#define _COLORINDEX_(arg, dst)           \
    if (_isSmallInteger(arg))            \
      dst = (Colorindex)(_intVal(arg));  \
    else { RETURN(false); }

#define _linestyleVal(l) ((Linestyle)(_intVal(l)))
#define _shortVal(l) ((short)(_intVal(l)))
#define _longVal(l) ((long)(_intVal(l)))
#define _deviceVal(l) ((Device)(_intVal(l)))
#define _tagVal(l) ((Tag)(_intVal(l)))
#define _objectVal(l) ((Object)(_intVal(l)))
#define _offsetVal(l) ((Offset)(_intVal(l)))
#define _rgbVal(l) ((RGBvalue)(_intVal(l)))

#define _angleVal(c) ((Angle)(_intVal(c)))
#define _ANGLE_(arg, dst)               \
    if (_isSmallInteger(arg))           \
	dst = (Angle)(_intVal(arg));    \
    else { RETURN(false); }

#define _FLOAT_(arg, dst)               \
    if (__isFloat(arg))                  \
	dst = (float)(_floatVal(arg));  \
    else if (_isSmallInteger(arg))      \
	dst = (float)(_intVal(arg));    \
    else if (__isFraction(arg)           \
	  && _isSmallInteger(_FractionInstPtr(arg)->f_numerator)        \
	  && _isSmallInteger(_FractionInstPtr(arg)->f_denominator)) {   \
	float n, d;                                                     \
									\
	n = (float)(_intVal(_FractionInstPtr(arg)->f_numerator));       \
	d = (float)(_intVal(_FractionInstPtr(arg)->f_denominator));     \
	dst = (float)(n / d);                                           \
    } else { RETURN(false); }

#define _INT_(arg, dst)                 \
    if (_isSmallInteger(arg))           \
	dst = (int)(_intVal(arg));      \
    else { RETURN(false); }

#define _indexedArea(object)            \
    (((char *) (_InstPtr(object)))      \
	+ OHDR_SIZE                     \
	+ (_intVal(_ClassInstPtr(_qClass(object))->c_ninstvars)) * sizeof(OBJ))
%}
! !

!GLXWorkstation class primitiveFunctions!

%{
/*
 * helper for rotation - call rot()
 */
static OBJ
doRotate(angle, axis)
    OBJ angle;
    char axis;
{
    Angle a_angle;
    float f_angle;

    if (__isFloat(angle)) {
	f_angle = (float)(_floatVal(angle));
	if (f_angle != 0.0)
	    rot(f_angle, axis);
	return (true);
    }
    if (__isFraction(angle)
     && _isSmallInteger(_FractionInstPtr(angle)->f_numerator)
     && _isSmallInteger(_FractionInstPtr(angle)->f_denominator)) {
	float n, d;

	n = (float)(_intVal(_FractionInstPtr(angle)->f_numerator));
	d = (float)(_intVal(_FractionInstPtr(angle)->f_denominator));
	f_angle = n / d;
	if (f_angle != 0.0)
	    rot(f_angle, axis);
	return (true);
    }
    if (_isSmallInteger(angle)) {
	f_angle = (float)(_intVal(angle));
	if (f_angle != 0.0)
	    rot(f_angle, axis);
	return (true);
    }
    return false;
}

/*
 * fetch integers from an st-array (elements must be smallIntegers)
 */
static long *
getLongsFromInto(obj, vec, count)
   OBJ obj;
   long *vec;
{
    OBJ cls, o;
    int nByte, i, ninstVars, nInstBytes;
    char *pElem;

    if (! _isNonNilObject(obj)) return (long *)NULL;
    cls = _qClass(obj);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);
    nByte = _qSize(obj) - nInstBytes;
    pElem = (char *)(_InstPtr(obj)) + nInstBytes;
    if (nByte < (count * sizeof(OBJ))) return (long *)NULL;
    for (i=0; i<count; i++) {
	o = *(OBJ *)pElem;
	if (! _isSmallInteger(o)) return (long *)NULL;
	vec[i] = (long)_intVal(o);
	pElem += sizeof(OBJ);
    }
    return vec;
}

/*
 * fetch shorts from an st-array (elements must be smallIntegers)
 */
static short *
getShortsFromInto(obj, vec, count)
   OBJ obj;
   short *vec;
{
    OBJ cls, o;
    int nByte, i, ninstVars, nInstBytes;
    char *pElem;

    if (! _isNonNilObject(obj)) return (short *)NULL;
    cls = _qClass(obj);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);
    nByte = _qSize(obj) - nInstBytes;
    pElem = (char *)(_InstPtr(obj)) + nInstBytes;
    if (nByte < (count * sizeof(OBJ))) return (short *)NULL;
    for (i=0; i<count; i++) {
	o = *(OBJ *)pElem;
	if (! _isSmallInteger(o)) return (short *)NULL;
	vec[i] = (short)_intVal(o);
	pElem += sizeof(OBJ);
    }
    return vec;
}

/*
 * fetch floats from an st-object into a c-float array 
 * which may be a floatArray, doubleArray or array-of-something,
 * where something may be a float, fraction or smallInteger,
 */
static float *
getFloatsFromInto(obj, vec, count)
   OBJ obj;
   float *vec;
{
    OBJ cls;
    int nByte;
    OBJ o;
    int i, ninstVars, nInstBytes;
    char *pElem;

    if (! _isNonNilObject(obj)) return (float *)0;

    cls = _qClass(obj);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);
    nByte = _qSize(obj) - nInstBytes;
    pElem = (char *)(_InstPtr(obj)) + nInstBytes;

    switch (_intVal(_ClassInstPtr(cls)->c_flags) & ARRAYMASK) {
      case FLOATARRAY:
	/*
	 * best speed for float array
	 * - the data is already as we want it
	 */
	if (nByte < (count * sizeof(float))) return (float *)0;
	return (float *)pElem;

      case DOUBLEARRAY:
	/*
	 * for double array, have to copy-and-cast
	 */
	if (nByte < (count * sizeof(double))) return (float *)0;
	for (i=0; i<count; i++) {
	    vec[i] = *((double *)pElem);
	    pElem += sizeof(double);
	}
	return vec;

      case POINTERARRAY:
	/*
	 * for other array, have to fetch, check and store
	 * the elements can be floats, smallintegers or fractions
	 */
	if (nByte < (count * sizeof(OBJ))) return (float *)0;
	/* get elements one-by-one */
	for (i=0; i<count; i++) {
	    o = *(OBJ *)pElem;
	    if (__isFloat(o)) {
		vec[i] = _floatVal(o);
	    } else if (_isSmallInteger(o)) {
		vec[i] = (float)(_intVal(o));
	    } else if (__isFraction(o)
		    && _isSmallInteger(_FractionInstPtr(o)->f_numerator)
		    && _isSmallInteger(_FractionInstPtr(o)->f_denominator)) {
		float n, d;

		n = (float)(_intVal(_FractionInstPtr(o)->f_numerator));
		d = (float)(_intVal(_FractionInstPtr(o)->f_denominator));
		vec[i] = n / d;
	    } else
		return 0;
	    pElem += sizeof(OBJ);
	}
	return vec;
    }
    return (float *)0;
}

/*
 * fetch doubles from an st-object into a c-double array 
 * which may be a floatArray, doubleArray or array-of-something,
 * where something may be a float, fraction or smallInteger,
 */
static double *
getDoublesFromInto(obj, vec, count)
   OBJ obj;
   double *vec;
{
    OBJ cls, o;
    int nByte, i, ninstVars, nInstBytes;
    char *pElem;

    if (! _isNonNilObject(obj)) return (double *)0;
    cls = _qClass(obj);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);
    nByte = _qSize(obj) - nInstBytes;
    pElem = (char *)(_InstPtr(obj)) + nInstBytes;

    switch (_intVal(_ClassInstPtr(cls)->c_flags) & ARRAYMASK) {
      case DOUBLEARRAY:
	/* best speed for double array - the data is already as we want it */
	if (nByte < (count * sizeof(double))) return (double *)0;
	return (double *)pElem;

      case FLOATARRAY:
	if (nByte < (count * sizeof(float))) return (double *)0;
	for (i=0; i<count; i++) {
	    vec[i] = *((float *)pElem);
	    pElem += sizeof(float);
	}
	return vec;

      case POINTERARRAY:
	if (nByte < (count * sizeof(OBJ))) return (double *)0;
	/* get elements one-by-one */
	for (i=0; i<count; i++) {
	    o = *(OBJ *)pElem;
	    if (__isFloat(o)) 
		vec[i] = _floatVal(o);
	    else if (_isSmallInteger(o)) 
		vec[i] = (double)(_intVal(o));
	    else if (__isFraction(o)
		     && _isSmallInteger(_FractionInstPtr(o)->f_numerator)
		     && _isSmallInteger(_FractionInstPtr(o)->f_denominator)) {
		double n, d;

		n = (double)(_intVal(_FractionInstPtr(o)->f_numerator));
		d = (double)(_intVal(_FractionInstPtr(o)->f_denominator));
		vec[i] = n / d;

	    } else 
		return 0;
	    pElem += sizeof(OBJ);
	}
	return vec;
    }
    return (double *)0;
}

/*
 * move from a c-float array into an st-object,
 * the st-object MUST be either a float- or double array
 */
static
putFloatsFromInto(vec, obj, count)
   OBJ obj;
   float *vec;
{
    OBJ cls;
    int nByte;
    OBJ o;
    int i, ninstVars, nInstBytes;
    char *pElem;

    if (! _isNonNilObject(obj)) return 0;

    cls = _qClass(obj);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);
    nByte = _qSize(obj) - nInstBytes;
    pElem = (char *)(_InstPtr(obj)) + nInstBytes;

    switch (_intVal(_ClassInstPtr(cls)->c_flags) & ARRAYMASK) {
      case FLOATARRAY:
	if (nByte < (count * sizeof(float))) return 0;
	for (i=0; i<count; i++) {
	    *(float *)pElem = vec[i];
	    pElem += sizeof(float);
	}
	return 1;

      case DOUBLEARRAY:
	if (nByte < (count * sizeof(float))) return 0;
	for (i=0; i<count; i++) {
	    *(double *)pElem = vec[i];
	    pElem += sizeof(double);
	}
	return 1;
    }
    /* not implemented for others */

    return 0;
}

static Matrix*
getFloatsFromMatrixInto(obj, mp)
    OBJ obj;
    Matrix *mp;
{
    OBJ cls;
    extern OBJ FloatArray, DoubleArray, Array;
    int nByte;
    OBJ o;
    int ninstVars, nInstBytes;
    char *pElem;
    int x = 0;
    int i,j;

    if (! _isNonNilObject(obj)) return (Matrix *)0;

    cls = _qClass(obj);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);
    nByte = _qSize(obj) - nInstBytes;
    pElem = (char *)(_InstPtr(obj)) + nInstBytes;

    switch (_intVal(_ClassInstPtr(cls)->c_flags) & ARRAYMASK) {
      case FLOATARRAY:
	/*
	 * very easy for FLOATARRAY objects - no copying needed
	 */
	if (nByte < (16 * sizeof(float))) return (Matrix *)0;
	return (Matrix *) _FloatArrayInstPtr(obj)->f_element;
    
      case DOUBLEARRAY:
	/*
	 * for DOUBLEARRAY objects copy and cast
	 */
	if (nByte < (16 * sizeof(double))) return (Matrix *)0;
	for (i=0; i<4; i++) {
	    for (j=0; j<4; j++) {
		(*mp)[i][j] = _DoubleArrayInstPtr(obj)->d_element[x];
		x++;
	    }
	}
	return mp;

      case POINTERARRAY:
	if (nByte < (16 * sizeof(OBJ))) return (Matrix *)0;
	/* 
	 * get elements one-by-one 
	 */
	for (i=0; i<4; i++) {
	    for (j=0; j<4; j++) {
		o = _ArrayInstPtr(obj)->a_element[x];
		if (__isFloat(o)) {
		    (*mp)[i][j] = _floatVal(o);
		} else if (_isSmallInteger(o)) {
		    (*mp)[i][j] = (double)_intVal(o);
		} else if (__isFraction(o)
		    && _isSmallInteger(_FractionInstPtr(o)->f_numerator)
		    && _isSmallInteger(_FractionInstPtr(o)->f_denominator)) {
		    double n, d;

		    n = (double)(_intVal(_FractionInstPtr(o)->f_numerator));
		    d = (double)(_intVal(_FractionInstPtr(o)->f_denominator));
		    (*mp)[i][j] = n / d;
		} else
		    return (Matrix *)0;
		x++;
	    }
	}
	return mp;
    }
    return (Matrix *)0;
}

static float*
getFloatsFromFloatArrayInto(obj, fp)
    OBJ obj;
    float *fp;
{
    OBJ cls;
    extern OBJ FloatArray, DoubleArray, Array;
    int ninstVars;

    if (! _isNonNilObject(obj)) return (float *)0;
    cls = _qClass(obj);
    if (cls == FloatArray)
	return _FloatArrayInstPtr(obj)->f_element;

    if ((_intVal(_ClassInstPtr(cls)->c_flags) & ARRAYMASK) == FLOATARRAY) {
	ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
	return (float *) &(_InstPtr(obj)->i_instvars[ninstVars]);
    }

    /*
     * need more here (i.e. convert from array-of-floats)
     */
    return (float *)0;
}

%}
! !

!GLXWorkstation methodsFor:'queries'!

supportsRGB
    "return true, if this gl workstation supports rgb
     (in addition to indexed) colors. Actually, we return true
     for a real GL engine, false for the simulator here."

%{  /* NOCONTEXT */

#ifdef VGL
    RETURN ( false );
#endif
#ifdef GLX
    RETURN ( true );
#endif
%}
!

supportsLight
    "return true, if this gl workstation supports light (i.e.
     if its a real GL)"
%{  /* NOCONTEXT */

#ifdef VGL
    RETURN ( false );
#endif
#ifdef GLX
    RETURN ( true );
#endif
%}
! !

!GLXWorkstation methodsFor:'window creation'!

createGLXWindowFor:aView left:xpos top:ypos width:wwidth height:wheight type:glxType
    |ext minWidth minHeight maxWidth maxHeight 
     bWidth bColor viewBg viewBgId wsuperView wsuperViewId wcreateOnTop 
     winputOnly wlabel wcursor wcursorId wicon wiconId windowId
     weventMask wiconView wiconViewId bitGravity viewGravity vBgColor
     vBgForm deepForm|

    wsuperView := aView superView.
    wsuperView notNil ifTrue:[
	wsuperViewId := wsuperView id
    ].

%{
    Display *dpy = myDpy;
    int screen = _intVal(_INST(screen));
    Window newWindow, parentWindow;
    extern Window GLXCreateWindow();
    int t;

    if (_isSmallInteger(xpos) && _isSmallInteger(ypos)
     && _isSmallInteger(wwidth) && _isSmallInteger(wheight)) {
	if (_isSmallInteger(wsuperViewId)) {
	    parentWindow = MKWIN(wsuperViewId);
	} else {
	    parentWindow = RootWindow(dpy, screen);
	}

	if (glxType == @symbol(colorIndexSingleBuffer))
	    t = GLXcolorIndexSingleBuffer;
	else if (glxType == @symbol(colorIndexDoubleBuffer))
	    t = GLXcolorIndexDoubleBuffer;
	else if (glxType == @symbol(rgbSingleBuffer))
	    t = GLXrgbSingleBuffer;
	else if (glxType == @symbol(rgbDoubleBuffer))
	    t = GLXrgbDoubleBuffer;
	else {
	    RETURN ( nil );
	}

	newWindow = GLXCreateWindow(dpy, parentWindow,
				    _intVal(xpos), _intVal(ypos),
				    _intVal(wwidth), _intVal(wheight),
				    0, t);

	if (! newWindow) {
	    RETURN ( nil );
	}

	windowId = MKOBJ(newWindow);
    }
%}
.
    windowId notNil ifTrue:[
	self addKnownView:aView withId:windowId.
    ].
    ^ windowId
!

unlinkGLXView:aGLXWindowId
    "remove X/GLX link"
%{
    if (_isSmallInteger(aGLXWindowId))
	GLXUnlinkWindow(myDpy, MKWIN(aGLXWindowId));
%}
! !

!GLXWorkstation methodsFor:'viewing'!

glxPerspectiveFovy:fovy aspect:aspect near:near far:far in:aGLXWindowId
    "define perspective projection"

%{  /* NOCONTEXT */

    Angle a_fovy;
    Coord c_near, c_far;
    float f_aspect;

    _ANGLE_ (fovy, a_fovy)
    _FLOAT_ (aspect, f_aspect)
    _COORD_ (near, c_near)
    _COORD_ (far, c_far)

    SETWIN(aGLXWindowId)
    perspective(a_fovy, f_aspect, c_near, c_far);

    RETURN (true);
%}
!

glxWindowLeft: left right: right bottom: bottom top: top near: near far: far in: aGLXWindowId
    "this one was added independently by JEFF - kept for his programs ..."

    self glxWindowLeft:left right:right top:top bottom:bottom near:near far:far in:aGLXWindowId
!

glxWindowLeft:left right:right top:top bottom:bottom near:near far:far in:aGLXWindowId
    "define perspective viewing pyramid"

%{  /* NOCONTEXT */
    Coord c_left, c_right, c_top, c_bot, c_near, c_far;

    _COORD_ (left, c_left)
    _COORD_ (right, c_right)
    _COORD_ (top, c_top)
    _COORD_ (bottom, c_bot)
    _COORD_ (near, c_near)
    _COORD_ (far, c_far)
    SETWIN(aGLXWindowId)
    window(c_left, c_right, c_bot, c_top, c_near, c_far);

    RETURN (true);
%}
!

glxLookatVx:vx vy:vy vz:vz px:px py:py pz:pz twist:twist in:aGLXWindowId
    "define viewing transformation"

%{  /* NOCONTEXT */

    Coord f_vx, f_vy, f_vz, f_px, f_py, f_pz;
    Angle a_twist;

    _COORD_ (vx, f_vx)
    _COORD_ (vy, f_vy)
    _COORD_ (vz, f_vz)
    _COORD_ (px, f_px)
    _COORD_ (py, f_py)
    _COORD_ (pz, f_pz)
    _ANGLE_ (twist, a_twist)
    SETWIN(aGLXWindowId)
    lookat(f_vx, f_vy, f_vz, f_px, f_py, f_pz, a_twist);
    RETURN (true);
%}
! 

glxOrthoLeft: left right: right bottom: bottom top: top near: near far: far in: aGLXWindowId
    "define orthogonal projection"

%{  /* NOCONTEXT */
    float f_left, f_right, f_bottom, f_top,
	  f_near, f_far;

    _FLOAT_(left, f_left)
    _FLOAT_(right, f_right)
    _FLOAT_(bottom, f_bottom)
    _FLOAT_(top, f_top)
    _FLOAT_(near, f_near)
    _FLOAT_(far, f_far)
    SETWIN(aGLXWindowId)
    ortho(f_left, f_right, f_bottom, f_top, f_near, f_far);
    RETURN (true);
%}
!

glxOrtho2Left: left right: right bottom: bottom top: top in: aGLXWindowId
    "define 2D orthogonal projection"

%{  /* NOCONTEXT */
    float f_left, f_right, f_top, f_bottom;

    SETWIN(aGLXWindowId)
    _FLOAT_(left, f_left)
    _FLOAT_(right, f_right)
    _FLOAT_(bottom, f_bottom)
    _FLOAT_(top, f_top)
    ortho2(f_left, f_right, f_bottom, f_top);
    RETURN (true);
%}
.
    ^ false
!

glxReshapeViewPortIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    reshapeviewport();
    RETURN (true);
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'transformations'!

glxTranslateX:x in:aGLXWindowId
    "translate current matrix on X axis"

%{  /* NOCONTEXT */

    Coord c_x;

    _COORD_ (x, c_x)
    SETWIN(aGLXWindowId)
    translate(c_x, (Coord)0, (Coord)0);
    RETURN (true);
%}
!

glxTranslateY:y in:aGLXWindowId
    "translate current matrix on Y axis"

%{  /* NOCONTEXT */

    Coord c_y;

    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    translate((Coord)0, c_y, (Coord)0);
    RETURN (true);
%}
!

glxTranslateZ:z in:aGLXWindowId
    "translate current matrix on Z axis"

%{  /* NOCONTEXT */

    Coord c_z;

    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    translate((Coord)0, (Coord)0, c_z);
    RETURN (true);
%}
!

glxTranslateX:x y:y z:z in:aGLXWindowId
    "translate current matrix, given individual x, y and z values"

%{  /* NOCONTEXT */

    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    translate(c_x, c_y, c_z);
    RETURN (true);
%}
!

glxTranslate:arrayOf3Floats in:aGLXWindowId
    "translate current matrix, given a 3-element vector"

%{  /* NOCONTEXT */

    float vec[3], *v;

    if (! (v = getFloatsFromInto(arrayOf3Floats, vec, 3))) RETURN(false);

    SETWIN(aGLXWindowId)
    translate((Coord)(v[0]), (Coord)(v[1]), (Coord)(v[2]));
    RETURN (true);
%}
!

glxScaleX:x in:aGLXWindowId
    "scale in x direction"

%{  /* NOCONTEXT */

    float f_x;

    _FLOAT_ (x, f_x)
    SETWIN(aGLXWindowId)
    scale(f_x, (float)0, (float)0);
    RETURN (true);
%}
!

glxScaleY:y in:aGLXWindowId
    "scale in y direction"

%{  /* NOCONTEXT */

    float f_y;

    _FLOAT_ (y, f_y)
    SETWIN(aGLXWindowId)
    scale((float)0, f_y, (float)0);
    RETURN (true);
%}
!

glxScaleZ:z in:aGLXWindowId
    "scale in z direction"

%{  /* NOCONTEXT */

    float f_z;

    _FLOAT_ (z, f_z)
    SETWIN(aGLXWindowId)
    scale((float)0, (float)0, f_z);
    RETURN (true);
%}
!

glxScaleX:x y:y z:z in:aGLXWindowId
    "scale & mirror current matrix, given individual x, y and z values"

%{  /* NOCONTEXT */

    float f_x, f_y, f_z;

    _FLOAT_ (x, f_x)
    _FLOAT_ (y, f_y)
    _FLOAT_ (z, f_z)
    SETWIN(aGLXWindowId)
    scale(f_x, f_y, f_z);
    RETURN (true);
%}
!

glxScale:arrayOf3Floats in:aGLXWindowId
    "scale current matrix, given a 3-element vector"

%{  /* NOCONTEXT */

    float vec[3], *v;

    if (! (v = getFloatsFromInto(arrayOf3Floats, vec, 3))) RETURN(false);

    SETWIN(aGLXWindowId)
    scale(v[0], v[1], v[2]);
    RETURN (true);
%}
!

glxRotateX:angle in:aGLXWindowId
    "rotate the current matrix on x axis.
     The angle is in degrees."

%{  /* NOCONTEXT */

    SETWIN(aGLXWindowId)
    RETURN (doRotate(angle, 'x'));
%}
.
    ^ false
!

glxRotateY:angle in:aGLXWindowId
    "rotate the current matrix on y axis.
     The angle is in degrees."

%{  /* NOCONTEXT */

    SETWIN(aGLXWindowId)
    RETURN (doRotate(angle, 'y'));
%}
.
    ^ false
!

glxRotateZ:angle in:aGLXWindowId
    "rotate the current matrix on z axis.
     The angle is in degrees."

%{  /* NOCONTEXT */

    SETWIN(aGLXWindowId)
    RETURN (doRotate(angle, 'z'));
%}
.
    ^ false
!

glxRotate:angle axis:axis in:aGLXWindowId
    "rotate the current matrix around the axis given by the axis arg,
     which must be one of the symbols: #x, #y or #z.
     The angle is in degrees."

%{  /* NOCONTEXT */

    char c_axis;

    if (axis == @symbol(x))
	c_axis = 'x';
    else if (axis == @symbol(y))
	c_axis = 'y';
    else if (axis == @symbol(z))
	c_axis = 'z';
    else {
	RETURN (false);
    }

    SETWIN(aGLXWindowId)
    RETURN ( doRotate(angle, c_axis) );
%}
!

glxRotateX:xAngle y:yAngle z:zAngle in:aGLXWindowId
    "rotate the current matrix on all axes, given individual x, y and z values.
     The values are in degrees"

%{  /* NOCONTEXT */

    SETWIN(aGLXWindowId)
    if ( doRotate(xAngle, 'x') == true) {
	if ( doRotate(yAngle, 'y') == true) {
	    RETURN (doRotate(zAngle, 'z'));
	}
    }
%}
.
    ^ false
!

glxRotate:arrayOf3Floats in:aGLXWindowId
    "rotate current matrix, given a 3-element vector (or more).
     The elements of the array are degrees."

%{  /* NOCONTEXT */

    float vec[3], *v;

    if (! (v = getFloatsFromInto(arrayOf3Floats, vec, 3))) RETURN(false);

    SETWIN(aGLXWindowId)
    rot(v[0], 'x');
    rot(v[1], 'y');
    rot(v[2], 'z');
    RETURN (true);
%}
!

glxRotateIX:angle in:aGLXWindowId
    "rotate the current matrix on x axis.
     The angle is an integer specifying tenths of a degree."

%{  /* NOCONTEXT */

    if (_isSmallInteger(angle)) {
	SETWIN(aGLXWindowId)
	rotate(_intVal(angle), 'x');
	RETURN (true);
    }
%}
.
    ^ false
!

glxRotateIY:angle in:aGLXWindowId
    "rotate the current matrix on x axis.
     The angle is an integer specifying tenths of a degree."

%{  /* NOCONTEXT */

    if (_isSmallInteger(angle)) {
	SETWIN(aGLXWindowId)
	rotate(_intVal(angle), 'y');
	RETURN (true);
    }
%}
.
    ^ false
!

glxRotateIZ:angle in:aGLXWindowId
    "rotate the current matrix on x axis.
     The angle is an integer specifying tenths of a degree."

%{  /* NOCONTEXT */

    if (_isSmallInteger(angle)) {
	SETWIN(aGLXWindowId)
	rotate(_intVal(angle), 'z');
	RETURN (true);
    }
%}
.
    ^ false
!

glxRotateI:angle axis:axis in:aGLXWindowId
    "rotate the current matrix around the axis given by the axis arg,
     which must be one of the symbols: #x, #y or #z.
     The angle is an integer specifying tenths of a degree."

%{  /* NOCONTEXT */

    char c_axis;

    if (axis == @symbol(x))
	c_axis = 'x';
    else if (axis == @symbol(y))
	c_axis = 'y';
    else if (axis == @symbol(z))
	c_axis = 'z';
    else {
	RETURN (false);
    }

    if (_isSmallInteger(angle)) {
	SETWIN(aGLXWindowId)
	rotate(_intVal(angle), c_axis);
	RETURN (true);
    }
%}
.
    ^ false
!

glxRotateIX:xAngle y:yAngle z:zAngle in:aGLXWindowId
    "rotate the current matrix on all axes, given individual x, y and z values.
     The values are integers specifying tenths of a degree."

%{  /* NOCONTEXT */

    if (_isSmallInteger(xAngle)
     && _isSmallInteger(yAngle)
     && _isSmallInteger(zAngle)) {
	SETWIN(aGLXWindowId)
	rotate(_intVal(xAngle), 'x');
	rotate(_intVal(yAngle), 'y');
	rotate(_intVal(zAngle), 'z');
	RETURN (true);
    }
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'materials & lights'!

glxLmdef:what index:index np:np props:props in:aGLXWindowId
    "define a material, light source or lighting model;
     props must be a FloatArray or a subclass of FloatArray"

%{  /* NOCONTEXT */
#ifdef GLX
    short defType;
    short i_index, i_np;
    extern OBJ FloatArray;
    float *fp;
    OBJ cls;
    int ninstVars, nInstBytes;

    if (what == @symbol(material))
	defType = DEFMATERIAL;
    else if (what == @symbol(light))
	defType = DEFLIGHT;
    else if (what == @symbol(lightModel))
	defType = DEFLMODEL;
    else {
	RETURN (false);
    }

    _INT_ (index, i_index);
    _INT_ (np, i_np);

    if (! _isNonNilObject(props)) fp = NULL;
    else {
	cls = _qClass(props);
	if (cls == FloatArray)
	    fp = _FloatArrayInstPtr(props)->f_element;
	else {
	    if ((_intVal(_ClassInstPtr(cls)->c_flags) & ARRAYMASK) == FLOATARRAY) {
		ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
		fp = (float *) &(_InstPtr(props)->i_instvars[ninstVars]);
	    } else {
		RETURN (false);
	    }
	} 
    }
    SETWIN(aGLXWindowId)
    lmdef(defType, i_index, i_np, fp);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxLmbind:target index:index in:aGLXWindowId
    "select a material, lighyt or lighting model"

%{  /* NOCONTEXT */
#ifdef GLX
    short defType;
    short i_index;

    if (target == @symbol(material))
	defType = MATERIAL;
    else if (target == @symbol(backMaterial))
	defType = BACKMATERIAL;
    else if (target == @symbol(light0))
	defType = LIGHT0;
    else if (target == @symbol(light1))
	defType = LIGHT1;
    else if (target == @symbol(light2))
	defType = LIGHT2;
    else if (target == @symbol(light3))
	defType = LIGHT3;
    else if (target == @symbol(light4))
	defType = LIGHT4;
    else if (target == @symbol(light5))
	defType = LIGHT5;
    else if (target == @symbol(light6))
	defType = LIGHT6;
    else if (target == @symbol(light7))
	defType = LIGHT7;
    else if (target == @symbol(lightModel))
	defType = LMODEL;
    else { 
	RETURN (false); 
    }

    _INT_ (index, i_index);
    SETWIN(aGLXWindowId)
    lmbind(defType, i_index);
    RETURN (true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'color'!

glxColor:index in:aGLXWindowId
    "set color, for non gouraud shading, we dont care if the
     argument is integer or float; otherwise, better results are
     expected with float values."

%{  /* NOCONTEXT */

    SETWIN(aGLXWindowId)
    if (_isSmallInteger(index)) {
	color((Colorindex)(_intVal(index)));
	RETURN (true);
    }
    if (__isFloat(index)) {
	colorf((float)(_floatVal(index)));
	RETURN (true);
    }
%}
.
    ^ false
!

glxColorRed:r green:g blue:b in:aGLXWindowId
    "set color, args must be integer values"

%{  /* NOCONTEXT */

#ifdef GLX
    short s_r, s_g, s_b;

    _INT_(r, s_r);
    _INT_(g, s_g);
    _INT_(b, s_b);
    SETWIN(aGLXWindowId)
    RGBcolor(s_r, s_g, s_b);
    RETURN (true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'clearing'!

glxClearIn:aGLXWindowId
    "clear to current color"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    clear();
    RETURN (true);
%}
.
    ^ false
!

glxZClearIn:aGLXWindowId
    "clear z buffer"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    zclear();
    RETURN (true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'matrix stack'!

glxPushmatrixIn:aGLXWindowId
    "push down transformation stack"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    pushmatrix();
    RETURN (true);
%}
.
    ^ false
!

glxPopmatrixIn:aGLXWindowId
    "pop transformation stack"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    popmatrix();
    RETURN (true);
%}
.
    ^ false
!

glxGetMatrix:arrayOf16Floats in:aGLXWindowId
    "argument must be an array (a matrix) of 16 floats. The current matrix
     will be stored into that."

%{  /* NOCONTEXT */
    Matrix matrix;

    SETWIN(aGLXWindowId)
    getmatrix(matrix);
    if (! putFloatsFromInto(matrix, arrayOf16Floats, 16)) RETURN(false);
%}
.
    ^ true
!

glxLoadMatrix:arrayOf16Floats in:aGLXWindowId
    "argument must be an array(a matrix) of 16 floats. The current matrix
     will be loaded from that."

%{  /* NOCONTEXT */
    Matrix matrix;
    Matrix *m;

    if (! (m = getFloatsFromMatrixInto(arrayOf16Floats, &matrix))) RETURN (false);
    SETWIN(aGLXWindowId)
    loadmatrix(*m);
    RETURN (true);
%}
.
    ^ false
!

glxMultMatrix:arrayOf16Floats in:aGLXWindowId
    "argument must be an array(a matrix) of 16 floats containing a
     matrix to multiply into the current matrix."

%{  /* NOCONTEXT */
    Matrix matrix;
    Matrix *m;

    if (! (m = getFloatsFromMatrixInto(arrayOf16Floats, &matrix))) RETURN (false);
    SETWIN(aGLXWindowId)
    multmatrix(*m);
    RETURN (true);
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'double buffering'!

glxDoubleBufferIn:aGLXWindowId
    "set double buffer mode"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    doublebuffer();
    RETURN (true);
%}
.
    ^ false
!

glxSwapBuffersIn:aGLXWindowId
    "swap double buffers"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    swapbuffers();
    RETURN (true);
%}
.
    ^ false
!

glxFrontBufferIn:aGLXWindowId
    "switch to front buffer - turning backbuffer off"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
#ifdef GLX
    backbuffer(FALSE);
#endif
    frontbuffer(TRUE);
    RETURN (true);
%}
.
    ^ false
!

glxBackBufferIn:aGLXWindowId
    "switch to back buffer - turning frontbuffer off"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
#ifdef GLX
    frontbuffer(FALSE);
#endif
    backbuffer(TRUE);
    RETURN (true);
%}
.
    ^ false
!

glxBackbuffer: b in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    backbuffer(_booleanVal(b));
    RETURN (true);
%}
.
    ^ false
! 

glxFrontbuffer: b in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    frontbuffer(_booleanVal(b));
    RETURN (true);
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'zbuffer'!

glxZbuffer:aBoolean in:aGLXWindowId
    "enable/disable z-buffer operation"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    zbuffer(aBoolean == false ? FALSE : TRUE);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxZbsize: planes in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    zbsize(_longVal(planes));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxZdraw: b in: aGLXWindowId
    "enable/disable drawing into the z-buffer"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    zdraw(_booleanVal(b));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxZfunction: func in: aGLXWindowId
    "set the z-buffer comparison function.
     func may be either the numeric value or a symbol (preferred)"

%{  /* NOCONTEXT */
#ifdef GLX
    long f;

    SETWIN(aGLXWindowId)
    if (func == @symbol(NEVER))
	f = ZF_NEVER;
    else if (func == @symbol(LESS))
	f = ZF_LESS;
    else if (func == @symbol(EQUAL))
	f = ZF_EQUAL;
    else if (func == @symbol(LEQUAL))
	f = ZF_LEQUAL;
    else if (func == @symbol(GREATER))
	f = ZF_GREATER;
    else if (func == @symbol(NOTEQUAL))
	f = ZF_NOTEQUAL;
    else if (func == @symbol(GEQUAL))
	f = ZF_GEQUAL;
    else if (func == @symbol(ALWAYS))
	f = ZF_ALWAYS;
    else
	f = _longVal(func);
    zfunction(f);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxZsource: src in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    zsource(_longVal(src));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxZwritemask: mask in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    zwritemask((ulong)_intVal(mask));
    RETURN (true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'misc'!

glxRGBmodeIn:aGLXWindowId
    "set true color mode (no colormap)"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RGBmode();
    RETURN (true);
#endif
%}
.
    ^ false
!

glxGconfigIn:aGLXWindowId
    "must be sent after RGBmode, doubleBuffer etc. to have these
     changes really take effect. See GLX manual.
     (Actually, it seems to be not allowed - I dont really know)"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    gconfig();
    RETURN (true);
%}
.
    ^ false
!

glxNmode:aSymbol in:aGLXWindowId
    "set normalize mode: #auto, #normalize"

%{  /* NOCONTEXT */
#ifdef GLX
    if (aSymbol == @symbol(auto)) {
	nmode(NAUTO);
	RETURN (true);
    }
    if (aSymbol == @symbol(normalize)) {
	nmode(NNORMALIZE);
	RETURN (true);
    }
#endif
%}
.
    ^ false
!

glxMmode:aSymbol in:aGLXWindowId
    "set matrix mode: #single, #viewing, #projection or #texture"

%{  /* NOCONTEXT */
#ifdef GLX
    if (aSymbol == @symbol(single)) {
	mmode(MSINGLE);
	RETURN (true);
    }
    if (aSymbol == @symbol(viewing)) {
	mmode(MVIEWING);
	RETURN (true);
    }
    if (aSymbol == @symbol(projection)) {
	mmode(MPROJECTION);
	RETURN (true);
    }
    if (aSymbol == @symbol(texture)) {
	mmode(MTEXTURE);
	RETURN (true);
    }
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'flat drawing'!

glxBeginPointIn:aGLXWindowId
    "start a point-group"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    bgnpoint();
    RETURN (true);
%}
.
    ^ false
!

glxEndPointIn:aGLXWindowId
    "end a point group"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    endpoint();
    RETURN (true);
%}
.
    ^ false
!

glxBeginClosedLineIn:aGLXWindowId
    "start a closed line"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    bgnclosedline();
    RETURN (true);
%}
.
    ^ false
!

glxEndClosedLineIn:aGLXWindowId
    "end a closed line"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    endclosedline();
    RETURN (true);
%}
.
    ^ false
!

glxBeginLineIn:aGLXWindowId
    "start a line group"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    bgnline();
    RETURN (true);
%}
.
    ^ false
!

glxEndLineIn:aGLXWindowId
    "end a line group"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    endline();
    RETURN (true);
%}
.
    ^ false
!

glxBeginPolygonIn:aGLXWindowId
    "start a polygon"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    bgnpolygon();
    RETURN (true);
%}
.
    ^ false
!

glxEndPolygonIn:aGLXWindowId
    "end a polygon"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    endpolygon();
    RETURN (true);
%}
.
    ^ false
!

glxBeginTriangleMeshIn:aGLXWindowId
    "start a triangle mesh"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    bgntmesh();
    RETURN (true);
%}
.
    ^ false
!

glxEndTriangleMeshIn:aGLXWindowId
    "end a triangle mesh"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    endtmesh();
    RETURN (true);
%}
.
    ^ false
!

glxBeginQuadrilateralStripIn:aGLXWindowId
    "start a quadrilateral strip"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    bgnqstrip();
    RETURN (true);
%}
.
    ^ false
!

glxEndQuadrilateralStripIn:aGLXWindowId
    "end a quadrilateral strip"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    endqstrip();
    RETURN (true);
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'sphere drawing'!

glxSphDraw:arrayOf4Floats in:aGLXWindowId
    "argument must be an array(a matrix) of 4 floats containing the
     sphere - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[4], *v;

    if (! (v = getFloatsFromInto(arrayOf4Floats, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    sphdraw(v);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSphDrawX:x y:y z:z radius:r in:aGLXWindowId
    "arguments must be convertable to floats - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[4];

    _FLOAT_(x, vec[0])
    _FLOAT_(y, vec[1])
    _FLOAT_(z, vec[2])
    _FLOAT_(r, vec[3])
    SETWIN(aGLXWindowId)
    sphdraw(vec);
    RETURN (true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'patches & surfaces'!

glxDefBasis:id mat:aMatrix in:aGLXWindowId
    "define the basis"

%{  /* NOCONTEXT */
    Matrix matrix;
    Matrix *m;

    if (! (m = getFloatsFromMatrixInto(aMatrix, &matrix))) RETURN (false);
    if (_isSmallInteger(id)) {
	SETWIN(aGLXWindowId)
	defbasis((short)(_intVal(id)), *m);
	RETURN (true);
    }
%}
.
    ^ false
!

glxPatchCurvesU:u v:v in:aGLXWindowId
    "set the number of curves in a patch"

%{  /* NOCONTEXT */
    if (_isSmallInteger(u) && _isSmallInteger(v)) {
	SETWIN(aGLXWindowId)
	patchcurves((long)_intVal(u), (long)_intVal(v));
	RETURN (true);
    }
%}
.
    ^ false
!

glxPatchPrecisionU:u v:v in:aGLXWindowId
    "set the patch precision"

%{  /* NOCONTEXT */
    if (_isSmallInteger(u) && _isSmallInteger(v)) {
	SETWIN(aGLXWindowId)
	patchprecision((long)_intVal(u), (long)_intVal(v));
	RETURN (true);
    }
%}
.
    ^ false
!

glxPatchBasisU:u v:v in:aGLXWindowId
    "set the current basis matrices"

%{  /* NOCONTEXT */
    if (_isSmallInteger(u) && _isSmallInteger(v)) {
	SETWIN(aGLXWindowId)
	patchbasis((long)_intVal(u), (long)_intVal(v));
	RETURN (true);
    }
%}
.
    ^ false
!

glxPatchX:arrayOf16XFloats y:arrayOf16YFloats z:arrayOf16ZFloats in:aGLXWindowId
    "arguments must be arrays of 16 floats containing the patch"

%{  /* NOCONTEXT */
    Matrix matrixX, matrixY, matrixZ;
    Matrix *mX, *mY, *mZ;

    if (! (mX = getFloatsFromMatrixInto(arrayOf16XFloats, &matrixX))) RETURN (false);
    if (! (mY = getFloatsFromMatrixInto(arrayOf16YFloats, &matrixY))) RETURN (false);
    if (! (mZ = getFloatsFromMatrixInto(arrayOf16ZFloats, &matrixZ))) RETURN (false);
    SETWIN(aGLXWindowId)
    patch(*mX, *mY, *mZ);
    RETURN (true);
%}
.
    ^ false
!

glxBeginCurveIn:aGLXWindowId
    "start a NURBS curve def - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    bgncurve();
    RETURN (true);
#endif
%}
.
    ^ false
!

glxEndCurveIn:aGLXWindowId
    "end a NURBS curve def - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    endcurve();
    RETURN (true);
#endif
%}
.
    ^ false
!

glxBeginSurfaceIn:aGLXWindowId
    "start a NURBS surface def - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    bgnsurface();
    RETURN (true);
#endif
%}
.
    ^ false
!

glxEndSurfaceIn:aGLXWindowId
    "end a NURBS surface def - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    endsurface();
    RETURN (true);
#endif
%}
.
    ^ false
!

glxNurbsSurfaceUKnotCount: uKnotCount uKnot: uKnot 
    vKnotCount: vKnotCount vKnot: vKnot
    uOffset: uOffset vOffset: vOffset 
    ctlArray: ctlArray 
    uOrder: uOrder vOrder: vOrder 
    type: type in: aGLXWindowId

    | ctlPoints i |
    ctlPoints := DoubleArray new: ctlArray size * (ctlArray first size).
    i := 1.
    ctlArray do: [:point |
	point do: [:coord | 
	    ctlPoints at: i put: coord.
	    i := i + 1]].

%{  /* NOCONTEXT */
#ifdef GLX
    char *uKnotElements, *vKnotElements, *ctlElements;
    OBJ cls;
    int ninstVars, nInstBytes;

    SETWIN(aGLXWindowId)
    cls = _qClass(ctlPoints);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);

    ctlElements = (char *)(_InstPtr(ctlPoints)) + nInstBytes;
    uKnotElements = (char *)(_InstPtr(uKnot)) + nInstBytes;
    vKnotElements = (char *)(_InstPtr(vKnot)) + nInstBytes;

    nurbssurface (
	_intVal(uKnotCount), (double *)uKnotElements,
	_intVal(vKnotCount), (double *)vKnotElements,
	_intVal(uOffset), _intVal(vOffset),
	(double *)ctlElements, 
	_intVal(uOrder), _intVal(vOrder), _intVal(type));
    RETURN(true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'arcs and circles '!

glxArcX: x y: y radius: radius startang: startang endang: endang in: aGLXWindowId
    "draw an arc"

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_radius;
    Angle a_startang, a_endang;

    _COORD_(x, c_x)
    _COORD_(y, c_y)
    _COORD_(radius, c_radius)
    _ANGLE_(startang, a_startang)
    _ANGLE_(endang, a_endang)
    SETWIN(aGLXWindowId)
    arc(c_x, c_y, c_radius, a_startang, a_endang);
    RETURN (true);
%}
! 

glxArciX: x y: y radius: radius startang: startang endang: endang in: aGLXWindowId
    "draw an arc"

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_radius;
    Angle a_startang, a_endang;

    _ICOORD_(x, c_x)
    _ICOORD_(y, c_y)
    _ICOORD_(radius, c_radius)
    _ANGLE_(startang, a_startang)
    _ANGLE_(endang, a_endang)
    SETWIN(aGLXWindowId)
    arci(c_x, c_y, c_radius, a_startang, a_endang);
    RETURN (true);
%}
.
    ^ false
! 

glxArcsX: x y: y radius: radius startang: startang endang: endang in: aGLXWindowId
    "draw an arc"

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_radius;
    Angle a_startang, a_endang;

    _SCOORD_(x, c_x)
    _SCOORD_(y, c_y)
    _SCOORD_(radius, c_radius)
    _ANGLE_(startang, a_startang)
    _ANGLE_(endang, a_endang)
    SETWIN(aGLXWindowId)
    arcs(c_x, c_y, c_radius, a_startang, a_endang);
    RETURN (true);
%}
.
    ^ false
! 

glxArcfX: x y: y radius: radius startang: startang endang: endang in: aGLXWindowId
    "draw a filled arc"

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_radius;
    Angle a_startang, a_endang;

    _COORD_(x, c_x)
    _COORD_(y, c_y)
    _COORD_(radius, c_radius)
    _ANGLE_(startang, a_startang)
    _ANGLE_(endang, a_endang)
    SETWIN(aGLXWindowId)
    arcf(c_x, c_y, c_radius, a_startang, a_endang);
    RETURN (true);
%}
.
    ^ false
! 

glxArcfiX: x y: y radius: radius startang: startang endang: endang in: aGLXWindowId
    "draw a filled arc"

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_radius;
    Angle a_startang, a_endang;

    _ICOORD_(x, c_x)
    _ICOORD_(y, c_y)
    _ICOORD_(radius, c_radius)
    _ANGLE_(startang, a_startang);
    _ANGLE_(endang, a_endang)
    SETWIN(aGLXWindowId)
    arcfi(c_x, c_y, c_radius, a_startang, a_endang);
    RETURN (true);
%}
.
    ^ false
! 

glxArcfsX: x y: y radius: radius startang: startang endang: endang in: aGLXWindowId
    "draw a filled arc"

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_radius;
    Angle a_startang, a_endang;

    _SCOORD_(x, c_x)
    _SCOORD_(y, c_y)
    _SCOORD_(radius, c_radius)
    _ANGLE_(startang, a_startang)
    _ANGLE_(endang, a_endang)
    SETWIN(aGLXWindowId)
    arcfs(c_x, c_y, c_radius, a_startang, a_endang);
    RETURN (true);
%}
.
    ^ false
!

glxCircX: x y: y radius: radius in: aGLXWindowId
    "draw a circle"

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_radius;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (radius, c_radius)
    SETWIN(aGLXWindowId)
    circ(c_x, c_y, c_radius);
    RETURN (true);
%}
.
    ^ false
! 

glxCirciX: x y: y radius: radius in: aGLXWindowId
    "draw a circle"

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_radius;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (radius, c_radius)
    SETWIN(aGLXWindowId)
    circi(c_x, c_y, c_radius);
    RETURN (true);
%}
.
    ^ false
! 

glxCircsX: x y: y radius: radius in: aGLXWindowId
    "draw a circle"

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_radius;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (radius, c_radius)
    SETWIN(aGLXWindowId)
    circs(c_x, c_y, c_radius);
    RETURN (true);
%}
.
    ^ false
! 

glxCircfX: x y: y radius: radius in: aGLXWindowId
    "draw a filled circle"

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_radius;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (radius, c_radius)
    SETWIN(aGLXWindowId)
    circf(c_x, c_y, c_radius);
    RETURN (true);
%}
.
    ^ false
! 

glxCircfiX: x y: y radius: radius in: aGLXWindowId
    "draw a filled circle"

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_radius;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (radius, c_radius)
    SETWIN(aGLXWindowId)
    circfi(c_x, c_y, c_radius);
    RETURN (true);
%}
.
    ^ false
! 

glxCircfsX: x y: y radius: radius in: aGLXWindowId
    "draw a filled circle"

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_radius;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (radius, c_radius)
    SETWIN(aGLXWindowId)
    circfs(c_x, c_y, c_radius);
    RETURN (true);
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'unspecified rest '!

glxAcbufOp: op value: value in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    acbuf(_intVal(op), _floatVal(value));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxAcsizePlanes: planes in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    acsize(_intVal(planes));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxAfunctionRef: ref func: func in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    afunction(_intVal(ref), _intVal(func));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBackface: b in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    backface(_booleanVal(b));
    RETURN (true);
%}
.
    ^ false
! 

glxBbox2Xmin: xmin ymin: ymin x1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Screencoord c_xmin, c_ymin;
    Coord c_x1, c_y1, c_x2, c_y2; 

    _SCREENCOORD_ (xmin, c_xmin)
    _SCREENCOORD_ (ymin, c_ymin)
    _COORD_ (x1, c_x1)
    _COORD_ (y1, c_y1)
    _COORD_ (x2, c_x2)
    _COORD_ (y2, c_y2)
    SETWIN(aGLXWindowId)
    bbox2(c_xmin, c_ymin, c_x1, c_y1, c_x2, c_y2);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBbox2iXmin: xmin ymin: ymin x1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Screencoord c_xmin, c_ymin;
    Icoord c_x1, c_y1, c_x2, c_y2; 

    _SCREENCOORD_ (xmin, c_xmin)
    _SCREENCOORD_ (ymin, c_ymin)
    _ICOORD_ (x1, c_x1)
    _ICOORD_ (y1, c_y1)
    _ICOORD_ (x2, c_x2)
    _ICOORD_ (y2, c_y2)
    SETWIN(aGLXWindowId)
    bbox2i(c_xmin, c_ymin, c_x1, c_y1, c_x2, c_y2);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBbox2sXmin: xmin ymin: ymin x1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Screencoord c_xmin, c_ymin;
    Scoord c_x1, c_y1, c_x2, c_y2; 

    _SCREENCOORD_ (xmin, c_xmin)
    _SCREENCOORD_ (ymin, c_ymin)
    _SCOORD_ (x1, c_x1)
    _SCOORD_ (y1, c_y1)
    _SCOORD_ (x2, c_x2)
    _SCOORD_ (y2, c_y2)
    SETWIN(aGLXWindowId)
    bbox2s(c_xmin, c_ymin, c_x1, c_y1, c_x2, c_y2);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBeginTrimIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    bgntrim();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxEndTrimIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    endtrim();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBlankscreen: b in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    blankscreen(_booleanVal(b));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBlanktime: count in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    blanktime(_intVal(count));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBlendcolorRed: red green: green blue: blue alpha: alpha in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    blendcolor(_floatVal(red), _floatVal(green), _floatVal(blue), _floatVal(alpha)); 
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBlendfunctionSfactr: sfactr dfactr: dfactr in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    blendfunction(_intVal(sfactr), _intVal(dfactr));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBlinkRate: rate i: i red: red green: green blue: blue in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    blink(_shortVal(rate), _colorindexVal(i), 
	  _shortVal(red), _shortVal(green), _shortVal(blue));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxBlkqreadData: data n: n in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(blkqread((short *)_indexedArea(data), _intVal(n))));
#endif
%}
.
    ^ false
! 

glxC3s: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    short vec[3], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    c3s(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxC3i: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    long vec[3], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    c3i(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxC3f: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[3], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    c3f(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxC4s: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    short vec[4], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    c4s(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxC4i: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    long vec[4], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    c4i(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxC4f: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[4], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    c4f(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxCallObject:obj in:aGLXWindowId
    "do objects definition
     I defined that one too - but with a different name"

%{  /* NOCONTEXT */
    if (_isSmallInteger(obj)) {
	SETWIN(aGLXWindowId)
	callobj(_objectVal(obj));
	RETURN (true);
    }
%}
.
    ^ false
!

glxCallobj: obj in: aGLXWindowId

%{  /* NOCONTEXT */
    if (_isSmallInteger(obj)) {
	SETWIN(aGLXWindowId)
	callobj(_objectVal(obj));
	RETURN (true);
    }
%}
.
    ^ false
!

glxClearhitcodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    clearhitcode();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxClipplaneIndex: index mode: mode params: params in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[4], *v;

    if (! (v = getFloatsFromInto(params, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    clipplane(_intVal(index), _intVal(mode), v);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCloseObjectIn:aGLXWindowId
    "end object defnition - JEFF and I defined this with different names"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    closeobj();
    RETURN (true);
%}
.
    ^ false
!

glxCloseobjIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    closeobj();
    RETURN (true);
%}
.
    ^ false
! 

glxCmodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    cmode();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCmovX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    cmov(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxCmoviX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    cmovi(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxCmovsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    cmovs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxCmov2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    cmov2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxCmov2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    cmov2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxCmov2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    cmov2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxColorfIndex: index in: aGLXWindowId

    ^self glxColor: index in: aGLXWindowId
! 

glxConcave: b in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    concave(_booleanVal(b));
    RETURN (true);
%}
.
    ^ false
! 

glxCuroriginN: n xorigin: xorigin yorigin: yorigin in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    curorigin(_shortVal(n), _shortVal(xorigin), _shortVal(yorigin));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCursoffIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    cursoff();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCursonIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    curson();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCurstype: type in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    curstype(_intVal(type));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCurvebasis: basid in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    curvebasis(_shortVal(basid));
    RETURN (true);
%}
.
    ^ false
! 

glxCurveit: iterationcount in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    curveit(_shortVal(iterationcount));
    RETURN (true);
%}
.
    ^ false
! 

glxCurveprecision: nsegments in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    curveprecision(_shortVal(nsegments));
    RETURN (true);
%}
.
    ^ false
! 

glxCyclemapDuration: duration map: map nxtmap: nxtmap in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    cyclemap(_shortVal(duration), _shortVal(map), _shortVal(nxtmap));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxCzclearCval: cval zval: zval in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    czclear((ulong)_intVal(cval), _intVal(zval));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxDeflinestyleN: n ls: ls in: aGLXWindowId
    "define a line style"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    deflinestyle(_shortVal(n), _linestyleVal(ls));
    RETURN (true);
%}
.
    ^ false
! 

glxDefpatternN: n size: size mask: mask in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    defpattern(_shortVal(n), _shortVal(size), (unsigned short *)_indexedArea(mask));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxDelobj: obj in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    delobj(_objectVal(obj));
    RETURN (true);
%}
.
    ^ false
!

glxDeltag: t in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    deltag(_tagVal(t));
    RETURN (true);
#endif
%}
.
    ^ false
!

glxDepthcueMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    depthcue(_booleanVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxDitherMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    dither(_longVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxDopup: pup in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    dopup(_longVal(pup));
    RETURN (true);
#endif
%}
.
    ^ false
!

glxDrawX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    draw(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxDrawiX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    drawi(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxDrawsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    draws(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxDraw2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    draw2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxDraw2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    draw2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxDraw2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    draw2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxDrawmode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    drawmode(_longVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxEditobj: obj in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    editobj(_objectVal(obj));
    RETURN (true);
#endif
%}
.
    ^ false
!

glxEndfullscrnIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    endfullscrn();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxFullscrnIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    fullscrn();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxEndpupmodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    endpupmode();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPupmodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pupmode();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxFinishIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    finish();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxFont: fntnum in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    font(_shortVal(fntnum));
    RETURN (true);
%}
.
    ^ false
! 

glxForegroundIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    foreground();
    RETURN (true);
%}
.
    ^ false
! 

glxFreepup: pup in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    freepup(_longVal(pup));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxFrontface: b in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    frontface(_booleanVal(b));
    RETURN (true);
%}
.
    ^ false
! 

glxFudgeXfudge: xfudge yfudge: yfudge in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    fudge(_longVal(xfudge), _longVal(yfudge));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGbeginIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    gbegin();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGetbackfaceIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getbackface()));
#endif
%}
.
    ^ false
! 

glxGenobjIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(genobj()));
%}
.
    ^ false
! 

glxGentagIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(gentag()));
#endif
%}
.
    ^ false
! 

glxGetbufferIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getbuffer()));
#endif
%}
.
    ^ false
! 

glxGetbutton: num in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getbutton(_deviceVal(num))));
%}
.
    ^ false
! 

glxGetcmmodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(getcmmode()));
#endif
%}
.
    ^ false
! 

glxGetcolorIn: aGLXWindowId
    "return the current drawing color"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getcolor()));
%}
.
    ^ false
! 

glxGetcposIn: aGLXWindowId

    | x y |
%{ 
#ifdef GLX
    short s_x, s_y;
    SETWIN(aGLXWindowId)
    getcpos(&s_x, &s_y);
    x = _MKSMALLINT(s_x);
    y = _MKSMALLINT(s_y);
#endif
%}
.
    ^x @ y
! 

glxGetdcmIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(getdcm()));
#endif
%}
.
    ^ false
! 

glxGetdescenderIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getdescender()));
#endif
%}
.
    ^ false
! 

glxGetdisplaymodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getdisplaymode()));
#endif
%}
.
    ^ false
! 

glxGetdrawmodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getdrawmode()));
#endif
%}
.
    ^ false
! 

glxGetfontIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getfont()));
#endif
%}
.
    ^ false
! 

glxGetgconfigBuffer: buffer in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getgconfig(_longVal(buffer))));
#endif
%}
.
    ^ false
! 

glxGetgdescInquiry: inquiry in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getgdesc(_longVal(inquiry))));
%}
.
    ^ false
! 

glxGetheightIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getheight()));
%}
.
    ^ false
! 

glxGethitcodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(gethitcode()));
#endif
%}
.
    ^ false
! 

glxGetlsbackupIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(getlsbackup()));
#endif
%}
.
    ^ false
! 

glxGetlsrepeatIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getlsrepeat()));
#endif
%}
.
    ^ false
! 

glxGetlstyleIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getlstyle()));
#endif
%}
.
    ^ false
! 

glxGetlwidthIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getlwidth()));
#endif
%}
.
    ^ false
! 

glxGetmapIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getmap()));
#endif
%}
.
    ^ false
! 

glxGetmmodeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getmmode()));
#endif
%}
.
    ^ false
! 

glxGetmonitorIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getmonitor()));
#endif
%}
.
    ^ false
! 

glxGetmultisampleIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(getmultisample()));
#endif
%}
.
    ^ false
! 

glxGetopenobjIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getopenobj()));
#endif
%}
.
    ^ false
! 

glxGetothermonitorIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getothermonitor()));
#endif
%}
.
    ^ false
! 

glxGetpatternIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getpattern()));
#endif
%}
.
    ^ false
! 

glxGetplanesIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getplanes()));
#endif
%}
.
    ^ false
! 

glxGetresetlsIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(getresetls()));
#endif
%}
.
    ^ false
! 

glxGetshadeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getshade()));
#endif
%}
.
    ^ false
! 

glxGetsmIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getsm()));
#endif
%}
.
    ^ false
! 

glxGetvaluator: dev in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getvaluator(_deviceVal(dev))));
%}
.
    ^ false
! 

glxGetvideo: reg in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getvideo(_longVal(reg))));
#endif
%}
.
    ^ false
! 

glxGetwritemaskIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getwritemask()));
#endif
%}
.
    ^ false
! 

glxGetwscrnIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(getwscrn()));
#endif
%}
.
    ^ false
! 

glxGetzbufferIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(getzbuffer()));
#endif
%}
.
    ^ false
! 

glxGexitIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    gexit();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGflushIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    gflush();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGinitIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    ginit();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGlcompatMode: mode value: value in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    glcompat(_longVal(mode), _longVal(value));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGresetIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    greset();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxGsyncIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    gsync();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxIconsizeX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    iconsize(_longVal(x), _longVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxImakebackgroundIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    imakebackground();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxInitnamesIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    initnames();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxIsobj: obj in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(isobj(_objectVal(obj))));
%}
.
    ^ false
! 

glxIsqueued: dev in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(isqueued(_deviceVal(dev))));
#endif
%}
.
    ^ false
! 

glxIstag: t in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKBOOLEAN(istag(_tagVal(t))));
#endif
%}
.
    ^ false
! 

glxKeepaspectX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    keepaspect(_longVal(x), _longVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLeftbuffer: bool in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    leftbuffer(_booleanVal(bool));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRightbuffer: bool in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    rightbuffer(_booleanVal(bool));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLinesmoothMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    linesmooth((ulong)_intVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLinewidth: n in: aGLXWindowId
    "set the linewidth"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    linewidth(_shortVal(n));
    RETURN (true);
%}
.
    ^ false
! 

glxLinewidthf: n in: aGLXWindowId
    "set the linewidth"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    linewidthf(_floatVal(n));
    RETURN (true);
%}
.
    ^ false
! 

glxLmcolorMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    lmcolor(_longVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLoadname: name in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    loadname(_shortVal(name));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLogicop: opcode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    logicop(_longVal(opcode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLrgbrangeRmin: rmin gmin: gmin bmin: bmin rmax: rmax gmax: gmax bmax: bmax
    znear: znear zfar: zfar in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    lRGBrange(_shortVal(rmin), _shortVal(gmin), _shortVal(bmin), 
	_shortVal(rmax), _shortVal(gmax), _shortVal(bmax), 
	_longVal(znear), _longVal(zfar));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLsbackup: b in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    lsbackup(_booleanVal(b));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLsetdepthNear: near far: far in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    lsetdepth(_longVal(near), _longVal(far));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLshaderangeLowin: lowin hiwin: hiwin znear: znear zfar: zfar in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    lshaderange(_colorindexVal(lowin), _colorindexVal(hiwin), 
	_longVal(znear), _longVal(zfar));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxLsrepeatFactor: factor in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    lsrepeat(_longVal(factor));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMakeObject:id in:aGLXWindowId
    "start object definition -
     another name conflict"

%{  /* NOCONTEXT */
    if (_isSmallInteger(id)) {
	SETWIN(aGLXWindowId)
	makeobj(_objectVal(id));
	RETURN (true);
    }
%}
.
    ^ false
!

glxMakeobj: obj in: aGLXWindowId
    "start object definition"

%{  /* NOCONTEXT */
    if (_isSmallInteger(obj)) {
	SETWIN(aGLXWindowId)
	makeobj(_objectVal(obj));
	RETURN (true);
    }
%}
.
    ^ false
! 

glxMaketag: t in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    maketag(_tagVal(t));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMapcolorI: i red: red green: green blue: blue in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    mapcolor(_colorindexVal(i), _shortVal(red), _shortVal(green), _shortVal(blue));
    RETURN (true);
%}
.
    ^ false
! 

glxMaxsizeX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    maxsize(_longVal(x), _longVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMinsizeX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    minsize(_longVal(x), _longVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMonobufferIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    monobuffer();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMoveX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    move(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxMoveiX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    movei(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxMovesX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    moves(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxMove2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    move2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxMove2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    move2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxMove2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    move2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxMsalphaMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    msalpha(_longVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMsmask: mask inverse: inverse in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    msmask(_floatVal(mask), _booleanVal(inverse));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMspattern: pattern in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    mspattern(_longVal(pattern));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMssizeSamples: samples zsize: zsize ssize: ssize in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    mssize(_longVal(samples), _longVal(zsize), _longVal(ssize));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMswapbuffers: fbuf in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    mswapbuffers(_longVal(fbuf));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMultimapIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    multimap();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxMultisample: bool in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    multisample(_booleanVal(bool));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxNewpupIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(newpup()));
#endif
%}
.
    ^ false
! 

glxNewtag: newtg oldtg: oldtg offst: offst in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    newtag(_tagVal(newtg), _tagVal(oldtg), _offsetVal(offst));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxNoborderIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    noborder();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxNoise: v delta: delta in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    noise(_deviceVal(v), _shortVal(delta));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxNoportIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    noport();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxNurbscurveKnotCount: knotCount knotList: knotList
    offset: offset ctlArray: ctlArray 
    order: order type: type in: aGLXWindowId

    | ctlPoints i |
    ctlPoints := DoubleArray new: ctlArray size * (ctlArray first size).
    i := 1.
    ctlArray do: [:point |
	point do: [:coord | 
	    ctlPoints at: i put: coord.
	    i := i + 1]].

%{  /* NOCONTEXT */
#ifdef GLX
    char *knotElements, *ctlElements;
    OBJ cls;
    int ninstVars, nInstBytes;

    SETWIN(aGLXWindowId)
    cls = _qClass(ctlPoints);
    ninstVars = _intVal(_ClassInstPtr(cls)->c_ninstvars);
    nInstBytes = OHDR_SIZE + ninstVars * sizeof(OBJ);

    ctlElements = (char *)(_InstPtr(ctlPoints)) + nInstBytes;
    knotElements = (char *)(_InstPtr(knotList)) + nInstBytes;

    nurbscurve (
	_longVal(knotCount), (double *)knotElements,
	_longVal(offset), (double *)ctlElements, 
	_longVal(order), _longVal(type));
    RETURN(true);
#endif
%}
.
    ^ false
! 

glxObjdeleteTag1: tag1 tag2: tag2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    objdelete(_tagVal(tag1), _tagVal(tag2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxObjinsert: t in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    objinsert(_tagVal(t));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxObjreplace: t in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    objreplace(_tagVal(t));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxOnemapIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    onemap();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxOverlayPlanes: planes in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    overlay(_longVal(planes));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPagecolor: pcolor in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pagecolor(_colorindexVal(pcolor));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPassthroughToken: token in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    passthrough(_shortVal(token));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPclosIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pclos();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPdrX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pdr(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPdriX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pdri(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPdrsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pdrs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPdr2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pdr2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPdr2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pdr2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPdr2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pdr2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPicksizeX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    picksize(_shortVal(x), _shortVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPixmode: mode value: value in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pixmode(_longVal(mode), _longVal(value));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPmvX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pmv(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPmviX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pmvi(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPmvsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pmvs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPmv2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pmv2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPmv2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pmv2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPmv2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pmv2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPntX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pnt(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPntiX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pnti(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPntsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    pnts(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxPnt2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pnt2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPnt2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pnt2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPnt2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    pnt2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxPntsize: n in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pntsize(_shortVal(n));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPntsizef: n in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pntsizef(_floatVal(n));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPntsmoothMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pntsmooth((ulong)_intVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPolarviewDist: dist azim: azim inc: inc twist: twist in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_dist;
    Angle a_azim, a_inc, a_twist;

    _COORD_(dist, c_dist)
    _ANGLE_(azim, a_azim)
    _ANGLE_(inc, a_inc)
    _ANGLE_(twist, a_twist)
    SETWIN(aGLXWindowId)
    polarview(c_dist, a_azim, a_inc, a_twist);
    RETURN (true);
%}
.
    ^ false
! 

glxPolymode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    polymode(_longVal(mode));
    RETURN (true);
%}
.
    ^ false
! 

glxPolysmoothMode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    polysmooth(_longVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPopattributesIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    popattributes();
    RETURN (true);
%}
.
    ^ false
! 

glxPopnameIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    popname();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPopviewportIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    popviewport();
    RETURN (true);
%}
.
    ^ false
! 

glxPrefpositionX1: x1 x2: x2 y1: y1 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    prefposition(_longVal(x1), _longVal(x2), _longVal(y1), _longVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxPrefsizeX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    prefsize(_longVal(x), _longVal(y));
    RETURN (true);
%}
.
    ^ false
! 

glxPushattributesIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    pushattributes();
    RETURN (true);
%}
.
    ^ false
! 

glxPushname: name In: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    pushname(_shortVal(name));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxPushviewportIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    pushviewport();
    RETURN (true);
%}
.
    ^ false
! 

glxQdevice: dev in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    qdevice(_deviceVal(dev));
    RETURN (true);
%}
.
    ^ false
! 

glxQenterDev: dev val: val in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    qenter(_deviceVal(dev), _shortVal(val));
    RETURN (true);
%}
.
    ^ false
! 

glxQgetfdIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(qgetfd()));
#endif
%}
.
    ^ false
! 

glxQreadIn: aGLXWindowId

    | dev data |
%{ 
    short c_data;

    SETWIN(aGLXWindowId)
    dev = _MKSMALLINT(qread(&c_data));
    data = _MKSMALLINT(c_data);
%}
.
    ^ Array with: dev with: data
! 

glxQresetIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    qreset();
    RETURN (true);
%}
.
    ^ false
! 

glxQtestIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(qtest()));
%}
.
    ^ false
! 

glxRdrX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rdr(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRdriX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rdri(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRdrsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rdrs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRdr2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rdr2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRdr2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rdr2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRdr2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rdr2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxReadsource: src in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    readsource(_longVal(src));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRectX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    rect(_coordVal(x1), _coordVal(y1), _coordVal(x2), _coordVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxRectiX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    recti(_icoordVal(x1), _icoordVal(y1), _icoordVal(x2), _icoordVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxRectsX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    rects(_scoordVal(x1), _scoordVal(y1), _scoordVal(x2), _scoordVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxRectfX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    rectf(_coordVal(x1), _coordVal(y1), _coordVal(x2), _coordVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxRectfiX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    rectfi(_icoordVal(x1), _icoordVal(y1), _icoordVal(x2), _icoordVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxRectfsX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    rectfs(_scoordVal(x1), _scoordVal(y1), _scoordVal(x2), _scoordVal(y2));
    RETURN (true);
%}
.
    ^ false
! 

glxRectcopyX1: x1 y1: y1 x2: x2 y2: y2 newx: newx newy: newy in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    rectcopy(_screencoordVal(x1), _screencoordVal(y1), 
	_screencoordVal(x2), _screencoordVal(y2), 
	_screencoordVal(newx), _screencoordVal(newy));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRectzoomX: xfactor y: yfactor in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    rectzoom(_floatVal(xfactor), _floatVal(yfactor));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxResetls: b in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    resetls(_booleanVal(b));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRGBcursorIndex: index red: red green: green blue: blue 
    redm: redm greenm: greenm bluem: bluem in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RGBcursor(_shortVal(index), 
	_shortVal(red), _shortVal(green), _shortVal(blue), 
	_shortVal(redm), _shortVal(greenm), _shortVal(bluem));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRGBwritemaskRed: red green: green blue: blue in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RGBwritemask(_shortVal(red), _shortVal(green), _shortVal(blue));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRingbellIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    ringbell();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxRmvX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rmv(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRmviX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rmvi(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRmvsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rmvs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRmv2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rmv2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRmv2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rmv2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRmv2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rmv2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRpdrX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rpdr(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRpdriX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rpdri(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRpdrsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rpdrs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRpdr2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rpdr2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRpdr2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rpdr2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRpdr2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rpdr2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRpmvX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rpmv(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRpmviX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rpmvi(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRpmvsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    rpmvs(c_x, c_y, c_z);
    RETURN (true);
%}
.
    ^ false
! 

glxRpmv2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rpmv2(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRpmv2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rpmv2i(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxRpmv2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    rpmv2s(c_x, c_y);
    RETURN (true);
%}
.
    ^ false
! 

glxSboxX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sbox(_coordVal(x1), _coordVal(y1), _coordVal(x2), _coordVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSboxiX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sboxi(_icoordVal(x1), _icoordVal(y1), _icoordVal(x2), _icoordVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSboxsX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sboxs(_scoordVal(x1), _scoordVal(y1), _scoordVal(x2), _scoordVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSboxfX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sboxf(_coordVal(x1), _coordVal(y1), _coordVal(x2), _coordVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSboxfiX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sboxfi(_icoordVal(x1), _icoordVal(y1), _icoordVal(x2), _icoordVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSboxfsX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sboxfs(_scoordVal(x1), _scoordVal(y1), _scoordVal(x2), _scoordVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSclearSval: sval in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sclear((ulong)_intVal(sval));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxScrbox: arg in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    scrbox(_longVal(arg));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxScreenspaceIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    screenspace();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxScrmaskLeft: left right: right bottom: bottom top: top in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    scrmask(_screencoordVal(left), _screencoordVal(right), 
	_screencoordVal(bottom), _screencoordVal(top));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxScrnattach: gsnr in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    scrnattach(_longVal(gsnr));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxScrnselect: gsnr in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    scrnselect(_longVal(gsnr));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetcursorIndex: index color: color wtn: wtn in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setcursor(_shortVal(index), _colorindexVal(color), _colorindexVal(wtn));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetdblightsMask: mask in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setdblights((ulong)_intVal(mask));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetdepthNear: near far: far in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setdepth(_screencoordVal(near), _screencoordVal(far));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetlinestyle: index in: aGLXWindowId
    "set the linestyle"

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    setlinestyle(_shortVal(index));
    RETURN (true);
%}
.
    ^ false
! 

glxSetmap: mapnum in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setmap(_shortVal(mapnum));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetmonitor: mtype in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setmonitor(_shortVal(mtype));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetnurbsproperty: property value: value in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setnurbsproperty(_longVal(property), _floatVal(value));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetpattern: index in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setpattern(_shortVal(index));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetpup: pup entry: entry mode: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setpup(_longVal(pup), _longVal(entry), (ulong)_intVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetvaluator: v init: init vmin: vmin vmax: vmax in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setvaluator(_deviceVal(v), _shortVal(init), _shortVal(vmin), _shortVal(vmax));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSetvideo: reg value: value in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    setvideo(_longVal(reg), _longVal(value));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxShademodel: model in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    shademodel(_longVal(model));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxShaderangeLowin: lowin hiwin: hiwin z1: z1 z2: z2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    shaderange(_colorindexVal(lowin), _colorindexVal(hiwin), 
	_screencoordVal(z1), _screencoordVal(z2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSinglebufferIn: aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    singlebuffer();
    RETURN (true);
%}
.
    ^ false
!

glxSmoothline: mode in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    smoothline(_longVal(mode));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSphfreeIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sphfree();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSphgnpolysIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(sphgnpolys()));
#endif
%}
.
    ^ false
! 

glxSphmode: attribute value: value in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sphmode(_intVal(attribute), _intVal(value));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSphobj: objid in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    sphobj(_objectVal(objid));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSphrotmatrix: mat in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Matrix matrix, *m;

    if (! (m = getFloatsFromMatrixInto(mat, &matrix))) RETURN (false);
    SETWIN(aGLXWindowId)
    sphrotmatrix(*m);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxStencilEnable: enable ref: ref func: func mask: mask fail: fail 
    pass: pass zpass: zpass in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    stencil(_longVal(enable), (ulong)_intVal(ref), _longVal(func), 
	(ulong)_intVal(mask), _longVal(fail), _longVal(pass), _longVal(zpass));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxStensize: planes in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    stensize(_longVal(planes));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxStepunitX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    stepunit(_longVal(x), _longVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxStereobufferIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    stereobuffer();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSubpixel: b in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    subpixel(_booleanVal(b));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSwapinterval: i in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    swapinterval(_shortVal(i));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSwaptmeshIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    swaptmesh();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSwinopen: parent in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    swinopen(_longVal(parent));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxSwritemask: mask in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    swritemask((ulong)_intVal(mask));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxT2s: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    short vec[2], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    t2s(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT2i: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    long vec[2], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    t2i(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT2f: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[2], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    t2f(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT2d: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    double vec[2], *c_v;

    if (! (c_v = getDoublesFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    t2d(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT3s: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    short vec[3], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    t3s(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT3i: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    long vec[3], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    t3i(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT3f: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    float vec[3], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    t3f(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT3d: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    double vec[3], *c_v;

    if (! (c_v = getDoublesFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    t3d(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT4s: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    short vec[4], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    t4s(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT4i: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    long vec[4], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    t4i(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT4f: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    float vec[4], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    t4f(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxT4d: v in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    double vec[4], *c_v;

    if (! (c_v = getDoublesFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    t4d(c_v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxTexDef2dIndex: index nc:nc width:w height:h bits:image np:np props:props in: aGLXWindowId
    "bind a texture"

%{  /* NOCONTEXT */
#ifdef GLX
    unsigned char *cp;
    const float *fp;
    OBJ cls;
    float fbuff[30];

    if (__isByteArray(image)) {
	cp = _ByteArrayInstPtr(image)->ba_element;
	fp = getFloatsFromFloatArrayInto(props, fbuff);

	SETWIN(aGLXWindowId)
	texdef2d(_longVal(index), _longVal(nc), _longVal(w), _longVal(h),
		 (const unsigned long *)cp, _longVal(np), fp);
	RETURN (true);
    }
#endif
%}
.
    ^ false
! 

glxTevbind: target index: index in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    tevbind(_longVal(target), _longVal(index));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTexbind: target index: index in: aGLXWindowId
    "bind a texture"

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    texbind(_longVal(target), _longVal(index));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTextcolor: tcolor in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    textcolor(_colorindexVal(tcolor));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTextinitIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    textinit();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTextportLeft: left right: right bottom: bottom top: top in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    textport(_screencoordVal(left), _screencoordVal(right), 
	_screencoordVal(bottom), _screencoordVal(top));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTieB: b v1: v1 v2: v2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    tie(_deviceVal(b), _deviceVal(v1), _deviceVal(v2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTlutbind: target index: index in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef FULL_GLX
    SETWIN(aGLXWindowId)
    tlutbind(_longVal(target), _longVal(index));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTpoffIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    tpoff();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxTponIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    tpon();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxUnderlay: planes in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    underlay(_longVal(planes));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxUnqdevice: dev in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    unqdevice(_deviceVal(dev));
    RETURN (true);
#endif
%}
.
    ^ false
!

glxVideocmd:cmd in:aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    videocmd(_longVal(cmd));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxViewportLeft:left right:right bottom:bottom top:top in:aGLXWindowId

%{  /* NOCONTEXT */
    SETWIN(aGLXWindowId)
    viewport(_screencoordVal(left), _screencoordVal(right), 
	     _screencoordVal(bottom), _screencoordVal(top));
    RETURN (true);
%}
! 

glxWinclose:gwid in:aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winclose(_longVal(gwid));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWinconstraintsIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winconstraints();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWindepth: gwid in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(windepth(_longVal(gwid))));
#endif
%}
.
    ^ false
! 

glxWingetIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    RETURN (_MKSMALLINT(winget()));
#endif
%}
.
    ^ false
! 

glxWinmoveX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winmove(_longVal(x), _longVal(y));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWinpopIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winpop();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWinpositionX1: x1 y1: y1 x2: x2 y2: y2 in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winposition(_longVal(x1), _longVal(y1), _longVal(x2), _longVal(y2));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWinpushIn: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winpush();
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWinset: gwid in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    winset(_longVal(gwid));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWmpack: pack in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    wmpack((ulong)_intVal(pack));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxWritemask: wtm in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    SETWIN(aGLXWindowId)
    writemask(_colorindexVal(wtm));
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfptX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Coord c_x, c_y, c_z;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    xfpt(c_x, c_y, c_z);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfptiX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Icoord c_x, c_y, c_z;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    xfpti(c_x, c_y, c_z);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfptsX: x y: y z: z in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Scoord c_x, c_y, c_z;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    SETWIN(aGLXWindowId)
    xfpts(c_x, c_y, c_z);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfpt2X: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Coord c_x, c_y;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    xfpt2(c_x, c_y);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfpt2iX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Icoord c_x, c_y;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    xfpt2i(c_x, c_y);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfpt2sX: x y: y in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Scoord c_x, c_y;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    SETWIN(aGLXWindowId)
    xfpt2s(c_x, c_y);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfpt4X: x y: y z: z w: w in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Coord c_x, c_y, c_z, c_w;

    _COORD_ (x, c_x)
    _COORD_ (y, c_y)
    _COORD_ (z, c_z)
    _COORD_ (w, c_w)
    SETWIN(aGLXWindowId)
    xfpt4(c_x, c_y, c_z, c_w);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfpt4iX: x y: y z: z w: w in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Icoord c_x, c_y, c_z, c_w;

    _ICOORD_ (x, c_x)
    _ICOORD_ (y, c_y)
    _ICOORD_ (z, c_z)
    _ICOORD_ (w, c_w)
    SETWIN(aGLXWindowId)
    xfpt4i(c_x, c_y, c_z, c_w);
    RETURN (true);
#endif
%}
.
    ^ false
! 

glxXfpt4sX: x y: y z: z w: w in: aGLXWindowId

%{  /* NOCONTEXT */
#ifdef GLX
    Scoord c_x, c_y, c_z, c_w;

    _SCOORD_ (x, c_x)
    _SCOORD_ (y, c_y)
    _SCOORD_ (z, c_z)
    _SCOORD_ (w, c_w)
    SETWIN(aGLXWindowId)
    xfpt4s(c_x, c_y, c_z, c_w);
    RETURN (true);
#endif
%}
.
    ^ false
! !

!GLXWorkstation methodsFor:'vertex data transfer '!

glxV2s:v in:aGLXWindowId
    "pass a vertex; v must be a vector with 2 shorts; z is taken as 0"

%{  /* NOCONTEXT */
    short vec[2], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    v2s(c_v);
    RETURN (true);
%}
!

glxV2i:v in:aGLXWindowId
    "pass a vertex; v must be a vector with 2 longs; z is taken as 0"

%{  /* NOCONTEXT */
    long vec[2], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    v2i(c_v);
    RETURN (true);
%}
!

glxV2f:v in:aGLXWindowId
    "pass a vertex; v must be a vector with 2 floats; z is taken as 0"

%{  /* NOCONTEXT */
    float vec[2], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    v2f(c_v);
    RETURN (true);
%}
!

glxV2d:v in:aGLXWindowId
    "pass a vertex; v must be a vector with 2 doubles; z is taken as 0"

%{  /* NOCONTEXT */
    double vec[2], *c_v;

    if (! (c_v = getDoublesFromInto(v, vec, 2))) RETURN(false);
    SETWIN(aGLXWindowId)
    v2d(c_v);
    RETURN (true);
%}
!

glxV2fX:x y:y in:aGLXWindowId
    "pass a vertex from individual x and y values; z is taken as 0.0"

%{  /* NOCONTEXT */
    float vec[2];

    _FLOAT_(x, vec[0])
    _FLOAT_(y, vec[1])
    SETWIN(aGLXWindowId)
    v2f(vec);
    RETURN (true);
%}
!

glxV3s:v in:aGLXWindowId
    "pass a vertex; v must be a vector with 3 shorts"

%{  /* NOCONTEXT */
    short vec[3], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    v3s(c_v);
    RETURN (true);
%}
!

glxV3i:v in:aGLXWindowId
    "pass a vertex; v must be a vector with 3 longs"

%{  /* NOCONTEXT */
    long vec[3], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    v3i(c_v);
    RETURN (true);
%}
!

glxV3f:v in:aGLXWindowId
    "pass a vertex; v must be a 3-element float-vector"

%{  /* NOCONTEXT */
    float vec[3], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    v3f(c_v);
    RETURN (true);
%}
!

glxV3fX:x y:y z:z in: aGLXWindowId
    "pass a vector from individual x, y and z (float) values"

%{  /* NOCONTEXT */
    float vec[3];

    _FLOAT_(x, vec[0])
    _FLOAT_(y, vec[1])
    _FLOAT_(z, vec[2])
    SETWIN(aGLXWindowId)
    v3f(vec);
    RETURN (true);
%}
!

glxVOriginIn:aGLXWindowId
    "pass a 0.0/0.0/0.0 vector.
     This is the same as v3f:#(0.0 0.0 0.0), but, since its so
     common, this somewhat faster method has been provided"

%{  /* NOCONTEXT */
    static float vec[3] = {0.0, 0.0, 0.0};

    SETWIN(aGLXWindowId)
    v3f(vec);
    RETURN (true);
%}
!

glxVUnitXIn:aGLXWindowId
    "pass a 1.0/0.0/0.0 vector.
     This is the same as v3f:#(1.0 0.0 0.0), but, since its so
     common, this somewhat faster method has been provided"

%{  /* NOCONTEXT */
    static float vec[3] = {1.0, 0.0, 0.0};

    SETWIN(aGLXWindowId)
    v3f(vec);
    RETURN (true);
%}
!

glxVUnitYIn:aGLXWindowId
    "pass a 0.0/1.0/0.0 vector.
     This is the same as v3f:#(0.0 1.0 0.0), but, since its so
     common, this somewhat faster method has been provided"

%{  /* NOCONTEXT */
    static float vec[3] = {0.0, 1.0, 0.0};

    SETWIN(aGLXWindowId)
    v3f(vec);
    RETURN (true);
%}
!

glxVUnitZIn:aGLXWindowId
    "pass a 0.0/0.0/1.0 vector.
     This is the same as v3f:#(0.0 0.0 1.0), but, since its so
     common, this somewhat faster method has been provided"

%{  /* NOCONTEXT */
    static float vec[3] = {0.0, 0.0, 1.0};

    SETWIN(aGLXWindowId)
    v3f(vec);
    RETURN (true);
%}
!

glxV3d:v in:aGLXWindowId
    "pass a vertex; v must be a 3-element double-vector"

%{  /* NOCONTEXT */
    double vec[3], *c_v;

    if (! (c_v = getDoublesFromInto(v, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    v3d(c_v);
    RETURN (true);
%}
.
    ^ false
!

glxN3f:arrayOf3Floats in:aGLXWindowId
    "argument must be an array of 3 floats containing the
     current vertex normal - in real GL only"

%{  /* NOCONTEXT */
#ifdef GLX
    float vec[3], *v;

    if (! (v = getFloatsFromInto(arrayOf3Floats, vec, 3))) RETURN(false);
    SETWIN(aGLXWindowId)
    n3f(v);
    RETURN (true);
#endif
%}
.
    ^ false
!

glxV4s:v in:aGLXWindowId
    "pass a vertex; v must be a 4-element short-vector,
     containing x, y, z and w"

%{  /* NOCONTEXT */
    short vec[4], *c_v;

    if (! (c_v = getShortsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    v4s(c_v);
    RETURN (true);
%}
!

glxV4i:v in:aGLXWindowId
    "pass a vertex; v must be a 4-element int-vector,
     containing x, y, z and w"

%{  /* NOCONTEXT */
    long vec[4], *c_v;

    if (! (c_v = getLongsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    v4i(c_v);
    RETURN (true);
%}
!

glxV4f:v in:aGLXWindowId
    "pass a vertex; v must be a 4-element float-vector,
     containing x, y, z and w"

%{  /* NOCONTEXT */
    float vec[4], *c_v;

    if (! (c_v = getFloatsFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    v4f(c_v);
    RETURN (true);
%}
!

glxV4d:v in:aGLXWindowId
    "pass a vertex; v must be a 4-element double-vector,
     containing x, y, z and w"

%{  /* NOCONTEXT */
    double vec[4], *c_v;

    if (! (c_v = getDoublesFromInto(v, vec, 4))) RETURN(false);
    SETWIN(aGLXWindowId)
    v4d(c_v);
    RETURN (true);
%}
! !