Module Glu

module Glu: sig .. end

Glu interface


val gluPerspective : fovy:float -> aspect:float -> zNear:float -> zFar:float -> unit

manual page

val gluLookAt : eyeX:float ->
eyeY:float ->
eyeZ:float ->
centerX:float ->
centerY:float -> centerZ:float -> upX:float -> upY:float -> upZ:float -> unit

manual page

val gluOrtho2D : left:float -> right:float -> bottom:float -> top:float -> unit

manual page

val gluErrorString : error:GL.gl_error -> string

manual page

val gluPickMatrix : x:float ->
y:float ->
width:float -> height:float -> viewport:int * int * int * int -> unit

manual page

val gluUnProject : win_x:float ->
win_y:float ->
win_z:float ->
model:float array array ->
proj:float array array -> viewport:int array -> float * float * float

manual page

val gluUnProjectFlat : win_x:float ->
win_y:float ->
win_z:float ->
model:float array ->
proj:float array -> viewport:int array -> float * float * float

same than gluUnProject but optimised

val gluUnProjectUtil : x:int -> y:int -> float * float * float

Utility provides a classic use of gluUnProject with default parameters, the modelview matrix, the projection matrix, and the current viewport.

val gluUnProjectPixel : x:int -> y:int -> float * float * float

Utility Same as gluUnProjectUtil but also checks the depth of the pixel.

val gluProject : win_x:float ->
win_y:float ->
win_z:float ->
model:float array array ->
proj:float array array -> viewport:int array -> float * float * float

manual page

val gluProjectFlat : win_x:float ->
win_y:float ->
win_z:float ->
model:float array ->
proj:float array -> viewport:int array -> float * float * float

same than gluProject but optimised

val gluProjectUtil : obj_x:float -> obj_y:float -> obj_z:float -> float * float * float

Utility provides a classic use of gluProject with default parameters, the modelview matrix, the projection matrix, and the current viewport.

type glu_desc = 
| GLU_VERSION
| GLU_EXTENSIONS
val gluGetString : name:glu_desc -> string

manual page

Mipmaps

val gluBuild2DMipmaps : internal_format:GL.InternalFormat.internal_format ->
width:int ->
height:int ->
format_:GL.pixel_data_format ->
type_:GL.pixel_data_type -> pixels:GL.image_data -> unit

manual page

val gluBuild1DMipmaps : internal_format:GL.InternalFormat.internal_format ->
width:int ->
format_:GL.pixel_data_format ->
type_:GL.pixel_data_type -> pixels:GL.image_data -> unit

manual page

val gluBuild3DMipmaps : internal_format:GL.InternalFormat.internal_format ->
width:int ->
height:int ->
depth:int ->
format_:GL.pixel_data_format ->
type_:GL.pixel_data_type -> pixels:GL.image_data -> unit

manual page

Quadric Functions

type glu_quadric 
val gluNewQuadric : unit -> glu_quadric

manual page

val gluDeleteQuadric : quad:glu_quadric -> unit

manual page

type draw_style = 
| GLU_POINT
| GLU_LINE
| GLU_FILL
| GLU_SILHOUETTE
val gluQuadricDrawStyle : quad:glu_quadric -> draw_style:draw_style -> unit

manual page

val gluQuadricTexture : quad:glu_quadric -> texture:bool -> unit

manual page

val gluSphere : quad:glu_quadric -> radius:float -> slices:int -> stacks:int -> unit

manual page

val gluCylinder : quad:glu_quadric ->
base:float -> top:float -> height:float -> slices:int -> stacks:int -> unit

manual page

val gluDisk : quad:glu_quadric ->
inner:float -> outer:float -> slices:int -> loops:int -> unit

manual page

val gluPartialDisk : quad:glu_quadric ->
inner:float ->
outer:float -> slices:int -> loops:int -> start:float -> sweep:float -> unit

manual page

type orientation = 
| GLU_OUTSIDE
| GLU_INSIDE
val gluQuadricOrientation : quad:glu_quadric -> orientation:orientation -> unit

manual page

type normal = 
| GLU_NONE
| GLU_FLAT
| GLU_SMOOTH
val gluQuadricNormals : quad:glu_quadric -> normal:normal -> unit

manual page

Tesselation

type glu_tesselator 
val gluNewTess : unit -> glu_tesselator

manual page

val gluDeleteTess : tess:glu_tesselator -> unit

manual page

val gluBeginPolygon : tess:glu_tesselator -> unit

manual page

val gluEndPolygon : tess:glu_tesselator -> unit

manual page

val gluTessBeginPolygon : tess:glu_tesselator -> unit
val gluTessBeginPolygonData : tess:glu_tesselator -> data:'a -> unit

manual page

val gluTessEndPolygon : tess:glu_tesselator -> unit

manual page

val gluTessBeginContour : tess:glu_tesselator -> unit

manual page

val gluTessEndContour : tess:glu_tesselator -> unit

manual page

type tess_contour = 
| GLU_CW
| GLU_CCW
| GLU_INTERIOR
| GLU_EXTERIOR
| GLU_UNKNOWN
val gluNextContour : tess:glu_tesselator -> contour:tess_contour -> unit

manual page

val gluTessVertex : tess:glu_tesselator -> x:float -> y:float -> z:float -> unit

manual page

val gluTessNormal : tess:glu_tesselator -> x:float -> y:float -> z:float -> unit

manual page

val gluTesselate : glu_tesselator -> (float * float * float) array -> unit

