Module GL

module GL: sig .. end

OpenGL functions


OpenGL 2.1 Reference Pages

OpenGL Overview

Drawing Functions

type primitive = 
| GL_POINTS
| GL_LINES
| GL_LINE_LOOP
| GL_LINE_STRIP
| GL_TRIANGLES
| GL_TRIANGLE_STRIP
| GL_TRIANGLE_FAN
| GL_QUADS (*

deprecated in core OpenGL 3.

*)
| GL_QUAD_STRIP (*

deprecated in core OpenGL 3.

*)
| GL_POLYGON (*

deprecated in core OpenGL 3.

*)
val glBegin : primitive:primitive -> unit
Deprecated.in core OpenGL 3.

manual page

val glEnd : unit -> unit
Deprecated.in core OpenGL 3.

manual page

val glVertex2 : x:float -> y:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glVertex3 : x:float -> y:float -> z:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glVertex4 : x:float -> y:float -> z:float -> w:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glVertex2v : float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glVertex3v : float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glVertex4v : float * float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glNormal3 : nx:float -> ny:float -> nz:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glNormal3v : v:float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glIndex : c:float -> unit
val glIndexi : c:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glColor3 : r:float -> g:float -> b:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glColor4 : r:float -> g:float -> b:float -> a:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glColor3v : v:float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glColor4v : v:float * float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glColor3c : r:char -> g:char -> b:char -> unit
val glColor4c : r:char -> g:char -> b:char -> a:char -> unit

not clamped to range [0.0 - 1.0] but ['\000' - '\255']

val glColor3cv : v:char * char * char -> unit
Deprecated.in core OpenGL 3.

manual page

val glColor4cv : v:char * char * char * char -> unit
Deprecated.in core OpenGL 3.

manual page

val glEdgeFlag : flag:bool -> unit
Deprecated.in core OpenGL 3.

manual page

val glRasterPos2 : x:float -> y:float -> unit
val glRasterPos3 : x:float -> y:float -> z:float -> unit
val glRasterPos4 : x:float -> y:float -> z:float -> w:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glRasterPos2i : x:int -> y:int -> unit
val glRasterPos3i : x:int -> y:int -> z:int -> unit
val glRasterPos4i : x:int -> y:int -> z:int -> w:int -> unit
val glRasterPos2v : v:float * float -> unit
val glRasterPos3v : v:float * float * float -> unit
val glRasterPos4v : v:float * float * float * float -> unit
val glRasterPos2iv : v:int * int -> unit
val glRasterPos3iv : v:int * int * int -> unit
val glRasterPos4iv : v:int * int * int * int -> unit

All glRasterPos* functions are deprecated in core OpenGL 3.

val glRecti : x1:int -> y1:int -> x2:int -> y2:int -> unit
val glRect : x1:float -> y1:float -> x2:float -> y2:float -> unit
Deprecated.in core OpenGL 3.

manual page

Transformations

type matrix_mode = 
| GL_MODELVIEW
| GL_PROJECTION
| GL_TEXTURE
val glMatrixMode : mode:matrix_mode -> unit
Deprecated.in core OpenGL 3.

manual page

val glViewport : x:int -> y:int -> width:int -> height:int -> unit

manual page

val glOrtho : left:float ->
right:float -> bottom:float -> top:float -> near:float -> far:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glFrustum : left:float ->
right:float -> bottom:float -> top:float -> near:float -> far:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glPushMatrix : unit -> unit
val glPopMatrix : unit -> unit
Deprecated.in core OpenGL 3.

manual page

val glLoadIdentity : unit -> unit
Deprecated.in core OpenGL 3.

manual page

val glRotatev : angle:float -> vec:float * float * float -> unit
val glRotate : angle:float -> x:float -> y:float -> z:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glTranslatev : float * float * float -> unit
val glTranslate : x:float -> y:float -> z:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glScalev : float * float * float -> unit
val glScale : x:float -> y:float -> z:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glMultMatrix : mat:float array array -> unit
Deprecated.in core OpenGL 3.

checks the matrix given is 4x4 with assertions

manual page

val glMultMatrixFlat : float array -> unit
Deprecated.in core OpenGL 3.

same than glMultMatrix but with an array of length 16

manual page

val glMultMatrixFlat_unsafe : float array -> unit
Deprecated.in core OpenGL 3.

same than glMultMatrixFlat but doesn't make any checks.

val glLoadMatrix : mat:float array array -> unit
Deprecated.in core OpenGL 3.

checks the matrix given is 4x4 with assertions

manual page

val glLoadMatrixFlat : float array -> unit
Deprecated.in core OpenGL 3.

as glLoadMatrix but with an array of length 16

manual page

val glLoadMatrixFlat_unsafe : float array -> unit
Deprecated.in core OpenGL 3.

same than glLoadMatrixFlat but doesn't make any checks

Miscellaneous

val glFlush : unit -> unit

manual page

type orientation = 
| GL_CW
| GL_CCW
val glFrontFace : orientation:orientation -> unit

manual page

