Module Povray

module Povray: sig .. end

A PovRay module


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.

Scene Description
type location = float * float * float 
module Color: sig .. end
type color = Color.t 
type texture 
type triangle = location * location * location 
type triangle_c = triangle * Color.t 
type face_indice = int * int * int 
type face_indices = face_indice array 
type scene_desc = 
| Include of string
| Background of color
| Camera of location * location
| Light_source of location * color
| Ambient_light of float * float * float
| Sphere of float * location * texture * location option
* location option
(*

radius / center / texture / translate / scale

*)
| Cone of float * float * location * location * texture (*

radius1 / radius2 / center1 / center2 / texture

*)
| Box of location * location * texture * location option
* location option * location option
(*

corner1 / corner2 / texture / translate / rotate / scale

*)
| Cylinder of float * location * location * texture (*

radius / center1 / center2 / texture

*)
| Mesh of triangle list * texture * location option
* location option * location option
(*

triangles / texture / translate / rotate / scale

*)
| MeshC of (triangle * color) list * location option
* location option * location option
(*

(triangles / colors) / translate / rotate / scale

*)
module Textures: sig .. end
type texture_def = Textures.stones 
Adds to a Scene
type scene 
val new_scene : unit -> scene
val string_of_scene : scene -> string
val print_scene : scene -> unit
module Inc_file: sig .. end
type inc_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_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 -> scene
val add_ambient_light : scene -> color:float * float * float -> scene
val new_texture : ?color:color ->
?scale:int -> ?def:texture_def -> unit -> texture
val new_checker : color1:color -> color2:color -> unit -> texture
Adds Shapes to a Scene
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 -> ?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 -> ?texture:texture -> unit -> scene
val add_torus : scene ->
major:float ->
minor:float ->
?translate:float * float * float ->
?rotate: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 -> ?texture:texture -> unit -> scene
Print to Screen
val get_color : color:color -> string
val get_include : inc:inc_file -> 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 -> string
val get_ambient_light : color:float * float * float -> string
val get_texture : ?color:color ->
?scale:int -> ?def:texture_def -> unit -> string
val get_checker : color1:color -> color2:color -> unit -> string
Prints shapes to the Screen
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 -> ?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 -> ?texture:string -> unit -> string
val get_torus : major:float ->
minor:float ->
?translate:float * float * float ->
?rotate: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 -> ?texture:string -> unit -> string
Groups
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
CSG-Diff
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
Description Conv
module Desc: sig .. end
Selecting Floats or Ints
module Float: sig .. end
module Int: sig .. end
Meshes
module Mesh: sig .. end
module MeshC: sig .. end
module MeshD: sig .. end
module MeshD2: sig .. end