Is equivalent to:

    gluTessBeginPolygon ~tess;
      gluTessBeginContour ~tess;
        Array.iter (fun (x,y,z) -> gluTessVertex ~tess ~x ~y ~z) points;
      gluTessEndContour ~tess;
    gluTessEndPolygon ~tess;
val gluTesselateIter : tess:glu_tesselator -> data:(float * float * float) array list -> unit

Is equivalent to:

    gluTessBeginPolygon ~tess;
      List.iter (fun points ->
          gluTessBeginContour ~tess;
            Array.iter (fun (x,y,z) -> gluTessVertex ~tess ~x ~y ~z) points;
          gluTessEndContour ~tess;
        ) datas;
    gluTessEndPolygon ~tess;
type tess_winding = 
| GLU_TESS_WINDING_ODD
| GLU_TESS_WINDING_NONZERO
| GLU_TESS_WINDING_POSITIVE
| GLU_TESS_WINDING_NEGATIVE
| GLU_TESS_WINDING_ABS_GEQ_TWO
type tess_property = 
| GLU_TESS_WINDING_RULE of tess_winding
| GLU_TESS_BOUNDARY_ONLY of bool
| GLU_TESS_TOLERANCE of float
val gluGetTessWindingRule : tess:glu_tesselator -> winding:tess_winding -> unit
val gluGetTessBoundaryOnly : tess:glu_tesselator -> boundary_only:bool -> unit
val gluGetTessTolerance : tess:glu_tesselator -> tolerance:float -> unit
val gluTessProperty : tess:glu_tesselator -> prop:tess_property -> unit

manual page

type tess_callback = 
| GLU_TESS_BEGIN
| GLU_TESS_BEGIN_DATA
| GLU_TESS_EDGE_FLAG
| GLU_TESS_EDGE_FLAG_DATA
| GLU_TESS_VERTEX
| GLU_TESS_VERTEX_DATA
| GLU_TESS_END
| GLU_TESS_END_DATA
| GLU_TESS_COMBINE
| GLU_TESS_COMBINE_DATA
| GLU_TESS_ERROR
| GLU_TESS_ERROR_DATA

manual page

val gluTessDefaultCallback : tess:glu_tesselator -> cb:tess_callback -> unit

Sets default callbacks for a classic use. GLU_TESS_BEGIN and GLU_TESS_END callbacks are set to glBegin and glEnd. GLU_TESS_VERTEX callback calls glVertex3 preceded by a call to glTexCoord2 with the x and y components (the size of the texture mapping can by scaled with glMatrixMode
    GL_TEXTURE;
and glScale). GLU_TESS_COMBINE callback makes the alloc of the new vertex, and a caml Failure with the Glu error message is raised for the GLU_TESS_ERROR callback.

type tess_error = 
| GLU_TESS_MISSING_BEGIN_POLYGON
| GLU_TESS_MISSING_BEGIN_CONTOUR
| GLU_TESS_MISSING_END_POLYGON
| GLU_TESS_MISSING_END_CONTOUR
| GLU_TESS_COORD_TOO_LARGE
| GLU_TESS_NEED_COMBINE_CALLBACK
| GLU_OUT_OF_MEMORY
| GLU_TESS_ERROR7
| GLU_TESS_ERROR8
val gluCallbackTessVertex : tess:glu_tesselator ->
tess_vertex:(x:float -> y:float -> z:float -> unit) -> unit
val gluCallbackTessBegin : tess:glu_tesselator -> tess_begin:(prim:GL.primitive -> unit) -> unit
val gluCallbackTessEnd : tess:glu_tesselator -> tess_end:(unit -> unit) -> unit
val gluCallbackTessError : tess:glu_tesselator -> tess_error:(error:tess_error -> unit) -> unit
val gluTessErrorString : error:tess_error -> string

same than gluErrorString but for type tess_error

Nurbs Surfaces

type glu_nurbs 
val gluNewNurbsRenderer : unit -> glu_nurbs

manual page

val gluBeginSurface : nurb:glu_nurbs -> unit

manual page

val gluEndSurface : nurb:glu_nurbs -> unit

manual page

type nurbs_mode = 
| GLU_NURBS_RENDERER
| GLU_NURBS_TESSELLATOR
type sampling_method = 
| GLU_PATH_LENGTH
| GLU_PARAMETRIC_ERROR
| GLU_DOMAIN_DISTANCE
| GLU_OBJECT_PATH_LENGTH
| GLU_OBJECT_PARAMETRIC_ERROR
module Disp: sig .. end
type nurbs_property = 
| GLU_SAMPLING_TOLERANCE of float
| GLU_DISPLAY_MODE of Disp.display_mode
| GLU_CULLING of bool
| GLU_AUTO_LOAD_MATRIX of bool
| GLU_PARAMETRIC_TOLERANCE of float
| GLU_SAMPLING_METHOD of sampling_method
| GLU_U_STEP of int
| GLU_V_STEP of int
| GLU_NURBS_MODE of nurbs_mode
val gluNurbsProperty : nurb:glu_nurbs -> property:nurbs_property -> unit

manual page

type surface_type = 
| GLU_MAP2_VERTEX_3
| GLU_MAP2_VERTEX_4
val gluNurbsSurface : nurb:glu_nurbs ->
sKnots:float array ->
tKnots:float array ->
sStride:int ->
tStride:int ->
control:float array ->
sOrder:int -> tOrder:int -> surface_type:surface_type -> unit

manual page