val glScissor : x:int -> y:int -> width:int -> height:int -> unit

manual page

val glFinish : unit -> unit

manual page

val glClearColor : r:float -> g:float -> b:float -> a:float -> unit

manual page

val glClearIndex : float -> unit

manual page

val glColorMask : r:bool -> g:bool -> b:bool -> a:bool -> unit

manual page

module Attrib: sig .. end
val glPushAttrib : attrib:Attrib.attrib_bit list -> unit
Deprecated.in core OpenGL 3.

manual page

val glPopAttrib : unit -> unit
Deprecated.in core OpenGL 3.
type face_mode = 
| GL_FRONT
| GL_BACK
| GL_FRONT_AND_BACK
type polygon_mode = 
| GL_POINT
| GL_LINE
| GL_FILL
val glPolygonMode : face:face_mode -> mode:polygon_mode -> unit

manual page

val glGetPolygonMode : unit -> polygon_mode * polygon_mode

glGet with argument GL_POLYGON_MODE manual page

type clear_mask = 
| GL_COLOR_BUFFER_BIT
| GL_DEPTH_BUFFER_BIT
| GL_ACCUM_BUFFER_BIT (*

deprecated in core OpenGL 3.

*)
| GL_STENCIL_BUFFER_BIT
val glClear : mask:clear_mask list -> unit

manual page

val glLineWidth : width:float -> unit

manual page. In OpenGL 3, this function does not support values greater than 1.0 anymore.

val glPointSize : size:float -> unit

manual page

type sprite_coord_origin = 
| GL_LOWER_LEFT
| GL_UPPER_LEFT
type point_parameter = 
| GL_POINT_SIZE_MIN of float
| GL_POINT_SIZE_MAX of float
| GL_POINT_FADE_THRESHOLD_SIZE of float
| GL_POINT_DISTANCE_ATTENUATION of float * float * float
| GL_POINT_SPRITE_COORD_ORIGIN of sprite_coord_origin
val glPointParameter : point_parameter -> unit

manual page

type gl_func = 
| GL_NEVER
| GL_LESS
| GL_EQUAL
| GL_LEQUAL
| GL_GREATER
| GL_NOTEQUAL
| GL_GEQUAL
| GL_ALWAYS
val glAlphaFunc : func:gl_func -> ref:float -> unit
Deprecated.in core OpenGL 3.

manual page

type hint_target = 
| GL_FOG_HINT (*

deprecated in core OpenGL 3.

*)
| GL_LINE_SMOOTH_HINT
| GL_PERSPECTIVE_CORRECTION_HINT (*

deprecated in core OpenGL 3.

*)
| GL_POINT_SMOOTH_HINT (*

deprecated in core OpenGL 3.

*)
| GL_POLYGON_SMOOTH_HINT
| GL_TEXTURE_COMPRESSION_HINT
| GL_GENERATE_MIPMAP_HINT (*

deprecated in core OpenGL 3.

*)
| GL_FRAGMENT_SHADER_DERIVATIVE_HINT
type hint_mode = 
| GL_FASTEST
| GL_NICEST
| GL_DONT_CARE
val glHint : target:hint_target -> mode:hint_mode -> unit

manual page

val glCullFace : mode:face_mode -> unit

manual page

val glGetCullFaceMode : unit -> face_mode

associated get for GL.glCullFace

val glLineStipple : factor:int -> pattern:int -> unit
Deprecated.in core OpenGL 3.

manual page

type polygon_stipple_mask = (int, Stdlib.Bigarray.int8_unsigned_elt, Stdlib.Bigarray.c_layout)
Stdlib.Bigarray.Array1.t
val glPolygonStipple : mask:polygon_stipple_mask -> unit
Deprecated.in core OpenGL 3.

manual page

val glPolygonStipple_unsafe : mask:polygon_stipple_mask -> unit
Deprecated.in core OpenGL 3.

Same than glPolygonStipple but does not check the size of the big array.

module DrawBuffer: sig .. end
val glDrawBuffer : mode:DrawBuffer.draw_buffer_mode -> unit

manual page

module ReadBuffer: sig .. end
val glReadBuffer : mode:ReadBuffer.read_buffer_mode -> unit

manual page

module Sfactor: sig .. end
module Dfactor: sig .. end
val glBlendFunc : sfactor:Sfactor.blend_sfactor -> dfactor:Dfactor.blend_dfactor -> unit

manual page ; Transparency, Translucency, and Blending Chapter

type blend_mode = 
| GL_FUNC_ADD
| GL_FUNC_SUBTRACT
| GL_FUNC_REVERSE_SUBTRACT
| GL_MIN
| GL_MAX
val glBlendEquation : mode:blend_mode -> unit

manual page

module Op: sig .. end
val glLogicOp : opcode:Op.op_code -> unit

manual page

val glPolygonOffset : factor:float -> units:float -> unit

manual page

Lighting

type shade_mode = 
| GL_FLAT
| GL_SMOOTH
val glShadeModel : shade_mode -> unit
Deprecated.in core OpenGL 3.

manual page

