Module GLE


module GLE: sig .. end
Bindings to the GLE library. A set of functions to make extrusions.


GLE is a library that draws extruded surfaces, including surfaces of revolution, sweeps, tubes, polycones, polycylinders and helicoids. Generically, the extruded surface is specified with a 2D polyline that is extruded along a 3D path. A local coordinate system allows for additional flexibility in the primitives drawn. Extrusions may be texture mapped in a variety of ways. The GLE library generates 3D triangle coordinates, lighting normal vectors and texture coordinates as output.

type join_style =
| TUBE_JN_RAW
| TUBE_JN_ANGLE
| TUBE_JN_CUT
| TUBE_JN_ROUND
| TUBE_JN_CAP
| TUBE_NORM_FACET
| TUBE_NORM_EDGE
| TUBE_NORM_PATH_EDGE
| TUBE_CONTOUR_CLOSED
val gleSetJoinStyle : join_style list -> unit
val gleGetJoinStyle : unit -> join_style list
control join style of the tubes
val gleDestroyGC : unit -> unit
clean up global memory usage
type gle_float 
val ba2_float32_of_array : float array array ->
(float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t
identical to Bigarray.Array2.of_array Bigarray.float32 Bigarray.c_layout array
val ba2_float32_create : int ->
int -> (float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t
identical to Bigarray.Array2.create Bigarray.float32 Bigarray.c_layout dim1 dim2
val ba2_glefloat_of_array : float array array ->
(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t
identical to ba2_float32_of_array but with gle_float
val ba2_glefloat_create : int -> int -> (float, gle_float, Bigarray.c_layout) Bigarray.Array2.t
identical to ba2_float32_create but with gle_float
val ba1_glefloat_of_array : float array -> (float, gle_float, Bigarray.c_layout) Bigarray.Array1.t
val ba1_glefloat_create : int -> (float, gle_float, Bigarray.c_layout) Bigarray.Array1.t
val colors_none : (float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t
val glePolyCylinder : points:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
colors:(float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t ->
radius:float -> unit
draw polyclinder, specified as a polyline
points : polyline vertices
colors : colors at polyline verts
radius : radius of polycylinder
val glePolyCone : points:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
colors:(float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t ->
radii:(float, gle_float, Bigarray.c_layout) Bigarray.Array1.t -> unit
draw polycone, specified as a polyline with radii
points : polyline vertices
colors : colors at polyline verts
radii : cone radii at polyline verts
val glePolyCone_c4f : points:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
colors:(float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t ->
radii:(float, gle_float, Bigarray.c_layout) Bigarray.Array1.t -> unit
same than glePolyCone but with RGBA colors
val gleExtrusion : contour:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
cont_normals:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
up:(float * float * float) option ->
points:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
colors:(float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t ->
unit
extrude arbitrary 2D contour along arbitrary 3D path
contour : 2D contour
cont_normals : 2D contour normals
up : up vector for contour
points : polyline vertices
colors : colors at polyline verts
val gleTwistExtrusion : contour:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
cont_normals:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
up:(float * float * float) option ->
points:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
colors:(float, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Array2.t ->
twist:(float, gle_float, Bigarray.c_layout) Bigarray.Array1.t -> unit
extrude 2D contour, specifying local rotations (twists)
contour : 2D contour
up : up vector for contour
val gleSpiral : contour:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
cont_normals:(float, gle_float, Bigarray.c_layout) Bigarray.Array2.t ->
up:(float * float * float) option ->
start_radius:float ->
drd_theta:float ->
start_z:float ->
dzd_theta:float ->
start_xform:((float * float * float) * (float * float * float)) option ->
dx_formd_theta:((float * float * float) * (float * float * float)) option ->
start_theta:float -> sweep_theta:float -> unit
sweep an arbitrary contour along a helical path
contour : 2D contour
up : up vector for contour
start_radius : spiral starts in x-y plane
drd_theta : change in radius per revolution
start_z : starting z value
dzd_theta : change in z per revolution
start_xform : starting contour affine transform
dx_formd_theta : tangent change transform per revolution
start_theta : start angle in x-y plane
sweep_theta : degrees to spiral around
val gleHelicoid : torus_radius:float ->
start_radius:float ->
drd_theta:float ->
start_z:float ->
dzd_theta:float ->
start_xform:((float * float * float) * (float * float * float)) option ->
dx_formd_theta:((float * float * float) * (float * float * float)) option ->
start_theta:float -> sweep_theta:float -> unit
Generalized Torus. Similar to gleSpiral, except contour is a circle.
torus_radius : circle contour (torus) radius
start_radius : spiral starts in x-y plane
drd_theta : change in radius per revolution
start_z : starting z value
dzd_theta : change in z per revolution
start_xform : starting contour affine transform
dx_formd_theta : tangent change transform per revolution
start_theta : start angle in x-y plane
sweep_theta : degrees to spiral around