#include #define USE_SURFACE_BTREE #include #include #include "GTS_inline.h" -- REMEMBER ForeignPtr for garbage collection! -- | Bindings DSL file for the Gnu Triangulated Surface Library module Bindings.GTS where #strict_import -- import Bindings.GObject import Bindings.GLib.Fundamentals import Bindings.GLib.Fundamentals.BasicTypes #cinline GTS_CHECK_VERSION, -> -> -> IO #globalvar gts_allow_floating_vertices, IO #starttype GSList #field data, #field next, Ptr #stoptype -- | Allocate a node in a GSList from gobject. Note this function should not be used as the append/insert -- functions call it internally #ccall g_slist_alloc, IO (Ptr ) -- | Free all the nodes in an GSList. See the glib library #ccall g_slist_free, Ptr -> IO () -- | Free one node in a GSList #ccall g_slist_free_1, Ptr -> IO () -- | Get the pointer to the next element in the GSList #cinline g_slist_next, Ptr -> IO (Ptr ) -- | Get the pointer to the last element in the GSList #ccall g_slist_last, Ptr -> IO (Ptr ) -- | Get the length of the GSList #ccall g_slist_length, Ptr -> IO -- | Get the n-th element of the GSList counting from 0 #ccall g_slist_nth, Ptr -> -> IO (Ptr ) -- | Append a new node to a GSList #ccall g_slist_append, Ptr -> -> IO (Ptr ) -- | Insert a new node in a GSList before the referenced node #ccall g_slist_insert_before, Ptr -> Ptr -> -> IO (Ptr ) -- | Insert a new node in a GSList at the specified position #ccall g_slist_insert, Ptr -> -> -> IO (Ptr ) -- | Callback for the GTS Object class initialization - don't use this unless you know what you are doing #callback GtsObjectClassInitFunc, Ptr -> IO () -- | Callback for the GTS Object initialization - don't use this unless you know what you are doing #callback GtsObjectInitFunc, Ptr -> IO () -- | Callback for the GTS argument set method - don't use this unless you know what you are doing #callback GtsArgSetFunc, Ptr -> IO () -- | Callback for the GTS argument get method - don't use this unless you know what you are doing #callback GtsArgGetFunc, Ptr -> IO () #num GTS_CLASS_NAME_LENGTH -- | Type of the GTS Vector object in Haskell #starttype GtsVector #stoptype -- | Type of the GTS Matrix object in Haskell #starttype GtsMatrix #stoptype -- | Create a new GTS Matrix 4x4 object and return the pointer to it. #ccall gts_matrix_new, -> -> -> -> -> -> -> -> -> -> -> -> -> -> -> -> IO (Ptr ) -- | Set the fields of an existing GTS Matrix object #ccall gts_matrix_assign,Ptr -> -> -> -> -> -> -> -> -> -> -> -> -> -> -> -> -> IO (Ptr ) -- | Destroy a GTS matrix and free the associated memory - Use this with ForeignPtr for GC #ccall gts_matrix_destroy,Ptr -> IO () -- | Set a GTS matrix to the Zero matrix (if the matrix is NULL a new one is allocated) #ccall gts_matrix_zero,Ptr -> IO (Ptr ) -- | Set a GTS matrix to the Identity matrix (if the matrix is NULL a new one is allocated) #ccall gts_matrix_identity,Ptr -> IO (Ptr ) -- | Transpose a GTS Matrix and return the newly allocated matrix #ccall gts_matrix_transpose,Ptr -> IO (Ptr ) -- | Invert a GTS Matrix and return the newly allocated matrix or NULL if the matrix can't be inverted #ccall gts_matrix_inverse,Ptr -> IO (Ptr ) -- | Calculate the product of two matricies and return the newly allocated matrix #ccall gts_matrix_product, Ptr -> Ptr -> IO (Ptr ) -- | Scale a GTS Matrix in place #ccall gts_matrix_scale, Ptr -> Ptr -> IO (Ptr ) -- | Translate the GTS Matrix by the GTS Vector (If the Matrix is NULL a new one is allocated and translated) #ccall gts_matrix_translate, Ptr -> Ptr -> IO (Ptr ) -- | Rotate the GTS Matrix around the vector by the #ccall gts_matrix_rotate, Ptr -> Ptr -> -> IO (Ptr ) -- | Type for an (r,g,b) triple in GTS (floating point) #starttype GtsColor #field r, #field g, #field b, #stoptype -- | Callback for most GTS visitors #callback GtsFunc, -> -> IO -- | Callback for gts_vertices_merge #callback GtsVertexMergeFunc, Ptr -> Ptr -> IO -- | GTS formatted data file #starttype GtsFile #field line, #field pos, #field error,Ptr #stoptype -- | A GTS formatted data file variable #starttype GtsFileVariable #stoptype -- | Open a C file #ccall fopen,CString -> CString -> IO (Ptr CFile) -- | Close a C file #ccall fclose, Ptr CFile -> IO Int -- | Create a new GTS file handle from an C file #ccall gts_file_new, Ptr CFile -> IO (Ptr ) -- | Create a new GTS file handle from a C String. Note this method doesn't seem to work #ccall gts_file_new_from_string, Ptr -> IO ( Ptr ) -- | Get a character from a GTS file (Don't use this) #ccall gts_file_getc, Ptr -> IO -- | Destroy a GTS file handle and free the memory #ccall gts_file_destroy, IO (Ptr ) -- #cinline GTS_OBJECT_FLAGS, Ptr -> #starttype GtsObjectClassInfo #array_field name, #field object_size, #field class_size, #stoptype #starttype GtsObjectClass #field info, #field parent_class,Ptr #stoptype #starttype GtsObject #field klass, Ptr #field flags, #stoptype #starttype GtsPointClass #field parent_class, #field binary, #stoptype #starttype GtsPoint #field object, Ptr #field x, #field y, #field z, #stoptype #ccall gts_object_class, IO #ccall gts_object_class_new, Ptr -> Ptr -> IO #ccall gts_object_check_cast, -> -> IO #ccall gts_object_class_check_cast, -> -> IO -- #cinline gts_object_is_from_class, -> -> IO -- #cinline gts_object_class_is_from_class, -> -> IO #ccall gts_object_class_from_name,Ptr -> IO (Ptr ) #starttype GtsRange #field min, #field max, #field sum, #field sum2, #field mean, #field stddev, #field n, #stoptype #starttype GtsSegment #stoptype #starttype GtsTriangleClass #stoptype #starttype GtsTriangle #field e1, Ptr #field e2, Ptr #field e3, Ptr #stoptype -- | Create a triangle which is guarenteed to enclose all the points in the list #ccall gts_triangle_enclosing, Ptr -> Ptr -> -> IO (Ptr ) -- | Get the class descriptor for the GTS Triangle class #ccall gts_triangle_class, IO (Ptr ) -- | Create a new triangle from 3 edges #ccall gts_triangle_new, Ptr -> Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Discard the existing edges of the triangle and replace with the new ones #ccall gts_triangle_set, Ptr -> Ptr -> Ptr -> Ptr -> IO () -- | Get the area of this triangle #ccall gts_triangle_area, Ptr -> IO -- | Get the perimeter of this triangle #ccall gts_triangle_perimeter, Ptr -> IO -- | Get a measure of the quality of this triangle (how close to equilateral it is?) #ccall gts_triangle_quality, Ptr -> IO -- | Get the normal to the plane of this triangle #ccall gts_triangle_normal, Ptr -> Ptr -> Ptr -> Ptr -> IO () -- | Changes the orientation of triangle t, turning it inside out #ccall gts_triangle_revert, Ptr -> IO () #ccall gts_triangle_orientation, Ptr -> IO #ccall gts_triangle_neighbors, Ptr -> IO (Ptr ) #ccall gts_triangle_vertices_edges, Ptr -> Ptr -> Ptr (Ptr ) -> Ptr (Ptr ) -> Ptr (Ptr ) -> Ptr (Ptr ) -> Ptr (Ptr ) -> Ptr (Ptr ) -> IO () #ccall gts_triangle_vertices, Ptr -> Ptr -> Ptr (Ptr ) -> Ptr (Ptr ) -> Ptr (Ptr ) -> IO () #ccall gts_triangle_vertex_opposite, Ptr -> Ptr -> IO (Ptr -> Ptr -> IO (Ptr -> IO #ccall gts_triangle_circumcircle_center, Ptr -> Ptr -> IO (Ptr ) #ccall gts_triangle_interpolate_height, Ptr -> Ptr -> IO () #ccall gts_triangles_from_edges, Ptr -> IO (Ptr ) #starttype GtsVertex #field p, #stoptype #starttype GtsVertexClass #stoptype -- | Clear a range #ccall gts_range_init, Ptr -> IO () #ccall gts_range_reset,Ptr -> IO () #ccall gts_range_add_value,Ptr -> -> IO () #ccall gts_range_update,Ptr -> IO () -- | GLib class pointer for the GTS point object class #ccall gts_point_class, IO (Ptr ) -- | Create a new GTS point in 3d space #ccall gts_point_new, Ptr -> -> -> -> IO ( Ptr ) -- | Set the value of a GTS point in 3d space #ccall gts_point_set, Ptr -> -> -> -> IO () -- | True iff the point is within or on the boundary of the box defined by the two other points #cinline gts_point_is_in_rectangle, Ptr -> Ptr -> Ptr -> IO -- | GLib class pointer for the GTS vertex class (vertex derives from point) #ccall gts_vertex_class,IO (Ptr ) -- | Create a new GTS vertex in 3d space #ccall gts_vertex_new,Ptr -> -> -> -> IO (Ptr ) -- | True if this vertex is not part of a GTS segment #ccall gts_vertex_is_unattached, Ptr -> IO -- | Return the number of connected triangles sharing the vertex, if second parameter is true then sever the connection #ccall gts_vertex_is_contact, Ptr -> -> IO -- | Null unless two vertices are the endpoints of the same segment, in which case return the segment #ccall gts_vertices_are_connected, Ptr -> Ptr -> IO (Ptr -> Ptr -> IO () -- | Adds to list all the GtsVertex connected to v by a GtsSegment and not already in list. If surface is not NULL only the vertices connected to v by an edge belonging to surface are considered. #ccall gts_vertex_neighbors, Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Adds all the GtsTriangle which share v as a vertex and do not already belong to list. #ccall gts_vertex_triangles, Ptr -> Ptr -> IO (Ptr ) -- | Adds all the GtsFace belonging to surface (if not NULL) which share v as a vertex and do not already belong to list. #ccall gts_vertex_faces, Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | A list of GtsEdge describing in counterclockwise order the boundary of the fan of summit v, the faces of the fan belonging to surface #ccall gts_vertex_fan_oriented, Ptr -> Ptr -> IO (Ptr ) -- | TRUE if v is strictly contained in the diametral circle of e, FALSE otherwise #ccall gts_vertex_encroaches_edge, Ptr -> Ptr -> IO -- | For each vertex v in vertices look if there are any vertex of vertices contained in a box centered on v of size 2*epsilon. If there are and if check is not NULL and returns TRUE, replace them with v (using gts_vertex_replace()), destroy them and remove them from list. This is done efficiently using Kd-Trees. #ccall gts_vertices_merge, Ptr -> -> -> IO (Ptr ) #starttype GtsVertexNormal #field n, #stoptype #ccall gts_vertex_normal_class,IO (Ptr ) #starttype GtsColorVertex #field c, #stoptype #ccall gts_color_vertex_class,IO (Ptr ) #starttype GtsSurface #field keep_faces, #stoptype #starttype GtsSurfaceClass #stoptype #starttype GtsEdgeClass #stoptype #starttype GtsEdge #field triangles,Ptr #field segment,Ptr #stoptype #starttype GtsFaceClass #stoptype #starttype GtsFace #stoptype #starttype GtsSurfaceStats #stoptype #starttype GtsSurfaceQualityStats #stoptype #ccall gts_face_class,IO (Ptr ) #ccall gts_edge_class,IO (Ptr ) #ccall gts_surface_class,IO (Ptr ) -- | Create a new empty surface which uses the specified types of sub-object #ccall gts_surface_new,Ptr -> Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Add a face to a surface #ccall gts_surface_add_face, Ptr -> Ptr -> IO () -- | Read a surface from a GTS formatted file #ccall gts_surface_read, Ptr -> Ptr -> IO -- | Remove a face from a surface #ccall gts_surface_remove_face,Ptr -> Ptr -> IO () -- | Get the surface area of all triangles in the surface #ccall gts_surface_area, Ptr -> IO -- | Get some statistics on the surface #ccall gts_surface_stats, Ptr -> Ptr -> IO () -- | Get some statistics on the quality of the triangles making up the surface #ccall gts_surface_quality_stats, Ptr -> Ptr -> IO () -- | Invoke a function for each vertex in the surface #ccall gts_surface_foreach_vertex, Ptr -> -> -> IO () -- | Invoke a function for each edge in the surface #ccall gts_surface_foreach_edge, Ptr -> -> -> IO () -- | Invoke a function for each face in the surface #ccall gts_surface_foreach_face, Ptr -> -> -> IO () -- | Invoke a function for each face in the surface and remove the face afterwards #ccall gts_surface_foreach_face_remove, Ptr -> -> -> IO -- | Generate a surface which is a tessalated model of a sphere #ccall gts_surface_generate_sphere, Ptr -> -> IO ( Ptr ) -- |Add a copy of all the faces, edges and vertices of s2 to s1. #ccall gts_surface_copy, Ptr -> Ptr -> IO (Ptr ) -- | Adds all the faces of with which do not already belong to s to s. #ccall gts_surface_merge, Ptr -> Ptr -> IO () -- | True iff the surface describes a manifold #ccall gts_surface_is_manifold, Ptr -> IO -- | True iff the surface is closed #ccall gts_surface_is_closed, Ptr -> IO -- | True iff all the faces of the surface have a compatible orientation #ccall gts_surface_is_orientable, Ptr -> IO -- | Return the volume of the domain bounded by the surface, only valid if the surface is closed and orientable #ccall gts_surface_volume, Ptr -> IO -- | Return the center of mass of the domain bounded by the surface s, only valid if the surface is closed and orientable #ccall gts_surface_center_of_mass, Ptr -> Ptr -> IO -- | Return the center of area of the surface (all faces should be co-planar) #ccall gts_surface_center_of_area, Ptr -> Ptr -> IO #ccall gts_surface_vertex_number, Ptr -> IO #ccall gts_surface_edge_number, Ptr -> IO #ccall gts_surface_face_number, Ptr -> IO #ccall gts_surface_boundary, Ptr -> IO (Ptr ) #ccall gts_surface_split, Ptr -> IO (Ptr ) #ccall gts_surface_write, Ptr -> Ptr CFile -> IO () #starttype GtsSurfaceInterClass #stoptype #starttype GtsSurfaceInter #field s1,Ptr #field s2,Ptr #stoptype #starttype GNode #stoptype -- | Create a new GTS Face from the 3 edges #ccall gts_face_new, Ptr -> Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Get the class for a surface intersection #ccall gts_surface_inter_class,IO (Ptr ) -- | Create a new surface intersection from the two surfaces and the precomputed face bounding box trees #ccall gts_surface_inter_new, Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> -> -> IO (Ptr ) -- | True iff the edges in the intersection form a closed curve #ccall gts_surface_inter_check, Ptr -> Ptr -> IO -- | Adds to surface the part of the surface described by si and op. #ccall gts_surface_inter_boolean, Ptr -> Ptr -> -> IO () -- | A new GtsSurface containing the faces of s which are self-intersecting or NULL if no faces of s are self-intersecting. #ccall gts_surface_is_self_intersecting, Ptr -> IO (Ptr ) -- | A list of GtsEdge defining the curve intersection of the two surfaces. #ccall gts_surface_intersection, Ptr -> Ptr -> Ptr -> Ptr -> IO (Ptr ) #ccall gts_bb_tree_new, Ptr -> IO (Ptr ) #ccall gts_bb_tree_surface, Ptr -> IO (Ptr ) #ccall gts_bb_tree_destroy, Ptr -> -> IO () -- | TRUE if the ray starting at p and ending at (+infty, p->y, p->z) intersects with bb, FALSE otherwise. #ccall gts_bb_tree_stabbed, Ptr -> Ptr -> IO (Ptr ) -- | Destroy a GTS object and free the associated memory. This is the generic version, see the typed helper functions #ccall gts_object_destroy, Ptr -> IO () -- #starttype GtsConstraintClass -- #stoptype -- #starttype GtsConstraint -- #stoptype #callback GtsEncroachFunc, Ptr -> Ptr -> Ptr -> -> IO #callback GtsKeyFunc, -> -> IO #ccall gts_constraint_class, IO (Ptr ) #ccall gts_point_locate, Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Create a new edge from a pair of vertices #ccall gts_edge_new, Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Replaces e with with. For each triangle which uses e as an edge, e is replaced with with. The with->triangles list is updated appropriately and the e->triangles list is freed and set to NULL #ccall gts_edge_replace, Ptr -> Ptr -> IO () -- | Performs an "edge swap" on the two triangles sharing e and belonging to s. #ccall gts_edge_swap, Ptr -> Ptr -> IO () #ccall gts_segment_triangle_intersection, Ptr -> Ptr -> -> IO (Ptr ) -- | Tests if the planar projection (x, y) of p is inside or outside the circumcircle of the planar projection of t. This function is geometrically robust. #ccall gts_point_in_triangle_circle,Ptr -> Ptr -> IO -- | Checks for orientation of the projection of three points on the (x,y) plane. The result is also an approximation of twice the signed area of the triangle defined by the three points. This function uses adaptive floating point arithmetic and is consequently geometrically robust. #ccall gts_point_orientation, Ptr -> Ptr -> Ptr -> IO -- | TRUE if p is inside the surface defined by tree, FALSE otherwise. #ccall gts_point_is_inside_surface, Ptr -> Ptr -> -> IO -- | Tests if the planar projection (x, y) of p is inside or outside the circle defined by the planar projection of p1, p2 and p3. #ccall gts_point_in_circle, Ptr -> Ptr -> Ptr -> Ptr -> IO -- | Checks if p4 lies above, below or on the plane passing through the points p1, p2 and p3. Below is defined so that p1, p2 and p3 appear in counterclockwise order when viewed from above the plane. The returned value is an approximation of six times the signed volume of the tetrahedron defined by the four points. This function uses adaptive floating point arithmetic and is consequently geometrically robust. #ccall gts_point_orientation_3d, Ptr -> Ptr -> Ptr -> Ptr -> Ptr -> IO #starttype GtsBBoxClass #stoptype #ccall gts_bbox_class, IO (Ptr ) #starttype GtsBBox #field x1, #field y1, #field z1, #field x2, #field y2, #field z2, #field bounded, #stoptype -- | A list of triangle strips containing all the triangles of s. A triangle strip is itself a list of successive triangles having one edge in common. #ccall gts_surface_strip, Ptr -> IO (Ptr ) -- | Using the gts_bb_tree_surface_distance() and gts_bb_tree_surface_boundary_distance() functions fills face_range and boundary_range with the min, max and average Euclidean (minimum) distances between the faces of s1 and the faces of s2 and between the boundary edges of s1 and s2. #ccall gts_surface_distance, Ptr -> Ptr -> -> Ptr -> Ptr -> IO () -- | A new GtsBBox bounding box of surface. #ccall gts_bbox_surface, Ptr -> Ptr -> IO ( Ptr ) -- | TRUE if the bounding boxes bb1 and bb2 are overlapping (including just touching), FALSE otherwise. #ccall gts_bboxes_are_overlapping, Ptr -> Ptr -> IO -- | Add a constraint edge to a Delaunay surface #ccall gts_delaunay_add_constraint, Ptr -> Ptr -> IO (Ptr ) -- | NULL if the planar projection of surface is a Delaunay triangulation (unconstrained), a GtsFace violating the Delaunay property otherwise. #ccall gts_delaunay_check, Ptr -> IO (Ptr ) -- | Removes all the edges of the boundary of surface which are not constraints. #ccall gts_delaunay_remove_hull, Ptr -> IO () -- | Recursively split constraints of surface which are encroached by vertices of surface (see Shewchuk 96 for details). The split constraints are destroyed and replaced by a set of new constraints of the same class. If gts_vertex_encroaches_edge() is used for encroaches, the resulting surface will be Delaunay conforming. If steiner_max is positive or nul, the recursive splitting procedure will stop when this maximum number of Steiner points is reached. In that case the resulting surface will not necessarily be Delaunay conforming. #ccall gts_delaunay_conform,Ptr -> -> FunPtr -> -> IO -- | An implementation of the refinement algorithm described in Ruppert (1995) and Shewchuk (1996). #ccall gts_delaunay_refine,Ptr -> -> FunPtr -> -> FunPtr -> -> IO -- | Add one vertex to a Delaunay triangulation preserving the Delaunay property #ccall gts_delaunay_add_vertex, Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Add one vertex to a face of a Delaunay triangulation preserving the Delaunay property #ccall gts_delaunay_add_vertex_to_face, Ptr -> Ptr -> Ptr -> IO (Ptr ) -- | Removes v from the Delaunay triangulation defined by surface and restores the Delaunay property. Vertex v must not be used by any constrained edge otherwise the triangulation is not guaranteed to be Delaunay. #ccall gts_delaunay_remove_vertex, Ptr -> Ptr -> IO () -- Typed helper functions #ccall gts_surface_destroy, Ptr -> IO () #ccall gts_triangle_destroy, Ptr -> IO () #ccall gts_vertex_destroy, Ptr -> IO ()