module Light: sig .. end
type gl_light = 
| GL_LIGHT of int
val glLight : light:gl_light -> pname:Light.light_pname -> unit
Deprecated.in core OpenGL 3.

manual page

type color_control = 
| GL_SEPARATE_SPECULAR_COLOR
| GL_SINGLE_COLOR
type light_model = 
| GL_LIGHT_MODEL_AMBIENT of (float * float * float * float)
| GL_LIGHT_MODEL_COLOR_CONTROL of color_control
| GL_LIGHT_MODEL_LOCAL_VIEWER of bool
| GL_LIGHT_MODEL_TWO_SIDE of bool
val glLightModel : light_model:light_model -> unit
Deprecated.in core OpenGL 3.

manual page

See glGetLight for associated get.

module Material: sig .. end
val glMaterial : face:face_mode -> mode:Material.material_mode -> unit
Deprecated.in core OpenGL 3.

manual page

module GetMat: sig .. end
val glGetMaterial4f : GetMat.face_mode ->
mode:GetMat.get_material_4f -> float * float * float * float
val glGetMaterial1f : GetMat.face_mode -> mode:GetMat.get_material_1f -> float
val glGetMaterial3i : GetMat.face_mode -> mode:GetMat.get_material_3i -> int * int * int

manual page

type color_material_mode = 
| GL_EMISSION
| GL_AMBIENT
| GL_DIFFUSE
| GL_SPECULAR
| GL_AMBIENT_AND_DIFFUSE
val glColorMaterial : face:face_mode -> mode:color_material_mode -> unit
Deprecated.in core OpenGL 3.

manual page

val glSecondaryColor3 : red:float -> green:float -> blue:float -> unit
Deprecated.in core OpenGL 3.

manual page

Stenciling

val glStencilFunc : func:gl_func -> ref:int -> mask:int -> unit

manual page

val glStencilFuncn : func:gl_func -> ref:int -> mask:nativeint -> unit

OCaml standard ints have 1 bit missing from nativeint.

val glStencilMask : mask:int -> unit

manual page

type stencil_op = 
| GL_KEEP
| GL_ZERO
| GL_REPLACE
| GL_INCR
| GL_INCR_WRAP
| GL_DECR
| GL_DECR_WRAP
| GL_INVERT
val glStencilOp : sfail:stencil_op -> dpfail:stencil_op -> dppass:stencil_op -> unit

manual page

val glClearStencil : s:int -> unit

manual page

Depth Buffer

val glDepthRange : near:float -> far:float -> unit

manual page

val glClearDepth : depth:float -> unit

manual page

val glDepthFunc : func:gl_func -> unit

manual page

val glDepthMask : bool -> unit

manual page

Accumulation Buffer

type accum_op = 
| GL_ACCUM
| GL_LOAD
| GL_ADD
| GL_MULT
| GL_RETURN
val glAccum : op:accum_op -> value:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glClearAccum : r:float -> g:float -> b:float -> a:float -> unit
Deprecated.in core OpenGL 3.

manual page

GL Capabilities

type gl_capability = 
| GL_ALPHA_TEST (*

deprecated in core OpenGL 3.

*)
| GL_AUTO_NORMAL
| GL_BLEND
| GL_CLIP_PLANE0
| GL_CLIP_PLANE1
| GL_CLIP_PLANE2
| GL_CLIP_PLANE3
| GL_CLIP_PLANE4
| GL_CLIP_PLANE5
| GL_COLOR_LOGIC_OP
| GL_COLOR_MATERIAL (*

deprecated in core OpenGL 3.

*)
| GL_COLOR_TABLE
| GL_CONVOLUTION_1D
| GL_CONVOLUTION_2D
| GL_CULL_FACE
| GL_DEPTH_TEST
| GL_DITHER
| GL_FOG
| GL_HISTOGRAM
| GL_INDEX_LOGIC_OP
| GL_LIGHT0 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT1 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT2 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT3 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT4 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT5 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT6 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHT7 (*

deprecated in core OpenGL 3.

*)
| GL_LIGHTING (*

deprecated in core OpenGL 3.

*)
| GL_LINE_SMOOTH
| GL_LINE_STIPPLE
| GL_MAP1_COLOR_4
| GL_MAP1_INDEX
| GL_MAP1_NORMAL
| GL_MAP1_TEXTURE_COORD_1
| GL_MAP1_TEXTURE_COORD_2
| GL_MAP1_TEXTURE_COORD_3
| GL_MAP1_TEXTURE_COORD_4
| GL_MAP1_VERTEX_3
| GL_MAP1_VERTEX_4
| GL_MAP2_COLOR_4
| GL_MAP2_INDEX
| GL_MAP2_NORMAL
| GL_MAP2_TEXTURE_COORD_1
| GL_MAP2_TEXTURE_COORD_2
| GL_MAP2_TEXTURE_COORD_3
| GL_MAP2_TEXTURE_COORD_4
| GL_MAP2_VERTEX_3
| GL_MAP2_VERTEX_4
| GL_MINMAX
| GL_MULTISAMPLE
| GL_NORMALIZE
| GL_POINT_SMOOTH (*

deprecated in core OpenGL 3.

*)
| GL_POINT_SPRITE (*

deprecated in core OpenGL 3.

*)
| GL_POLYGON_OFFSET_FILL
| GL_POLYGON_OFFSET_LINE
| GL_POLYGON_OFFSET_POINT
| GL_POLYGON_SMOOTH
| GL_POLYGON_STIPPLE
| GL_POST_COLOR_MATRIX_COLOR_TABLE
| GL_POST_CONVOLUTION_COLOR_TABLE
| GL_RESCALE_NORMAL (*

deprecated in core OpenGL 3.

*)
| GL_SAMPLE_ALPHA_TO_COVERAGE
| GL_SAMPLE_ALPHA_TO_ONE
| GL_SAMPLE_COVERAGE
| GL_SEPARABLE_2D
| GL_SCISSOR_TEST
| GL_STENCIL_TEST
| GL_TEXTURE_1D
| GL_TEXTURE_2D
| GL_TEXTURE_3D
| GL_TEXTURE_CUBE_MAP
| GL_TEXTURE_GEN_Q (*

deprecated in core OpenGL 3.

*)
| GL_TEXTURE_GEN_R (*

deprecated in core OpenGL 3.

*)
| GL_TEXTURE_GEN_S (*

deprecated in core OpenGL 3.

*)
| GL_TEXTURE_GEN_T (*

deprecated in core OpenGL 3.

*)
| GL_VERTEX_PROGRAM_POINT_SIZE
| GL_VERTEX_PROGRAM_TWO_SIDE (*

deprecated in core OpenGL 3.

*)
val glEnable : cap:gl_capability -> unit

