Copyright | © Mike Meyer, 2014 |
---|---|
License | BSD4 |
Maintainer | mwm@mired.org |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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 Model
s. 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 polygon
s and polyhedron
s 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.
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.
- data Model v
- class Vector a
- type Model2d = Model Vector2d
- type Model3d = Model Vector3d
- type Vector2d = (Double, Double)
- type Vector3d = (Double, Double, Double)
- data Facet
- type TransMatrix = ((Double, Double, Double, Double), (Double, Double, Double, Double), (Double, Double, Double, Double), (Double, Double, Double, Double))
- rectangle :: Double -> Double -> Model2d
- square :: Double -> Model2d
- circle :: Double -> Facet -> Model2d
- polygon :: Int -> [[Vector2d]] -> Model2d
- projection :: Bool -> Model3d -> Model2d
- importFile :: Vector v => FilePath -> Model v
- sphere :: Double -> Facet -> Model3d
- box :: Double -> Double -> Double -> Model3d
- cube :: Double -> Model3d
- cylinder :: Double -> Double -> Facet -> Model3d
- obCylinder :: Double -> Double -> Double -> Facet -> Model Vector3d
- polyhedron :: Int -> [[Vector3d]] -> Model3d
- multMatrix :: TransMatrix -> Model3d -> Model3d
- linearExtrude :: Double -> Double -> Vector2d -> Int -> Int -> Facet -> Model2d -> Model3d
- rotateExtrude :: Int -> Facet -> Model2d -> Model3d
- surface :: FilePath -> Bool -> Int -> Model3d
- solid :: Model2d -> Model3d
- union :: Vector v => [Model v] -> Model v
- intersection :: Vector v => [Model v] -> Model v
- difference :: Vector v => Model v -> Model v -> Model v
- minkowski :: Vector v => [Model v] -> Model v
- hull :: Vector v => [Model v] -> Model v
- scale :: Vector v => v -> Model v -> Model v
- resize :: Vector v => v -> Model v -> Model v
- rotate :: Vector v => v -> Model v -> Model v
- translate :: Vector v => v -> Model v -> Model v
- mirror :: Vector v => v -> Model v -> Model v
- color :: Vector v => Colour Double -> Model v -> Model v
- transparent :: Vector v => AlphaColour Double -> Model v -> Model v
- up :: Double -> Model3d -> Model3d
- render :: Vector v => Model v -> String
- renderL :: Vector v => [Model v] -> String
- var :: Facet -> [Model v] -> Model v
- fn :: Int -> Facet
- fs :: Double -> Facet
- fa :: Double -> Facet
- def :: Facet
- diam :: Double -> Double
- draw :: Vector v => Model v -> IO ()
- drawL :: Vector v => [Model v] -> IO ()
Types
A Model
to be rendered, and a Vector
that fixes the
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 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
Model2d
s
rectangle :: Double -> Double -> Model2d Source
Create a rectangular Model2d
with rectangle x-size y-size
.
polygon :: Int -> [[Vector2d]] -> Model2d Source
Turn a list of list of Vector2d
s 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 Vector2d
s, not references to Vector2d
s 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
importFile :: Vector v => FilePath -> Model v Source
importFile
is import filename
.
Model3d
s
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 Vector3d
s and an int into polyhedron
points
. The argument to polyhedron is the list
of paths that is the second argument to the OpenSCAD polygon
function, except the points are Sides
convexityVector3d
s, not the references to
Vector3d
s 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, an
triangles
is depreciate. Until a mechanism to set the version of
OpenSCAD is provided, generating the faces
version will cause an
error.
multMatrix :: TransMatrix -> Model3d -> Model3d Source
Transform a Model3d
with a TransMatrix
:: Double | height |
-> Double | twist |
-> Vector2d | scale |
-> Int | slices |
-> Int | convexity |
-> Facet | |
-> Model2d | to extrude |
-> Model3d |
Extrude a Model2d
along a line with linear_extrude
.
surface :: FilePath -> Bool -> Int -> Model3d Source
Load a height map from a file with surface FilePath Invert Convexity
.
Functions
Combinations
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.
mirror :: Vector v => v -> Model v -> Model v Source
Mirror a Model
across a plane intersecting the origin.
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
renderL :: Vector v => [Model v] -> String Source
A convenience function to render a list of Model
s by taking
their union.