package OCADml

  1. Overview
  2. Docs

Generation, and manipulation of triangular meshes (points and faces).

This data type and its constructors/transformers are based on the the vnf structure module of the BOSL2 OpenSCAD library, but with the constraint that all faces are triangular on construction.

type tri = int * int * int

Triangular face indices

type t

Triangular mesh (points and faces)

Basic Constructors

val empty : t

An empty t, with no points.

val make : points:V3.t list -> faces:tri list -> t

make ~points ~faces

Create a mesh t from a list of V3.t points, and a list of faces described by indices into points.

Accessors

val size : t -> int
val points : t -> V3.t list
val e : t -> int -> V3.t

e t i gets the point at index i

val faces : t -> tri list

Low-level Generators

type endcaps = [
  1. | `Loop
    (*

    Last/top row wrapped to the first/bottom

    *)
  2. | `Both
    (*

    Both bottom and top rows are closed with flat faces

    *)
  3. | `None
    (*

    Neither top or bottom rows are closed with a face

    *)
  4. | `Top
    (*

    A face is generated to close the top row with itself

    *)
  5. | `Bot
    (*

    A face is generated to close the bottom row with itself

    *)
]

Describes desired row wrapping behaviour in of_rows, which creates a mesh from rows of points.

type style = [
  1. | `Default
  2. | `Alt
  3. | `MinEdge
  4. | `Quincunx
  5. | `Convex
  6. | `Concave
]

Quadrilateral face triangulation strategy.

val prune_rows : ?min_dist:float -> Path3.t list -> int list * Path3.t list

prune_rows ?min_dist rows

Filter rows such that each row polygon is at least min_dist (default 0.05) above the plane of the previous polygon, indicating the dropped indices. This can be useful for avoiding self-intersections in the output of of_rows. Note that all polygons in rows must be planar, else Failure will be raised.

val of_rows : ?rev:bool -> ?endcaps:endcaps -> ?col_wrap:bool -> ?style:style -> V3.t list list -> t

of_rows ?rev ?endcaps ?col_wrap ?style rows

Create a triangular mesh t from a list of layers (counter_clockwise loops of 3d points). endcaps defaults to `Both, which specifies that faces should be generated to close off the bottom and top layers of the generated shape. If it is instead set to `Loop, the open faces of the first and last layers will be closed with one another. For more advanced usages, one or both of the endcaps can be left open, so the resulting meshes can be closed off by some other means.

  • col_wrap sets whether faces should be generated to loop between the ends of each row.
  • If rev is true, faces winding direction will be reversed (default = false)
  • style governs how the quadrilaterals formed by the rows and columns of points are divided into triangles:

    • `Default is an arbitrary systematic subdivision in the same direction
    • `Alt is the uniform subdivision in the other (alternate direction)
    • `MinEdge picks the shorter edge to subdivide the quadrilateral, so the division may not be uniform across the shape
    • `Quincunx adds a vertex in the middle of each quadrilateral and creates four triangles
    • `Convex and `Concave choose the locally convex/concave subdivision
  • If rows is empty, a empty is returned. Throws Invalid_argument if rows contains only one row, or if it is not rectangular (any row differs in length).
val of_ragged : ?looped:bool -> ?rev:bool -> V3.t list list -> t

of_ragged ?looped ?reverse rows

Create a triangular mesh from a list of rows, where each row can differ in length relative to its neighbours by up to 2. Since the rows can be ragged, no (columnar) wrapping is done, thus they are best described as rows, rather than layers as with of_rows which produces a mesh of a closed shape. Instead, this function is useful for the generation of triangular patches that can be joined with one another to create a complete mesh. Setting looped to true will generate faces between the last and first rows, so long as their lengths differ by no more than 2. Face winding order is reversed if reverse is true. Throws Invalid_argument if a row length delta of greater than 2 is encountered.

val of_path2 : ?rev:bool -> Path2.t -> t

of_path3 ?rev layer

Create a mesh from a single path (a closed loop of V2.t), returning a t with a single face including all of the points. Face winding order is reversed if rev is true. This can be useful for producing a flat patch mesh to be combined with other meshes to produce a complete shape.

val of_path3 : ?rev:bool -> Path3.t -> t

of_path3 ?rev layer

Create a mesh from a single path (a closed loop of V3.t, should be coplanar though it is not confirmed), returning a t with a single face including all of the points. Face winding order is reversed if rev is true. This can be useful for producing a flat patch mesh to be combined with other meshes to produce a complete shape.

val of_poly2 : ?rev:bool -> Poly2.t -> t

of_poly2 ?rev poly

Create a mesh from a 2d polygon. If poly does not have any holes, then this is equivalent to of_path2. If there are holes, polyhole partitioning is performed to determine a set of faces that can close the points.

The earcutting algorithm used to partition the polygon into faces is a port of RonaldoCMP's work found here.

val of_poly3 : ?rev:bool -> Poly3.t -> t

of_poly3 ?rev poly

Create a mesh from a 3d polygon. If poly does not have any holes, then this is equivalent to of_path3. If there are holes, polyhole partitioning is performed to determine a set of faces that can close the points.

The earcutting algorithm used to partition the polygon into faces is a port of RonaldoCMP's work found here.

val of_polygons : Path3.t list -> t

of_polygons polys

Create a triangular mesh from a list of polygonal point faces.

val hull : Path3.t -> t

hull points

Create a convex hull mesh that encloses points. If the points are coplanar, a 2-dimensional hull is found, resulting in an unclosed single face mesh (as with of_path3). Unused points are not discarded.

Skins

Functions for generating meshes which cover over a sequence of closed polygonal Path3.t profiles. Ported from the skin module of the BOSL2 OpenSCAD library.

type resampler = [
  1. | `Direct of [ `ByLen | `BySeg ]
  2. | `Reindex of [ `ByLen | `BySeg ]
]

Path resampling vertex mapping strategies.

Each of these variants specify that profiles of incommensurate length should simply resampled with Path3.subdivide with the provided point distribution frequency strategy ([`ByLen | `BySeg]). In the case of `Direct _, the profiles are assumed to be "lined up", with the points at their zeroth indices corresponding to eachother. The `Reindex _ strategy will rotate the second profile of a pair via Path3.reindex_polygon following resampling to minimize the distance between the zeroth indices of the two paths.

type duplicator = [
  1. | `Distance
    (*

    Minimize the length of the edges between associated vertices. Best results when connecting discrete polygon profiles with low point counts.

    *)
  2. | `FastDistance
    (*

    Like `Distance, but profiles are assumed to already be lined up, with their zeroth indices corresponding to one another.

    *)
  3. | `Tangent
    (*

    Split finely sampled (convex) curve into groups of points, and map each group to point on the smaller discrete polygon. Can fail if the larger curved path is non-convex, or does not have enough points.

    *)
]

Point duplicating vertex mapping strategies.

Each of these variants specify profiles of incommensurate length should be matched up by computing vertex mappings between the profiles, and duplicating vertices on the smaller/shorter profile until the point counts are equalized. See the conspicuously named vertex matching functions Path3.distance_match, Path3.aligned_distance_match, and Path3.tangent_match for more details (also available in the Path2 module).

type mapping = [
  1. | resampler
  2. | duplicator
]

Vertex count matching strategy specification type.

val slice_profiles : ?looped:bool -> slices:[< `Flat of int | `Mix of int list ] -> Path3.t list -> Path3.t list

slice_profiles ?looped ~slices profiles

Linearly transition between each neighbouring pair of closed paths in profiles to produce new interpolated list of profiles. The number of slices inserted between can either be the same between each pair (`Flat n), or specified separately with `Mix ns. If looped is true, then slices will also be inserted between the last and initial profiles (default is false). Lists of profiles such as these can be used to produce meshes with of_rows (as skin does).

Raises Invalid_argument if the length of `Mix ns does not correspond to the number of transitions, or if profiles has fewer than two elements.