manual page

val glDisable : cap:gl_capability -> unit
module Enabled: sig .. end
val glIsEnabled : Enabled.enabled_cap -> bool

manual page

Texture mapping

type texture_id = private int 
val glGenTextures : n:int -> texture_id array

manual page

val glGenTexture : unit -> texture_id
module BindTex: sig .. end
val glBindTexture : target:BindTex.texture_binding -> texture:texture_id -> unit

manual page

val glUnbindTexture : target:BindTex.texture_binding -> unit
val glBindTexture2D : texture:texture_id -> unit

equivalent to glBindTexture with parameter GL_TEXTURE_2D

val glUnbindTexture2D : unit -> unit
val glDeleteTextures : textures:texture_id array -> unit

manual page

val glDeleteTexture : texture:texture_id -> unit
val glIsTexture : texture:texture_id -> bool

manual page

val glPrioritizeTextures : textures:texture_id array -> priority:float array -> unit
val glPrioritizeTexture : texture:texture_id -> priority:float -> unit

manual page

val glPrioritizeTexturesp : prioritized_textures:(texture_id * float) array -> unit
module TexEnv: sig .. end
val glTexEnv : TexEnv.texenv_target ->
TexEnv.texenv_pname -> TexEnv.texenv_param -> unit

manual page

type tex_coord = 
| GL_S
| GL_T
| GL_R
| GL_Q
type tex_coord_gen_func = 
| GL_TEXTURE_GEN_MODE
type tex_gen_param = 
| GL_OBJECT_LINEAR
| GL_EYE_LINEAR
| GL_SPHERE_MAP
| GL_NORMAL_MAP
| GL_REFLECTION_MAP
val glTexGen : tex_coord -> tex_coord_gen_func -> tex_gen_param -> unit
Deprecated.in core OpenGL 3.

manual page

type tex_coord_fun_params = 
| GL_OBJECT_PLANE
| GL_EYE_PLANE
val glTexGenv : tex_coord ->
tex_coord_fun_params -> float * float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

val glTexGenva : tex_coord -> tex_coord_fun_params -> float array -> unit
Deprecated.in core OpenGL 3.

manual page

module TexTarget: sig .. end
module InternalFormat: sig .. end
type pixel_data_format = 
| GL_COLOR_INDEX
| GL_RED
| GL_GREEN
| GL_BLUE
| GL_ALPHA
| GL_RGB
| GL_RGBA
| GL_LUMINANCE
| GL_LUMINANCE_ALPHA
type pixel_data_type = 
| GL_UNSIGNED_BYTE
| GL_BYTE
| GL_BITMAP
| GL_UNSIGNED_SHORT
| GL_SHORT
| GL_UNSIGNED_INT
| GL_INT
| GL_FLOAT
| GL_UNSIGNED_BYTE_3_3_2
| GL_UNSIGNED_BYTE_2_3_3_REV
| GL_UNSIGNED_SHORT_5_6_5
| GL_UNSIGNED_SHORT_5_6_5_REV
| GL_UNSIGNED_SHORT_4_4_4_4
| GL_UNSIGNED_SHORT_4_4_4_4_REV
| GL_UNSIGNED_SHORT_5_5_5_1
| GL_UNSIGNED_SHORT_1_5_5_5_REV
| GL_UNSIGNED_INT_8_8_8_8
| GL_UNSIGNED_INT_8_8_8_8_REV
| GL_UNSIGNED_INT_10_10_10_2
| GL_UNSIGNED_INT_2_10_10_10_REV
type img_input = 
| Filename of string (*

provide the filename of a texture

*)
| Buffer of string (*

provide the image data as a buffer

*)

