NAME
	  fglBlendFunc - specify pixel arithmetic


     FORTRAN SPECIFICATION
	  SUBROUTINE fglBlendFunc( INTEGER*4 sfactor,
				   INTEGER*4 dfactor )


     PARAMETERS
	  sfactor  Specifies how the red, green, blue, and alpha
		   source blending factors are computed.  Nine
		   symbolic constants are accepted:  GL_ZERO, GL_ONE,
		   GL_DST_COLOR, GL_ONE_MINUS_DST_COLOR, GL_SRC_ALPHA,
		   GL_ONE_MINUS_SRC_ALPHA, GL_DST_ALPHA,
		   GL_ONE_MINUS_DST_ALPHA, and GL_SRC_ALPHA_SATURATE.
		   The initial value is	GL_ONE.

	  dfactor  Specifies how the red, green, blue, and alpha
		   destination blending	factors	are computed.  Eight
		   symbolic constants are accepted:  GL_ZERO, GL_ONE,
		   GL_SRC_COLOR, GL_ONE_MINUS_SRC_COLOR, GL_SRC_ALPHA,
		   GL_ONE_MINUS_SRC_ALPHA, GL_DST_ALPHA, and
		   GL_ONE_MINUS_DST_ALPHA. The initial value is
		   GL_ZERO.

     DESCRIPTION
	  In RGBA mode,	pixels can be drawn using a function that
	  blends the incoming (source) RGBA values with	the RGBA
	  values that are already in the frame buffer (the destination
	  values).  Blending is	initially disabled.  Use fglEnable and
	  fglDisable with argument GL_BLEND to enable and disable
	  blending.

	  fglBlendFunc defines the operation of	blending when it is
	  enabled.  sfactor specifies which of nine methods is used to
	  scale	the source color components.  dfactor specifies	which
	  of eight methods is used to scale the	destination color
	  components.  The eleven possible methods are described in
	  the following	table.	Each method defines four scale
	  factors, one each for	red, green, blue, and alpha.

	  In the table and in subsequent equations, source and
	  destination color components are referred to as
	  (R ,G	,B ,A )	and (R ,G ,B ,A	).  They are understood	to
	  have integer values between 0dand (k ,k ,k ,k	), where
					      R	 G  B  A
					   mc
				     kc	= 2  -1

	  and (mR,mG,mB,mA) is the number of red, green, blue, and
	  alpha	bitplanes.
	  Source and destination scale factors are referred to as
	  (s ,s	,s ,s )	and (d ,d ,d ,d	).  The	scale factors
	  described in the table,Gdenoted (f ,f	,f ,f ), represent
	  either source	or destination factors.G All scale factors
	  have range [0,1].

     ______________________________________________________________________
     |	    parameter	     |		  (f ,	f ,  f ,  f )		   |
     |_______________________|_____________________________________________|
     |	     GL_ZERO	     |		      (0, 0, 0,	0)		   |
     |	      GL_ONE	     |		      (1, 1, 1,	1)		   |
     |	   GL_SRC_COLOR	     |	      (R /k , G	/k , B /k , A /k )	   |
     |GL_ONE_MINUS_SRC_COLOR | (1, 1, 1,s1)R- (R /k , G	/k , B /k , A /k ) |
     |	   GL_DST_COLOR	     |	      (R /k , G	/k , B /k , A /k )   s	A  |
     |GL_ONE_MINUS_DST_COLOR | (1, 1, 1,d1)R- (R /k , G	/k , B /k , A /k ) |
     |	   GL_SRC_ALPHA	     |	      (A /k , A	/k , A /k , A /k )   d	A  |
     |GL_ONE_MINUS_SRC_ALPHA | (1, 1, 1,s1)A- (A /k , A	/k , A /k , A /k ) |
     |	   GL_DST_ALPHA	     |	      (A /k , A	/k , A /k , A /k )   s	A  |
     |GL_ONE_MINUS_DST_ALPHA | (1, 1, 1,d1)A- (A /k , A	/k , A /k , A /k ) |
     |GL_SRC_ALPHA_SATURATE  |		      (i, i, i,d1)A   d	 A   d	A  |
     |_______________________|_____________________________________________|

	  In the table,

		    i =	min(A ,	k -A ) / k
			     s	 A  d	  A
	  To determine the blended RGBA	values of a pixel when drawing
	  in RGBA mode,	the system uses	the following equations:

		    R  = min(k ,  R s +R d )
		    Gd = min(kR,  GssR+GddR)
		    Bd = min(kG,  BssG+BddG)
		    Ad = min(kB,  AssB+AddB)
		     d	      A	   s A	d A
	  Despite the apparent precision of the	above equations,
	  blending arithmetic is not exactly specified,	because
	  blending operates with imprecise integer color values.
	  However, a blend factor that should be equal to 1 is
	  guaranteed not to modify its multiplicand, and a blend
	  factor equal to 0 reduces its	multiplicand to	0.  For
	  example, when	sfactor	is GL_SRC_ALPHA, dfactor is
	  GL_ONE_MINUS_SRC_ALPHA, and A	 is equal to k , the equations
	  reduce to simple replacement:s	      A

		    R  = R
		    Gd = Gs
		    Bd = Bs
		    Ad = As
		     d	  s
     EXAMPLES
	  Transparency is best implemented using blend function
	  (GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA) with primitives
	  sorted from farthest to nearest.  Note that this
	  transparency calculation does	not require the	presence of
	  alpha	bitplanes in the frame buffer.

	  Blend	function (GL_SRC_ALPHA,	GL_ONE_MINUS_SRC_ALPHA)	is
	  also useful for rendering antialiased	points and lines in
	  arbitrary order.

	  Polygon antialiasing is optimized using blend	function
	  (GL_SRC_ALPHA_SATURATE, GL_ONE) with polygons	sorted from
	  nearest to farthest.	(See the fglEnable, fglDisable
	  reference page and the GL_POLYGON_SMOOTH argument for
	  information on polygon antialiasing.)	 Destination alpha
	  bitplanes, which must	be present for this blend function to
	  operate correctly, store the accumulated coverage.

     NOTES
	  Incoming (source) alpha is correctly thought of as a
	  material opacity, ranging from 1.0 (K	), representing
	  complete opacity, to 0.0 (0),	representing complete
	  transparency.

	  When more than one color buffer is enabled for drawing, the
	  GL performs blending separately for each enabled buffer,
	  using	the contents of	that buffer for	destination color.
	  (See fglDrawBuffer.)

	  Blending affects only	RGBA rendering.	 It is ignored by
	  color	index renderers.

     ERRORS
	  GL_INVALID_ENUM is generated if either sfactor or dfactor is
	  not an accepted value.

	  GL_INVALID_OPERATION is generated if fglBlendFunc is
	  executed between the execution of fglBegin and the
	  corresponding	execution of fglEnd.

     ASSOCIATED	GETS
	  fglGet with argument GL_BLEND_SRC
	  fglGet with argument GL_BLEND_DST
	  fglIsEnabled with argument GL_BLEND

     SEE ALSO
	  fglAlphaFunc,	fglClear, fglDrawBuffer, fglEnable,
	  fglLogicOp, fglStencilFunc