OpenSCAD-0.3.0.0: ADT wrapper and renderer for OpenSCAD models.

Copyright© Mike Meyer, 2014
LicenseBSD4
Maintainermwm@mired.org
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.OpenSCAD

Contents

Description

Overview

The Graphics.OpenSCAD module provides abstract data types for creating OpenSCAD model definitions calls, along with a function to render it as a string, and some utilities. The primary goal is that the output should always be valid OpenSCAD. If you manage to generate OpenSCAD source that causes OpenSCAD to complain, please open an issue.

The primary affect of this is that Graphics.OpenSCAD distinguishes between 2d and 3d Models. If you want to mix them, you must explicitly convert between them. While two-dimensional model creation could be polymorphic functions that create either, so that such models could be treated as either 2d or 3d, you'd still have to explicitly convert models whose type was fixed as 2d by a transformation, and render wouldn't work if the type was still ambiguous, ala render $ square 2.

Usage

Standard usage is to have a main function that looks like:

main = draw $ Solid

or main = drawL $ [Solid]

and then set your IDE's compile command to use runhaskell or equivalent to run your code and send the output to a .scad file. Open that file in OpenSCAD, and set it to automatically reload if the file changes. Recompiling your program will cause the model to be loaded and displayed by OpenSCAD.

The type constructors are not exported, with functions being exported in their stead. This allows extra checking to be done on those that need it. It also provides consistency, as otherwise you'd have to remember whether box is a constructor or a convenience function, etc.

Because of this, the constructors are not documented, the exported functions are. The documentation is generally just the corresponding OpenSCAD function name, along with the names of the arguments from the OpenSCAD documentation. If no OpenSCAD function name is given, then it's the same as the OpenSCAD function. You should check the OpenSCAD documentation for usage information.

Oddities

importFile has been left polymorphic. I couldn't find a sane way to check that you're importing the right file type, so detecting such errors - including importing a 3d file and trying to extrude it - have to be left up to OpenSCAD in any case. So for now, there's just importFile. This does create the oddity that if you import a file and try and render it without doing something to indicate how many dimensions it has (one of the transformations, an extrusion or projection, or solid) you'll get a compile error because the type is ambiguous. Later, this may turn into import2d and import3d.

The interfaces for polygons and polyhedrons is seriously different from the OpenSCAD interface. Rather than expecting you to enter a list of points and then references to them, you just enter the points directly. If you really want to do it the OpenSCAD way, you can do something like:

draw $ polyhedron [[(p 0, p 1, p 2), (p 0, p 2, p 3), ... ]]
where points = [.....]
      p i = points !! i

Also, the OpenSCAD polyedron code recently changed. The old version requires that the faces all be triangles, the new version allows for them to be arbitrary polygons. OpenSCAD supports both: if all your faces are triangles, it will use the old version. If some have more points, the new version will be used. If any have fewer than three points you get an error. At this time, no tests are done on the faces. That will probably change in the future.

Finally, polygon and polyhedron can generate errors on input that seems to generate proper solids. If you turn on 'View->Thrown Together', you'll see it highlighting errors in the object.

Offset is missing even though it's documented, as it isn't supported by a released version of OpenSCAD, so presumably subject to change. It is implemented, but untested as yet. You can add it to the module's export lists if you want to play with it.

Synopsis

Types

A Model to be rendered, and a Vector that fixes the

data Model v Source

A Model is either a Model2d, a Model3d, a transformation of a Model, a combination of Models, or a Model with it's rendering tweaked by a Facet. Models can be rendered.

Instances

Show v => Show (Model v) 
Vector v => Monoid (Model v) 
Vector v => Semigroup (Model v) 

class Eq a => Vector a Source

Minimal complete definition