input type to provide the textures

type image_data = (int, Stdlib.Bigarray.int8_unsigned_elt, Stdlib.Bigarray.c_layout)
Stdlib.Bigarray.Genarray.t
val assert_size : width:int -> height:int -> unit

utility function to check if the dimensions of the image are compatible with OpenGL textures.

val glTexImage2D : target:TexTarget.target_2d ->
level:int ->
internal_format:InternalFormat.internal_format ->
width:int ->
height:int ->
format_:pixel_data_format ->
type_:pixel_data_type -> pixels:image_data -> unit

manual page

val glTexImage2D_str : target:TexTarget.target_2d ->
level:int ->
internal_format:InternalFormat.internal_format ->
width:int ->
height:int ->
format_:pixel_data_format ->
type_:pixel_data_type -> pixels:string -> unit
val glTexImage1D : target:TexTarget.target_1d ->
level:int ->
internal_format:InternalFormat.internal_format ->
width:int ->
format_:pixel_data_format ->
type_:pixel_data_type -> pixels:image_data -> unit

manual page

val glTexImage3D : target:TexTarget.target_3d ->
level:int ->
internal_format:InternalFormat.internal_format ->
width:int ->
height:int ->
depth:int ->
format_:pixel_data_format ->
type_:pixel_data_type -> pixels:image_data -> unit

manual page

val glTexCoord1 : s:float -> unit
val glTexCoord2 : s:float -> t:float -> unit
val glTexCoord3 : s:float -> t:float -> r:float -> unit
val glTexCoord4 : s:float -> t:float -> r:float -> q:float -> unit
Deprecated.in core OpenGL 3.

manual page

val glTexCoord2v : v:float * float -> unit
val glTexCoord3v : v:float * float * float -> unit
val glTexCoord4v : v:float * float * float * float -> unit
Deprecated.in core OpenGL 3.

manual page

module Min: sig .. end
module Mag: sig .. end
type wrap_param = 
| GL_CLAMP (*

deprecated in core OpenGL 3.

*)
| GL_CLAMP_TO_BORDER
| GL_CLAMP_TO_EDGE
| GL_MIRRORED_REPEAT
| GL_REPEAT
module TexParam: sig .. end
val glTexParameter : target:TexParam.tex_param_target -> param:TexParam.tex_param -> unit

manual page

module CopyTex: sig .. end
val glCopyTexImage2D : target:CopyTex.copy_tex_target ->
level:int ->
internal_format:InternalFormat.internal_format ->
x:int -> y:int -> width:int -> height:int -> border:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glSampleCoverage : value:float -> invert:bool -> unit

manual page

Raster functions

type pixel_packing_b = 
| GL_PACK_SWAP_BYTES
| GL_PACK_LSB_FIRST
| GL_UNPACK_SWAP_BYTES
| GL_UNPACK_LSB_FIRST
val glPixelStoreb : pixel_packing:pixel_packing_b -> param:bool -> unit
type pixel_packing_i = 
| GL_PACK_ROW_LENGTH
| GL_PACK_IMAGE_HEIGHT
| GL_PACK_SKIP_PIXELS
| GL_PACK_SKIP_ROWS
| GL_PACK_SKIP_IMAGES
| GL_PACK_ALIGNMENT
| GL_UNPACK_ROW_LENGTH
| GL_UNPACK_IMAGE_HEIGHT
| GL_UNPACK_SKIP_PIXELS
| GL_UNPACK_SKIP_ROWS
| GL_UNPACK_SKIP_IMAGES
| GL_UNPACK_ALIGNMENT
val glPixelStorei : pixel_packing:pixel_packing_i -> param:int -> unit

manual page

val glPixelZoom : xfactor:float -> yfactor:float -> unit

manual page

type pixel_map = 
| GL_PIXEL_MAP_I_TO_I
| GL_PIXEL_MAP_S_TO_S
| GL_PIXEL_MAP_I_TO_R
| GL_PIXEL_MAP_I_TO_G
| GL_PIXEL_MAP_I_TO_B
| GL_PIXEL_MAP_I_TO_A
| GL_PIXEL_MAP_R_TO_R
| GL_PIXEL_MAP_G_TO_G
| GL_PIXEL_MAP_B_TO_B
| GL_PIXEL_MAP_A_TO_A
val glPixelMapfv : map:pixel_map -> v:float array -> unit

manual page

