module Povray:sig
..end
There are 3 different ways to create a povray
scene:
with the description type scene_desc
,
accumulating to the scene
type,
or with a type that we can print to a screen.
typelocation =
float * float * float
module Camera:sig
..end
module Color:sig
..end
typecolor =
Color.t
type
texture
type
finish
typetriangle =
location * location * location
typetriangle_c =
triangle * Color.t
typeface_indice =
int * int * int
typeface_indices =
face_indice array
type
scene_desc =
| |
Include of |
|||
| |
Background of |
|||
| |
Light_source of |
|||
| |
Ambient_light of |
|||
| |
Camera of |
|||
| |
Sphere of |
(* |
| *) |
| |
Cone of |
(* |
| *) |
| |
Box of |
(* |
| *) |
| |
Cylinder of |
(* |
| *) |
| |
Torus of |
(* |
| *) |
| |
Mesh of |
(* |
| *) |
| |
MeshC of |
(* | ( | *) |
| |
MeshD of |
(* |
| *) |
| |
MeshD2 of |
(* |
| *) |
module Textures:sig
..end
type
scene
val new_scene : unit -> scene
val string_of_scene : scene -> string
val print_scene : scene -> unit
module Inc_file:sig
..end
typeinc_file =
Inc_file.t
val string_of_inc_file : inc:inc_file -> string
val inc_file_of_string : inc:string -> inc_file
string_of_inc_file
is equivalent to Inc_file.to_string
inc_file_of_string
is equivalent to Inc_file.of_string
val add_include : scene -> inc:inc_file -> scene
val add_comment : scene -> com:string -> scene
val add_background : scene -> color:color -> scene
val add_light_source : scene ->
location:float * float * float -> color:color -> scene
val add_camera : scene ->
location:float * float * float ->
look_at:float * float * float ->
?kind:Camera.t -> ?angle:int -> unit -> scene
val add_ambient_light : scene -> color:float * float * float -> scene
val new_finish : ?ambient:float -> ?diffuse:float -> ?specular:float -> unit -> finish
val new_texture : ?color:color ->
?scale:int ->
?def:Textures.texture_def ->
?finish:finish -> unit -> texture
val new_checker : color1:color ->
color2:color -> ?finish:finish -> unit -> texture
val add_sphere : scene ->
center:float * float * float ->
radius:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
val add_cylinder : scene ->
center1:float * float * float ->
center2:float * float * float ->
radius:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
val add_box : scene ->
corner1:float * float * float ->
corner2:float * float * float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
val add_cone : scene ->
center1:float * float * float ->
radius1:float ->
center2:float * float * float ->
radius2:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
val add_torus : scene ->
major:float ->
minor:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
major-radius
/ minor-radius
val add_polygon : scene ->
pnts:(float * float) list ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
val add_plane : scene ->
norm:int * int * int ->
dist:int -> ?texture:texture -> unit -> scene
val add_text : scene ->
font:string ->
text:string ->
?thickness:float ->
?offset:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float ->
?texture:texture -> unit -> scene
val get_color : color:color -> string
val get_include : inc:inc_file -> string
val get_comment : com:string -> string
val get_background : color:color -> string
val get_light_source : location:float * float * float -> color:color -> string
val get_camera : location:float * float * float ->
look_at:float * float * float ->
?kind:Camera.t -> ?angle:int -> unit -> string
val get_ambient_light : color:float * float * float -> string
val get_finish : ?ambient:float -> ?diffuse:float -> ?specular:float -> unit -> string
val get_texture : ?color:Color.t ->
?scale:int ->
?def:Textures.texture_def -> ?finish:string -> unit -> string
val get_checker : color1:color ->
color2:color -> ?finish:string -> unit -> string
val get_sphere : center:float * float * float ->
radius:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_cylinder : center1:float * float * float ->
center2:float * float * float ->
radius:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_box : corner1:float * float * float ->
corner2:float * float * float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_cone : center1:float * float * float ->
radius1:float ->
center2:float * float * float ->
radius2:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_torus : major:float ->
minor:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_polygon : pnts:(float * float) list ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_plane : norm:int * int * int -> dist:int -> ?texture:string -> unit -> string
val get_text : font:string ->
text:string ->
?thickness:float ->
?offset:float ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> ?texture:string -> unit -> string
val get_union : group:string ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> unit -> string
val add_union : scene ->
group:(scene -> scene) ->
?translate:float * float * float ->
?rotate:float * float * float ->
?scale:float * float * float -> unit -> scene
val get_difference : elem1:string -> elem2:string -> ?texture:string -> unit -> string
val add_difference : scene ->
elem1:string ->
elem2:string -> ?texture:texture -> unit -> scene
val add_elem : scene -> elem:string -> unit -> scene
module Desc:sig
..end
module Float:sig
..end
module Int:sig
..end
module Mesh:sig
..end
module MeshC:sig
..end
module MeshD:sig
..end
module MeshD2:sig
..end