rVector, toList, (#*), (#-)

Types aliases with fixed dimensions

type Model2d = Model Vector2d Source

A two-dimensional model. Note that the types do not mix implicitly. You must turn a Model2d into a Model3d using one of linearExtrude, rotateExtrude, or solid.

type Model3d = Model Vector3d Source

A three-dimensional model. You can create a Model2d from a Model3d using projection.

type Vector2d = (Double, Double) Source

Vector2d is used where OpenSCAD expects an OpenSCAD vector of length 2.

type Vector3d = (Double, Double, Double) Source

Vector3d is used where OpenSCAD expects an OpenSCAD vector of length 3.

data Facet Source

A Facet is used to set one of the special variables that control the mesh used during generation of circular objects. They appear as arguments to various constructors, as well as in the var function to set them for the argument objects.

Instances

type TransMatrix = ((Double, Double, Double, Double), (Double, Double, Double, Double), (Double, Double, Double, Double), (Double, Double, Double, Double)) Source

A 4x4 transformation matrix specifying a complete 3-space transform of a Model3d.

Primitive creation

Model2ds

rectangle :: Double -> Double -> Model2d Source

Create a rectangular Model2d with rectangle x-size y-size.

square :: Double -> Model2d Source

square is a rectangle with both sides the same size.

circle :: Double -> Facet -> Model2d Source

Create a circular Model with circle radius Facet.

polygon :: Int -> [[Vector2d]] -> Model2d Source

Turn a list of list of Vector2ds and an int into polygon points path convexity. The argument to polygon is the list of paths that is the second argument to the OpenSCAD polygon function, except the points are Vector2ds, not references to Vector2ds in that functions points argument. If you were just going to pass in the points, it now needs to be in an extra level of List.

projection :: Bool -> Model3d -> Model2d Source

Project a Model3d into a Model with projection cut Model3d.

importFile :: Vector v => FilePath -> Model v Source

importFile is import filename.

Model3ds

sphere :: Double -> Facet -> Model3d Source

Create a sphere with sphere radius Facet.

box :: Double -> Double -> Double -> Model3d Source

Create a box with cube x-size y-size z-size

cube :: Double -> Model3d Source

A convenience function for creating a cube as a box with all sides the same length.

cylinder :: Double -> Double -> Facet -> Model3d Source

Create a cylinder with cylinder radius height Facet.

obCylinder :: Double -> Double -> Double -> Facet -> Model Vector3d Source

Create an oblique cylinder with cylinder radius1 height radius2 Facet.

polyhedron :: Int -> [[Vector3d]] -> Model3d Source

Turn a list of list of Vector3ds and an int into polyhedron points Sides convexity. The argument to polyhedron is the list of paths that is the second argument to the OpenSCAD polyhedron function, except the points are Vector3ds, not the references to Vector3ds used in that functions points argument. The function will build the appropriate function call, using faces if you pass in a side that uses more than 3 points, or triangles if not. Note that faces doesn't work in older versions of OpenSCAD, and triangles is depreciated. Until a mechanism to set the version of OpenSCAD is provided, generating the faces version will cause an error.

Passing in Sides that have fewer than three points, have collinear points or have points that aren't in the same plane is an error that is caught by the library.

linearExtrude Source

Arguments

:: Double

height

-> Double

twist

-> Vector2d

scale

-> Int

slices

-> Int

convexity

-> Facet 
-> Model2d

to extrude

-> Model3d 

Extrude a Model2d along a line with linear_extrude.

rotateExtrude :: Int -> Facet -> Model2d -> Model3d Source

Rotate a Model2d around the origin with rotate_extrude convexity Facet Model

surface :: FilePath -> Bool -> Int -> Model3d Source

Load a height map from a file with surface FilePath Invert Convexity.

solid :: Model2d -> Model3d Source

Turn a Model2d into a Model3d exactly as is.

Functions

Combinations

union :: Vector v => [Model v] -> Model v Source

Create the union of a list of Models.

intersection :: Vector v => [Model v] -> Model v Source

Create the intersection of a list of Models.

difference :: Vector v => Model v -> Model v -> Model v Source

The difference between two Models.

minkowski :: Vector v => [Model v] -> Model v Source

The Minkowski sum of a list of Models.

hull :: Vector v => [Model v] -> Model v Source

The convex hull of a list of Models.

Transformations

scale :: Vector v => v -> Model v -> Model v Source

Scale a Model, the vector specifying the scale factor for each axis.

resize :: Vector v => v -> Model v -> Model v Source

Resize a Model to occupy the dimensions given by the vector. Note that this does nothing prior to the 2014 versions of OpenSCAD.

rotate :: Vector v => v -> Model v -> Model v Source

Rotate a Model by different amounts around each of the three axis.

translate :: Vector v => v -> Model v -> Model v Source

Translate a Model along a Vector.

mirror :: Vector v => v -> Model v -> Model v Source

Mirror a Model across a plane intersecting the origin.

color :: Vector v => Colour Double -> Model v -> Model v Source

Render a Model in a specific color. This doesn't use the OpenSCAD color model, but instead uses the Colour model. The OpenSCAD module rexports Names so you can conveniently say color red Model.

transparent :: Vector v => AlphaColour Double -> Model v -> Model v Source

Render a Model in a transparent color. This uses the AphaColour color model.

up :: Double -> Model3d -> Model3d Source

A translate that just goes up, since those seem to be common.

Rendering

render :: Vector v => Model v -> String Source

render does all the real work. It will walk the AST for a Model, returning an OpenSCAD program in a String.

renderL :: Vector v => [Model v] -> String Source

A convenience function to render a list of Models by taking their union.

Facets.

var :: Facet -> [Model v] -> Model v Source

var uses assign to set a Facet variable for it's Models.

fn :: Int -> Facet Source

fn is used to set the $fn variable in a Facet or var.

fs :: Double -> Facet Source

fs is used to set the $fs variable in a Facet or var.

fa :: Double -> Facet Source

fa is used to set the $fa variable in a Facet or var.

def :: Facet Source

def is used where a Facet is needed but we don't want to change any of the values.

General convenience functions

diam :: Double -> Double Source

Use diam to turn a diameter into a radius for circles, spheres, etc.

draw :: Vector v => Model v -> IO () Source

A convenience function to write the rendered Model to standard output.

drawL :: Vector v => [Model v] -> IO () Source

A convenience function to write a union of Models to standard output.

(#) :: b -> (b -> c) -> c infixl 8 Source

You can use '(#)' to write transformations in a more readable postfix form, cube 3 translate (-3, -3, -3)