val glBitmap : width:int ->
height:int ->
xorig:float ->
yorig:float ->
xmove:float ->
ymove:float -> bitmap:('a, 'b, 'c) Stdlib.Bigarray.Array1.t -> unit

manual page

type pixel_type = 
| GL_COLOR
| GL_DEPTH
| GL_STENCIL
val glCopyPixels : x:int -> y:int -> width:int -> height:int -> pixel_type:pixel_type -> unit
Deprecated.in core OpenGL 3.

manual page

type pixel_transfer_i = 
| GL_INDEX_SHIFT
| GL_INDEX_OFFSET
type pixel_transfer_f = 
| GL_RED_SCALE
| GL_RED_BIAS
| GL_GREEN_SCALE
| GL_GREEN_BIAS
| GL_BLUE_SCALE
| GL_BLUE_BIAS
| GL_ALPHA_SCALE
| GL_ALPHA_BIAS
| GL_DEPTH_SCALE
| GL_DEPTH_BIAS
type pixel_transfer_b = 
| GL_MAP_COLOR
| GL_MAP_STENCIL
type pixel_transfer_f_ARB = 
| GL_POST_COLOR_MATRIX_RED_SCALE
| GL_POST_COLOR_MATRIX_GREEN_SCALE
| GL_POST_COLOR_MATRIX_BLUE_SCALE
| GL_POST_COLOR_MATRIX_ALPHA_SCALE
| GL_POST_COLOR_MATRIX_RED_BIAS
| GL_POST_COLOR_MATRIX_GREEN_BIAS
| GL_POST_COLOR_MATRIX_BLUE_BIAS
| GL_POST_COLOR_MATRIX_ALPHA_BIAS
| GL_POST_CONVOLUTION_RED_SCALE
| GL_POST_CONVOLUTION_GREEN_SCALE
| GL_POST_CONVOLUTION_BLUE_SCALE
| GL_POST_CONVOLUTION_ALPHA_SCALE
| GL_POST_CONVOLUTION_RED_BIAS
| GL_POST_CONVOLUTION_GREEN_BIAS
| GL_POST_CONVOLUTION_BLUE_BIAS
| GL_POST_CONVOLUTION_ALPHA_BIAS

if the ARB_imaging extension is supported, these symbolic names are accepted

val glPixelTransferi : pname:pixel_transfer_i -> param:int -> unit
val glPixelTransferf : pname:pixel_transfer_f -> param:float -> unit
val glPixelTransferb : pname:pixel_transfer_b -> param:bool -> unit
val glPixelTransferfARB : pname:pixel_transfer_f_ARB -> param:float -> unit

manual page

module Framebuffer: sig .. end
val glReadPixelsBA_unsafe : x:int ->
y:int ->
width:int ->
height:int ->
Framebuffer.pixel_buffer_format ->
Framebuffer.pixel_buffer_type -> image_data -> unit

manual page

val glReadPixelsBA : x:int ->
y:int ->
width:int ->
height:int ->
Framebuffer.pixel_buffer_format ->
Framebuffer.pixel_buffer_type -> image_data -> unit

same than glReadPixelsBA_unsafe but checks the size of the big-array

val glDrawPixels_str : width:int ->
height:int ->
format_:pixel_data_format ->
type_:pixel_data_type -> pixels:string -> unit
Deprecated.in core OpenGL 3.

manual page

Clipping

module Plane: sig .. end
val glClipPlane : plane:Plane.clip_plane -> equation:float array -> unit

manual page

val glClipPlane_unsafe : plane:Plane.clip_plane -> equation:float array -> unit

same than glClipPlane but doesn't check that equation contains 4 items.

type clip_plane_i = 
| GL_CLIP_PLANE of int
val glClipPlanei : plane:clip_plane_i -> equation:float array -> unit
val glClipPlanei_unsafe : plane:clip_plane_i -> equation:float array -> unit

Evaluators

module Map1: sig .. end
val glMap1 : target:Map1.map1_target ->
u1:float -> u2:float -> stride:int -> order:int -> points:float array -> unit
Deprecated.in core OpenGL 3.

manual page

module Map2: sig .. end
val glMap2 : target:Map2.map2_target ->
u1:float ->
u2:float ->
ustride:int ->
uorder:int ->
v1:float ->
v2:float ->
vstride:int -> vorder:int -> points:float array array array -> unit
Deprecated.in core OpenGL 3.

manual page

val glEvalCoord1 : u:float -> unit
val glEvalCoord2 : u:float -> v:float -> unit
Deprecated.in core OpenGL 3.

manual page

module EvalMesh1: sig .. end
module EvalMesh2: sig .. end
val glEvalMesh1 : mode:EvalMesh1.eval_mesh_1 -> i1:int -> i2:int -> unit
val glEvalMesh2 : mode:EvalMesh2.eval_mesh_2 -> i1:int -> i2:int -> j1:int -> j2:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glEvalPoint1 : i:int -> unit
val glEvalPoint2 : i:int -> j:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glMapGrid1 : un:int -> u1:float -> u2:float -> unit
val glMapGrid2 : un:int -> u1:float -> u2:float -> vn:int -> v1:float -> v2:float -> unit
Deprecated.in core OpenGL 3.

manual page

Display Lists

type list_mode = 
| GL_COMPILE
| GL_COMPILE_AND_EXECUTE
val glNewList : gl_list:int -> mode:list_mode -> unit
Deprecated.in core OpenGL 3.

manual page

val glEndList : unit -> unit
Deprecated.in core OpenGL 3.
val glGenList : unit -> int
val glGenLists : range:int -> int
Deprecated.in core OpenGL 3.

manual page

val glCallList : gl_list:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glCallLists : gl_lists:int array -> unit
Deprecated.in core OpenGL 3.

manual page

val glDeleteLists : gl_list:int -> range:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glListBase : base:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glIsList : gl_list:int -> bool
Deprecated.in core OpenGL 3.

manual page

val glGetListMode : unit -> list_mode
Deprecated.in core OpenGL 3.

Picking

type render_mode = 
| GL_RENDER
| GL_SELECT
| GL_FEEDBACK
val glRenderMode : mode:render_mode -> int
Deprecated.in core OpenGL 3.

manual page

val glInitNames : unit -> unit
Deprecated.in core OpenGL 3.

manual page

val glLoadName : name:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glPushName : name:int -> unit
Deprecated.in core OpenGL 3.

manual page

val glPopName : unit -> unit
Deprecated.in core OpenGL 3.

manual page

type select_buffer 
val new_select_buffer : buffer_size:int -> select_buffer
val free_select_buffer : select_buffer:select_buffer -> unit
val select_buffer_get : select_buffer:select_buffer -> index:int -> int
val glSelectBuffer : buffer_size:int -> select_buffer:select_buffer -> unit
Deprecated.in core OpenGL 3.

manual page

val glSelectBufferBA : (nativeint, Stdlib.Bigarray.nativeint_elt, Stdlib.Bigarray.c_layout)
Stdlib.Bigarray.Array1.t -> unit

Fog

type fog_mode = 
| GL_LINEAR
| GL_EXP
| GL_EXP2
type fog_coord_src = 
| GL_FOG_COORD
| GL_FRAGMENT_DEPTH
type fog_param = 
| GL_FOG_MODE of fog_mode
| GL_FOG_DENSITY of float
| GL_FOG_START of float
| GL_FOG_END of float
| GL_FOG_INDEX of float
| GL_FOG_COLOR of (float * float * float * float)
| GL_FOG_COORD_SRC of fog_coord_src
val glFog : pname:fog_param -> unit

manual page

GLSL Shaders

type shader_object 
type shader_program 
type shader_type = 
| GL_VERTEX_SHADER
| GL_FRAGMENT_SHADER
| GL_GEOMETRY_SHADER
val glCreateShader : shader_type:shader_type -> shader_object

manual page

val glDeleteShader : shader:shader_object -> unit

manual page

val glIsShader : shader:shader_object -> bool

manual page

val glShaderSource : shader:shader_object -> string -> unit

manual page

val glCompileShader : shader:shader_object -> unit

manual page

val glCreateProgram : unit -> shader_program

manual page

val glDeleteProgram : program:shader_program -> unit

manual page

val glAttachShader : program:shader_program -> shader:shader_object -> unit

manual page

val glDetachShader : program:shader_program -> shader:shader_object -> unit

manual page

val glLinkProgram : program:shader_program -> unit

manual page

val glUseProgram : program:shader_program -> unit

manual page

val glUnuseProgram : unit -> unit

equivalent to the C call glUseProgram(0) that desactivates the program

val glGetShaderCompileStatus : shader:shader_object -> bool

manual page

val glGetShaderCompileStatus_exn : shader:shader_object -> unit

same than glGetShaderCompileStatus but raises an exception instead of returning false

val glGetUniformLocation : program:shader_program -> name:string -> int

manual page

type get_program_bool = 
| GL_DELETE_STATUS
| GL_LINK_STATUS
| GL_VALIDATE_STATUS
type get_program_int = 
| GL_INFO_LOG_LENGTH
| GL_ATTACHED_SHADERS
| GL_ACTIVE_ATTRIBUTES
| GL_ACTIVE_ATTRIBUTE_MAX_LENGTH
| GL_ACTIVE_UNIFORMS
| GL_ACTIVE_UNIFORM_MAX_LENGTH
val glGetProgrami : program:shader_program -> pname:get_program_int -> int
val glGetProgramb : program:shader_program -> pname:get_program_bool -> bool

manual page

val glUniform1f : location:int -> v0:float -> unit
val glUniform2f : location:int -> v0:float -> v1:float -> unit
val glUniform3f : location:int -> v0:float -> v1:float -> v2:float -> unit
val glUniform4f : location:int -> v0:float -> v1:float -> v2:float -> v3:float -> unit
val glUniform1i : location:int -> v0:int -> unit
val glUniform2i : location:int -> v0:int -> v1:int -> unit
val glUniform3i : location:int -> v0:int -> v1:int -> v2:int -> unit
val glUniform4i : location:int -> v0:int -> v1:int -> v2:int -> v3:int -> unit

manual page

val glUniform1fv : location:int -> value:float array -> unit
val glUniform2fv : location:int -> count:int -> value:float array -> unit
val glUniform3fv : location:int -> count:int -> value:float array -> unit
val glUniform4fv : location:int -> count:int -> value:float array -> unit
val glUniform1iv : location:int -> value:int array -> unit
val glUniform2iv : location:int -> count:int -> value:int array -> unit
val glUniform3iv : location:int -> count:int -> value:int array -> unit
val glUniform4iv : location:int -> count:int -> value:int array -> unit

manual page

val glUniformMatrix2f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix3f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix4f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix2x3f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix3x2f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix2x4f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix4x2f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix3x4f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix4x3f : location:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix2fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix3fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix4fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix2x3fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix3x2fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix2x4fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix4x2fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix3x4fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glUniformMatrix4x3fv : location:int -> count:int -> transpose:bool -> value:float array -> unit
val glGetAttribLocation : program:shader_program -> name:string -> int

manual page

val glBindAttribLocation : program:shader_program -> index:int -> name:string -> unit

manual page

val glVertexAttrib1s : index:int -> v:int -> unit
val glVertexAttrib1d : index:int -> v:float -> unit
val glVertexAttrib2s : index:int -> v0:int -> v1:int -> unit
val glVertexAttrib2d : index:int -> v0:float -> v1:float -> unit
val glVertexAttrib3s : index:int -> v0:int -> v1:int -> v2:int -> unit
val glVertexAttrib3d : index:int -> v0:float -> v1:float -> v2:float -> unit
val glVertexAttrib4s : index:int -> v0:int -> v1:int -> v2:int -> v3:int -> unit
val glVertexAttrib4d : index:int -> v0:float -> v1:float -> v2:float -> v3:float -> unit

manual page

val glGetShaderInfoLog : shader:shader_object -> string

manual page

val glGetProgramInfoLog : program:shader_program -> string

manual page

val glEnableVertexAttribArray : index:int -> unit

manual page

val glDisableVertexAttribArray : index:int -> unit

manual page

Gets

module Get: sig .. end

manual page

val glGetBoolean1 : Get.get_boolean_1 -> bool
val glGetBoolean4 : Get.get_boolean_4 -> bool * bool * bool * bool
val glGetInteger4 : Get.get_integer_4 -> int * int * int * int
val glGetInteger1 : Get.get_integer_1 -> int
val glGetInteger2 : Get.get_integer_2 -> int * int
val glGetFloat4 : Get.get_float_4 -> float * float * float * float
val glGetFloat3 : Get.get_float_3 -> float * float * float
val glGetFloat2 : Get.get_float_2 -> float * float
val glGetFloat1 : Get.get_float_1 -> float
val glGetMatrix : Get.get_matrix -> float array array
val glGetMatrixFlat : Get.get_matrix -> float array
val glGetTextureBinding : Get.get_texture_binding -> texture_id
type get_string = 
| GL_VENDOR
| GL_RENDERER
| GL_VERSION
| GL_SHADING_LANGUAGE_VERSION
| GL_EXTENSIONS
val glGetString : name:get_string -> string

manual page

type gl_error = 
| GL_NO_ERROR
| GL_INVALID_ENUM
| GL_INVALID_VALUE
| GL_INVALID_OPERATION
| GL_STACK_OVERFLOW
| GL_STACK_UNDERFLOW
| GL_OUT_OF_MEMORY
| GL_TABLE_TOO_LARGE
val glGetError : unit -> gl_error

manual page

type tuple_params = 
| P1 of float
| P3 of float * float * float
| P4 of float * float * float * float
| PCC of color_control
val glGetLight : light:gl_light -> pname:Get.get_light -> tuple_params

manual page

Multitexture

Multitexture Node, ARB multitexture wiki

type texture_i = 
| GL_TEXTURE0
| GL_TEXTURE1
| GL_TEXTURE2
| GL_TEXTURE3
| GL_TEXTURE4
| GL_TEXTURE5
| GL_TEXTURE6
| GL_TEXTURE7
| GL_TEXTURE8
| GL_TEXTURE9
| GL_TEXTURE10
| GL_TEXTURE11
| GL_TEXTURE12
| GL_TEXTURE13
| GL_TEXTURE14
| GL_TEXTURE15
| GL_TEXTURE16
| GL_TEXTURE17
| GL_TEXTURE18
| GL_TEXTURE19
| GL_TEXTURE20
| GL_TEXTURE21
| GL_TEXTURE22
| GL_TEXTURE23
| GL_TEXTURE24
| GL_TEXTURE25
| GL_TEXTURE26
| GL_TEXTURE27
| GL_TEXTURE28
| GL_TEXTURE29
| GL_TEXTURE30
| GL_TEXTURE31
val glActiveTexture : texture:texture_i -> unit

manual page

val glActiveTexturei : texture:int -> unit

glActiveTexturei i is equivalent to glActiveTexture GL_TEXTUREi

val glMultiTexCoord2 : texture:texture_i -> s:float -> t:float -> unit

manual page

val glMultiTexCoord2i : texture:int -> s:float -> t:float -> unit

Library Version

val glmlite_version : int * int * int