val skin : ?style:style -> ?endcaps:endcaps -> ?refine:int -> ?mapping:[ `Flat of mapping | `Mix of mapping list ] -> slices:[< `Flat of int | `Mix of int list ] -> Path3.t list -> t

skin ?style ?endcaps ?refine ?mapping ~slices profiles

Produce a mesh that skins over two or more 3d profiles -- closed, ideally coplanar (though some slight variation can be ok) paths. This works by linearly interpolating between neighbouring profiles with slices steps, and passing the profiles along to of_rows, which generates faces to enclose the shape. For this to be well defined, each row must have the same length, thus mapping can be used to specify the strategy used to map/associate the vertices between them and reconcile the point counts and improve alignment for their connecting edges (see resampler and duplicator configuration variants). By default this is `Direct, which simply applies resampling without altering the vertex associations established by the start indices of each profile.

  • refine can be specified to apply additional upsampling which may help to improve the smoothness of the resulting mesh. Uses Path3.subdivide with the sampling frequency indicated for resampler mapped transitions, and `BySeg for duplicators.
  • slices and mapping can be provided as `Flat _ to be applied to all transitions, or as `Mix l, where l is a list with length equal to the number of profile transitions (length profiles - 1, or length profiles if endcaps is `Loop)
  • NOTE: mixing mapping strategies can be fickle, and some combinations may not work depending on the profiles. This may improve as kinks are worked out, but maybe not
val skin_between : ?style:style -> ?endcaps:[ `Both | `None | `Top | `Bot ] -> ?refine:int -> ?mapping:mapping -> slices:int -> Path3.t -> Path3.t -> t

skin_between ?style ?endcaps ?refine ?mapping ~slices a b

Create a mesh that skins over a linear interpolation/morph between 3d profiles a and b over slices steps. See skin for more details.

val skline : ?style:style -> ?endcaps:endcaps -> ?refine:int -> ?sampling:[ `Flat of [ `ByLen | `BySeg ] | `Mix of [ `ByLen | `BySeg ] list ] -> ?fn:int -> ?size: [ `Abs of float list | `Rel of float list | `Flat of [ `Abs of float | `Rel of float ] | `Mix of [ `Abs of float | `Rel of float ] list ] -> ?tangents:[ `NonUniform | `Uniform | `Tangents of V3.t list ] -> Path3.t list -> t

skline ?style ?endcaps ?refine ?sampling ?fn ?size ?tangents profiles

Create a mesh bound by bezier splines passing through the paths formed by the points of profiles -- closed, ideally coplanar (though some slight variation can be ok) paths. Unlike this functions linear counterpart skin, only direct mapping (vertex associations are already handled by the user, as determined by the start index of each profile) is available, though ?sampling is provided to give control over whether points are added by segment or by length when resampling (default `ByLen).

  • fn sets the number of segments to be sampled from the splines (default 64)
  • refine can be specified to apply additional upsampling which may help to improve the smoothness of the resulting mesh. Uses Path3.subdivide with the sampling frequency indicated by sampling.
  • see Bezier3.of_path for notes on ?size and ?tangents

Sweeps, extrusions, and morphs with roundovers

Sweeps, extrusions and morphs from 2d to 3d. Each of which can be given rounded over end caps via their optional ?caps parameters with specifications contsructed by the Cap module. and the optional ?caps. Roundovers are based on the implementations found in the BOSL2 library's offset_sweep functions from the rounding module.

module Cap : sig ... end

Configuration module for declaring how extrusions from 2d to 3d via sweep should be capped off.

Fixed polygon sweeps and extrusions

val sweep : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?caps:Cap.t -> transforms:Affine3.t list -> Poly2.t -> t

sweep ?check_valid ?style ?winding ?merge ?fn ?fs ?fa ?caps ~transforms poly

Sweep a 2d polygon into a 3d mesh by applying a sequence of transforms to the original shape. The winding parameter can be used to set automatic enforcement of polygon winding direction, which will impact the winding of the generated faces of the mesh. What is done with the endcaps can be specified with caps. By default the ends of the extrusion are sealed with flat faces, but they can instead be looped to eachother, left empty, or rounded over. If style is provided, it will be passed along to of_rows, which handles converting the swept shapes into a mesh.

If merge is true (as is default), merge_points is applied to the resulting mesh, as duplicate points are introduced when end caps are joined to the outer and inner meshes. If the duplicate points aren't a problem for you (they aren't necessarily), this can be turned off to save some compute.

check_valid determines whether validity checks are performed during offset operations (see Path2.offset), for cap roundovers (if specified). Additionally, unless check_valid is `No, polygon validation will be performed with final outer and inner paths of the caps before their mesh is generated.

val extrude : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?fa:float -> ?slices:int -> ?scale_ez:(V2.t * V2.t) -> ?twist_ez:(V2.t * V2.t) -> ?scale:V2.t -> ?twist:float -> ?center:bool -> ?caps:[ `Caps of Cap.caps ] -> height:float -> Poly2.t -> t

extrude ~height poly

Vertically extrude a 2d polygon from the XY plane to height. If ?center is true, the resulting 3D object is centered around the XY plane, rather than resting on top of it. Roundovers described by caps are taken into account such that the final shape conforms to the specified height. If height is less than the combined height of caps, there will simply be no "mid-section" (and the resulting height will not reflect the height parameter).

  • ?twist rotates the shape by the specified angle as it is extruded upwards
  • ?slices specifies the number of intermediate points along the Z axis of the extrusion. By default this increases with the value of ?twist, though manual refinement my improve results.
  • ?scale expands or contracts the shape in X and Y as it is extruded upward. Default is (v2 1. 1.), no scaling.
  • Scaling/twisting proceed linearly by default, though bezier easing can be specified by providing handle points to the scale_ez and twist_ez parameter respectively. (see Path3.scaler and Path3.twister).
val revolve : ?style:style -> ?check_valid:[ `No | `Quality of int ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?fn:int -> ?fa:float -> ?fs:float -> ?skew:V2.t -> ?angle:float -> Poly2.t -> t

revolve ?angle ?skew poly

Revolve a 2d polygon (defined within the X+ half-plane) around the z-axis. An angle between 0 and can be provided to specify an incomplete revolution, by default the result loops back onto itself.

  • skew:{x; y} skews the revolved mesh in the xz and yz planes
val path_extrude : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?caps:Cap.t -> ?euler:bool -> ?scale_ez:(V2.t * V2.t) -> ?twist_ez:(V2.t * V2.t) -> ?scale:V2.t -> ?twist:float -> path:Path3.t -> Poly2.t -> t

path_extrude ?check_valid ?style ?merge ?winding ?caps ?euler ?scale_ez ?twist_ez ?scale ?twist ~path poly

Extrude a 2d polygon along the given path into a 3d mesh. This is a convenience function that composes transform generation using Path3.to_transforms with sweep.

val helix_extrude : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?fn:int -> ?fa:float -> ?fs:float -> ?scale_ez:(V2.t * V2.t) -> ?twist_ez:(V2.t * V2.t) -> ?scale:V2.t -> ?twist:float -> ?caps:[ `Caps of Cap.caps ] -> ?left:bool -> n_turns:int -> pitch:float -> ?r2:float -> float -> Poly2.t -> t

helix_extrude ?check_valid ?style ?merge ?fn ?fs ?fa ?scale_ez ?twist_ez ?scale ?twist ?caps ?left ~n_turns ~pitch ?r2 r1 poly

Helical extrusion of a 2d polygon into a 3d mesh. This is a special case of path_extrude, but following a path generated with Path3.helix, and using transforms that take the helical rotation into account.

Morphing sweeps and extrusions

These functions serve as the morphing counterparts of the fixed polygon sweeping functions above. In contrast to the more general skin which transitions between 3d Path3.t profiles in sequence, these restrict the bounding shapes to 2d, and lift to 3d via the provided transforms, or path specifications. This separation of the morphing transition and spatial transformations allows for the easy addition of non-linear Easing between the shapes via the ?ez parameters (default is linear transition along the spatial distance covered by the sweep beginning from its origin).

val morphing_sweep : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?caps:[ `Caps of Cap.caps ] -> ?outer_map:mapping -> ?hole_map:[ `Same | `Flat of mapping | `Mix of mapping list ] -> ?refine:int -> ?ez:(V2.t * V2.t) -> transforms:Affine3.t list -> Poly2.t -> Poly2.t -> t

morphing_sweep ~transforms a b

Morph between the polygons a and b while sweeping the hybrids along transforms to create a mesh. The outer_map, hole_map, and refine correspond to the the similarly named parameters of the more general skin, while the optional ez parameter allows the transition to be bezier eased via Easing.make, rather than strictly linearly. See sweep for details on the remaining common parameters.

val morph : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?fa:float -> ?slices:int -> ?scale_ez:(V2.t * V2.t) -> ?twist_ez:(V2.t * V2.t) -> ?scale:V2.t -> ?twist:float -> ?center:bool -> ?caps:[ `Caps of Cap.caps ] -> ?outer_map:mapping -> ?hole_map:[ `Flat of mapping | `Mix of mapping list | `Same ] -> ?refine:int -> ?ez:(V2.t * V2.t) -> height:float -> Poly2.t -> Poly2.t -> t

morph ~height a b

Vertically morph between the 2d polygons a and b. This function is to morphing_sweep, as extrude is to sweep. See each of the former for details on their common parameters.

val path_morph : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?winding:[ `CCW | `CW | `NoCheck ] -> ?caps:[ `Caps of Cap.caps ] -> ?outer_map:mapping -> ?hole_map:[ `Flat of mapping | `Mix of mapping list | `Same ] -> ?refine:int -> ?ez:(V2.t * V2.t) -> ?euler:bool -> ?scale_ez:(V2.t * V2.t) -> ?twist_ez:(V2.t * V2.t) -> ?scale:V2.t -> ?twist:float -> path:Path3.t -> Poly2.t -> Poly2.t -> t

path_morph ~path poly

Morph between the 2d polygons a and b along the given path. This is a convenience function that composes transform generation using Path3.to_transforms with morphing_sweep.

val helix_morph : ?style:style -> ?check_valid:[ `Quality of int | `No ] -> ?merge:bool -> ?fn:int -> ?fa:float -> ?fs:float -> ?scale_ez:(V2.t * V2.t) -> ?twist_ez:(V2.t * V2.t) -> ?scale:V2.t -> ?twist:float -> ?caps:[ `Caps of Cap.caps ] -> ?outer_map:mapping -> ?hole_map:[ `Flat of mapping | `Mix of mapping list | `Same ] -> ?refine:int -> ?ez:(V2.t * V2.t) -> ?left:bool -> n_turns:int -> pitch:float -> ?r2:float -> float -> Poly2.t -> Poly2.t -> t

helix_morph ~n_turns ~pitch ?r2 r1 a b

Morph between the 2d polygons a and b along a helical path. This is a special case of path_morph, but following a path generated with Path3.helix, and using transforms that take the helical rotation into account.

Generalized prisms with continous rounding

module Prism : sig ... end

Rounded prism configuration module.

val prism : ?debug:bool -> ?fn:int -> ?holes:Prism.holes -> ?outer:Prism.spec -> Poly3.t -> Poly3.t -> t

prism ?debug ?fn ?holes ?outer bottom top

Create a prism with continuous curvature rounding from the given bottom and top polygons. The edges running between the corresponding paths must produce a valid polyhedron with coplanar side faces, thus the top should generally be the same shape as the bottom translated/transformed in such a way as to not violate this assumption (avoid z-rotation for one). Roundover specifications are provided with outer and holes (see Prism.spec and Prism.holes for details).

  • debug can be set to true to skip validity checks that would otherwise raise exceptions on failure, so a mesh can still be obtained for inspection.
val linear_prism : ?debug:bool -> ?fn:int -> ?holes:Prism.holes -> ?outer:Prism.spec -> ?center:bool -> height:float -> Poly2.t -> t

linear_prism ?debug ?fn ?holes ?outer ?center ~height bottom

Create a prism with continuous curvature rounding by extruding the polygon bottom linearaly upward to the given height. If center is true, the resulting prism will be centred in z around the xy plane. See the more general case prism for more details.

Function Plotting

Ported from the PlotFunction library by Ryan Colyer.

val cartesian_plot : min_x:float -> x_steps:int -> max_x:float -> min_y:float -> y_steps:int -> max_y:float -> (x:float -> y:float -> float) -> t

cartesian_plot ~min_x ~x_steps ~max_x ~min_y ~y_steps ~max_y f

Create a mesh of the function f (from x and y to z) over the ranges of x and y defined by the rest of the parameters.

val polar_plot : ?r_step:float -> max_r:float -> (r:float -> a:float -> float) -> t

polar_plot ?r_step ~max_r f

Create a mesh of the function f (from radius and angle to z) between the z-axis and the radius max_r, with the minimum radial step r_step.

val axial_plot : ?fn:int -> min_z:float -> z_steps:int -> max_z:float -> (z:float -> a:float -> float) -> t

axial_plot ?fn ~min_z ~z_step ~max_z f

Create a mesh of the function f (from z-height and angle to radius). fn sets the number of angular steps around the z-axis.

Mesh Utilities

val join : t list -> t

join ts

Join a list of meshes. This is not a boolean operation, it is simply collecting the points from each and updating face indices accordingly. Intended for use when building a closed mesh from a set of partial meshes.

val merge_points : ?eps:float -> t -> t

merge_points ?eps t

Eliminate duplicate points (less than eps distance apart) from t.

val drop_unused_points : t -> t

drop_unused_points t

Drop unreferenced points (not included in any face) from the mesh t.

val of_polyhedron : ?eps:float -> V3.t list -> int list list -> t

of_polyhedron ?eps points faces

Triangulate the faces of the polygonal mesh described by points and faces. Some degree of non-coplanarity in the input faces can be fine, though too much can cause triangulation to fail. If provided, eps is used for duplicate point and collinearity checks.

val rev_faces : t -> t

rev_faces t

Flip all faces of the mesh t.

val volume : t -> float

volume t

Calculate the volume of the mesh t.

val area : t -> float

area t

Calculate the surface area of the mesh t.

val centroid : ?eps:float -> t -> V3.t

centroid ?eps t

Calculate the centroid of the mesh t.

Basic Transfomations

val translate : V3.t -> t -> t
val xtrans : float -> t -> t
val ytrans : float -> t -> t
val ztrans : float -> t -> t
val rotate : ?about:V3.t -> V3.t -> t -> t
val xrot : ?about:V3.t -> float -> t -> t
val yrot : ?about:V3.t -> float -> t -> t
val zrot : ?about:V3.t -> float -> t -> t
val quaternion : ?about:V3.t -> Quaternion.t -> t -> t
val axis_rotate : ?about:V3.t -> V3.t -> float -> t -> t
val affine : Affine3.t -> t -> t
val scale : V3.t -> t -> t
val xscale : float -> t -> t
val yscale : float -> t -> t
val zscale : float -> t -> t
val mirror : V3.t -> t -> t

IO

val to_stl : ?ascii:bool -> ?rev:bool -> string -> t -> unit

to_stl ?ascii ?rev path t

Write the mesh t to disk at path as an stl. Binary serialization is performed by default, but the ascii format is also available.

  • As OCADml meshes (t) are typically generated to follow the CCW inner face convention of OpenSCAD, this can result in normals pointing the opposite direction expected by other programs with which you may want to use the output stl. Thus facets are reversed by default during serialization, however this can be avoided by setting ~rev:false.
val of_stl : ?rev:bool -> ?eps:float -> string -> t

of_stl ?rev ?eps path Load a mesh from the stl file at path (both binary and ascii encodings are supported).

  • eps can be provided to control the precision of point de-duplication/merge operation performed after loading (default is 1e-6)
  • facets are reversed by default during deserialization to counter the default reversal performed by to_stl, however this can be avoided by setting ~rev:false.