Replace the Rect primtives with SquareR and CubeR

As discussed in #295.

Fixes #295.
This commit is contained in:
Sandy Maguire 2020-11-19 22:33:59 -08:00
parent 5ddd75006c
commit 7538239a17
10 changed files with 59 additions and 43 deletions

View File

@ -31,6 +31,7 @@ module Graphics.Implicit (
P.difference,
-- * 2D primitive shapes
P.squareR,
P.rectR,
P.circle,
P.polygonR,
@ -40,6 +41,7 @@ module Graphics.Implicit (
P.pack2,
-- * 3D primitive shapes
P.cubeR,
P.rect3R,
P.sphere,
P.cylinder,
@ -79,7 +81,7 @@ import Prelude(FilePath, IO)
-- The primitive objects, and functions for manipulating them.
-- MAYBEFIXME: impliment slice operation, regularPolygon and zsurface primitives.
import Graphics.Implicit.Primitives as P (translate, scale, complement, union, intersect, difference, unionR, intersectR, differenceR, shell, extrudeR, extrudeRM, extrudeOnEdgeOf, sphere, rect3R, circle, cylinder, cylinder2, rectR, polygonR, rotateExtrude, rotate3, rotate3V, pack3, rotate, pack2, implicit, Object)
import Graphics.Implicit.Primitives as P (cubeR, squareR, translate, scale, complement, union, intersect, difference, unionR, intersectR, differenceR, shell, extrudeR, extrudeRM, extrudeOnEdgeOf, sphere, rect3R, circle, cylinder, cylinder2, rectR, polygonR, rotateExtrude, rotate3, rotate3V, pack3, rotate, pack2, implicit, Object)
-- The Extended OpenScad interpreter.
import Graphics.Implicit.ExtOpenScad as E (runOpenscad)

View File

@ -37,7 +37,7 @@ module Graphics.Implicit.Definitions (
BoxedObj2,
BoxedObj3,
SymbolicObj2(
RectR,
SquareR,
Circle,
PolygonR,
Complement2,
@ -51,7 +51,7 @@ module Graphics.Implicit.Definitions (
Outset2,
EmbedBoxedObj2),
SymbolicObj3(
Rect3R,
CubeR,
Sphere,
Cylinder,
Complement3,
@ -247,7 +247,7 @@ type BoxedObj3 = Boxed3 Obj3
-- cases.
data SymbolicObj2 =
-- Primitives
RectR 2 2 -- rounding, start, stop.
SquareR 2 -- rounding, size.
| Circle -- radius.
| PolygonR [2] -- rounding, points.
-- (Rounded) CSG
@ -269,7 +269,7 @@ data SymbolicObj2 =
-- | A symbolic 3D format!
data SymbolicObj3 =
-- Primitives
Rect3R 3 3 -- rounding, start, stop.
CubeR 3 -- rounding, size.
| Sphere -- radius
| Cylinder --
-- (Rounded) CSG

View File

@ -10,7 +10,7 @@ module Graphics.Implicit.Export.SymbolicFormats (scad2, scad3) where
import Prelude(Either(Left, Right), ($), (*), ($!), (-), (/), pi, error, (+), (==), take, floor, (&&), const, pure, (<>), sequenceA, (<$>))
import Graphics.Implicit.Definitions(, SymbolicObj2(RectR, Circle, PolygonR, Complement2, UnionR2, DifferenceR2, IntersectR2, Translate2, Scale2, Rotate2, Outset2, Shell2, EmbedBoxedObj2), SymbolicObj3(Rect3R, Sphere, Cylinder, Complement3, UnionR3, IntersectR3, DifferenceR3, Translate3, Scale3, Rotate3, Rotate3V, Outset3, Shell3, ExtrudeR, ExtrudeRotateR, ExtrudeRM, EmbedBoxedObj3, RotateExtrude, ExtrudeOnEdgeOf), isScaleID)
import Graphics.Implicit.Definitions(, SymbolicObj2(SquareR, Circle, PolygonR, Complement2, UnionR2, DifferenceR2, IntersectR2, Translate2, Scale2, Rotate2, Outset2, Shell2, EmbedBoxedObj2), SymbolicObj3(CubeR, Sphere, Cylinder, Complement3, UnionR3, IntersectR3, DifferenceR3, Translate3, Scale3, Rotate3, Rotate3V, Outset3, Shell3, ExtrudeR, ExtrudeRotateR, ExtrudeRM, EmbedBoxedObj3, RotateExtrude, ExtrudeOnEdgeOf), isScaleID)
import Graphics.Implicit.Export.TextBuilderUtils(Text, Builder, toLazyText, fromLazyText, bf)
import Control.Monad.Reader (Reader, runReader, ask)
@ -52,9 +52,7 @@ callNaked = callToken ("", "")
-- | First, the 3D objects.
buildS3 :: SymbolicObj3 -> Reader Builder
buildS3 (Rect3R r (x1,y1,z1) (x2,y2,z2)) | r == 0 = call "translate" [bf x1, bf y1, bf z1] [
call "cube" [bf $ x2 - x1, bf $ y2 - y1, bf $ z2 - z1] []
]
buildS3 (CubeR r (w,d,h)) | r == 0 = call "cube" [bf w, bf d, bf h] []
buildS3 (Sphere r) = callNaked "sphere" ["r = " <> bf r] []
@ -109,7 +107,7 @@ buildS3 (ExtrudeRM r twist scale (Left translate) obj (Left height)) | r == 0 &&
-- FIXME: where are RotateExtrude, ExtrudeOnEdgeOf?
buildS3 Rect3R{} = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS3 CubeR{} = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS3(UnionR3 _ _) = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS3(IntersectR3 _ _) = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS3(DifferenceR3 _ _) = error "cannot provide roundness when exporting openscad; unsupported in target format."
@ -126,9 +124,7 @@ buildS3(ExtrudeOnEdgeOf _ _) = error "cannot provide roundness when exporting op
buildS2 :: SymbolicObj2 -> Reader Builder
buildS2 (RectR r (x1,y1) (x2,y2)) | r == 0 = call "translate" [bf x1, bf y1] [
call "cube" [bf $ x2 - x1, bf $ y2 - y1] []
]
buildS2 (SquareR r (w,h)) | r == 0 = call "cube" [bf w, bf h] []
buildS2 (Circle r) = call "circle" [bf r] []
@ -154,7 +150,7 @@ buildS2 (Outset2 r obj) | r == 0 = call "outset" [] [buildS2 obj]
buildS2 (Shell2 r obj) | r == 0 = call "shell" [] [buildS2 obj]
-- Generate errors for rounding requests. OpenSCAD does not support rounding.
buildS2 RectR{} = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS2 SquareR{} = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS2 (PolygonR _ _) = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS2 (UnionR2 _ _) = error "cannot provide roundness when exporting openscad; unsupported in target format."
buildS2 (DifferenceR2 _ _) = error "cannot provide roundness when exporting openscad; unsupported in target format."

View File

@ -10,7 +10,7 @@ module Graphics.Implicit.Export.SymbolicObj2 (symbolicGetOrientedContour, symbol
import Prelude(fmap, ($), (-), (/), (+), (>), (*), reverse, cos, pi, sin, max, ceiling, (<$>))
import Graphics.Implicit.Definitions (, 2, Fast, SymbolicObj2(RectR, Circle, Translate2, Scale2), Polyline(Polyline), Polytri(Polytri), (*), fromFastto)
import Graphics.Implicit.Definitions (, 2, Fast, SymbolicObj2(SquareR, Circle, Translate2, Scale2), Polyline(Polyline), Polytri(Polytri), (*), fromFastto)
import Graphics.Implicit.Export.MarchingSquaresFill (getContourMesh)
@ -39,7 +39,7 @@ symbolicGetOrientedContour res symbObj = orient <$> symbolicGetContour res symbO
orient (Polyline [_]) = Polyline []
symbolicGetContour :: -> SymbolicObj2 -> [Polyline]
symbolicGetContour _ (RectR 0 (x1,y1) (x2,y2)) = [Polyline [ (x1,y1), (x2,y1), (x2,y2), (x1,y2), (x1,y1) ]]
symbolicGetContour _ (SquareR 0 (dx,dy)) = [Polyline [ (0,0), (dx,0), (dx,dy), (0,dy), (0,0) ]]
-- FIXME: magic number.
symbolicGetContour res (Circle r) = [Polyline [ ( r*cos(2*pi*fromFastto m/fromFastto n), r*sin(2*pi*fromFastto m/fromFastto n) ) | m <- [0.. n] ]] where
n :: Fast
@ -60,7 +60,7 @@ symbolicGetContourMesh res (Translate2 v obj) = (\(Polytri (a,b,c)) -> Polytri (
symbolicGetContourMesh res obj
symbolicGetContourMesh res (Scale2 s@(a,b) obj) = (\(Polytri (c,d,e)) -> Polytri (c * s, d * s, e * s)) <$>
symbolicGetContourMesh (res/sc) obj where sc = max a b
symbolicGetContourMesh _ (RectR 0 (x1,y1) (x2,y2)) = [Polytri ((x1,y1), (x2,y1), (x2,y2)), Polytri ((x2,y2), (x1,y2), (x1,y1)) ]
symbolicGetContourMesh _ (SquareR 0 (dx,dy)) = [Polytri ((0,0), (dx,0), (dx,dy)), Polytri ((dx,dy), (0,dy), (0,0)) ]
-- FIXME: magic number.
symbolicGetContourMesh res (Circle r) =
[ Polytri ((0,0),

View File

@ -7,7 +7,7 @@ module Graphics.Implicit.ObjectUtil.GetBox2 (getBox2, getBox2R) where
import Prelude(Bool, Fractional, Eq, (==), (||), unzip, minimum, maximum, ($), filter, not, (.), (/), fmap, (-), (+), (*), cos, sin, sqrt, min, max, head, (<), (<>), pi, atan2, (==), (>), show, (&&), otherwise, error)
import Graphics.Implicit.Definitions (, 2, Box2, (*),
SymbolicObj2(Shell2, Outset2, Circle, Translate2, Rotate2, UnionR2, Scale2, RectR,
SymbolicObj2(Shell2, Outset2, Circle, Translate2, Rotate2, UnionR2, Scale2, SquareR,
PolygonR, Complement2, DifferenceR2, IntersectR2, EmbedBoxedObj2), min)
import Data.VectorSpace ((^-^), (^+^))
@ -65,7 +65,7 @@ outsetBox r (a,b) =
-- Get a Box2 around the given object.
getBox2 :: SymbolicObj2 -> Box2
-- Primitives
getBox2 (RectR _ a b) = (a,b)
getBox2 (SquareR _ size) = ((0, 0), size)
getBox2 (Circle r) = ((-r, -r), (r,r))
getBox2 (PolygonR _ points) = pointsBox points
-- (Rounded) CSG
@ -113,7 +113,7 @@ getBox2 (Outset2 d symbObj) =
getBox2 (EmbedBoxedObj2 (_,box)) = box
-- | Define a Box2 around the given object, and the space it occupies while rotating about the center point.
-- Note: No implementations for RectR, Translate2, or Scale2 as they would be identical to the fallthrough.
-- Note: No implementations for SquareR, Translate2, or Scale2 as they would be identical to the fallthrough.
getBox2R :: SymbolicObj2 -> -> Box2
getBox2R (Circle r) _ = getBox2 $ Circle r
getBox2R (PolygonR _ points) deg =

View File

@ -7,7 +7,7 @@ module Graphics.Implicit.ObjectUtil.GetBox3 (getBox3) where
import Prelude(Eq, Bool(False), Fractional, Either (Left, Right), (==), (||), max, (/), (-), (+), fmap, unzip, ($), (<$>), filter, not, (.), unzip3, minimum, maximum, min, (>), (&&), head, (*), (<), abs, either, error, const, otherwise, take, fst, snd)
import Graphics.Implicit.Definitions (, Fast, Box3, SymbolicObj3 (Rect3R, Sphere, Cylinder, Complement3, UnionR3, IntersectR3, DifferenceR3, Translate3, Scale3, Rotate3, Rotate3V, Shell3, Outset3, EmbedBoxedObj3, ExtrudeR, ExtrudeOnEdgeOf, ExtrudeRM, RotateExtrude, ExtrudeRotateR), SymbolicObj2 (Rotate2, RectR), ExtrudeRMScale(C1, C2), (*), fromFastto, fromFast, toScaleFn)
import Graphics.Implicit.Definitions (, Fast, Box3, SymbolicObj3 (CubeR, Sphere, Cylinder, Complement3, UnionR3, IntersectR3, DifferenceR3, Translate3, Scale3, Rotate3, Rotate3V, Shell3, Outset3, EmbedBoxedObj3, ExtrudeR, ExtrudeOnEdgeOf, ExtrudeRM, RotateExtrude, ExtrudeRotateR), SymbolicObj2 (Translate2, Rotate2, SquareR), ExtrudeRMScale(C1, C2), (*), fromFastto, fromFast, toScaleFn)
import Graphics.Implicit.ObjectUtil.GetBox2 (getBox2, getBox2R)
@ -33,7 +33,7 @@ outsetBox r (a,b) =
-- Get a Box3 around the given object.
getBox3 :: SymbolicObj3 -> Box3
-- Primitives
getBox3 (Rect3R _ a b) = (a,b)
getBox3 (CubeR _ size) = ((0, 0, 0), size)
getBox3 (Sphere r) = ((-r, -r, -r), (r,r,r))
getBox3 (Cylinder h r1 r2) = ( (-r,-r,0), (r,r,h) ) where r = max r1 r2
-- (Rounded) CSG
@ -89,7 +89,7 @@ getBox3 (Scale3 s symbObj) =
getBox3 (Rotate3 (a, b, c) symbObj) =
let
((x1, y1, z1), (x2, y2, z2)) = getBox3 symbObj
rotate v1 w1 v2 w2 angle = getBox2(Rotate2 angle $ RectR 0 (v1, w1) (v2, w2))
rotate v1 w1 v2 w2 angle = getBox2(Rotate2 angle $ Translate2 (v2, w1) $ SquareR 0 (v2-v1, w2-w1))
((y1', z1'), (y2', z2')) = rotate y1 z1 y2 z2 a
((z1'', x1'), (z2'', x2')) = rotate z1' x1 z2' x2 b
((x1'', y1''), (x2'', y2'')) = rotate x1' y1' x2' y2' c

View File

@ -6,7 +6,7 @@ module Graphics.Implicit.ObjectUtil.GetImplicit2 (getImplicit2) where
import Prelude(abs, (-), (/), sqrt, (*), (+), mod, length, fmap, (<=), (&&), (>=), (||), odd, ($), (>), filter, (<), minimum, max, cos, sin, head, tail, (.))
import Graphics.Implicit.Definitions (, , 2, (/), Obj2, SymbolicObj2(RectR, Circle, PolygonR, Complement2, UnionR2, DifferenceR2, IntersectR2, Translate2, Scale2, Rotate2, Shell2, Outset2, EmbedBoxedObj2))
import Graphics.Implicit.Definitions (, , 2, (/), Obj2, SymbolicObj2(SquareR, Circle, PolygonR, Complement2, UnionR2, DifferenceR2, IntersectR2, Translate2, Scale2, Rotate2, Shell2, Outset2, EmbedBoxedObj2))
import Graphics.Implicit.MathUtil (rminimum, rmaximum, distFromLineSeg)
@ -15,11 +15,10 @@ import Data.List (nub, genericIndex, genericLength)
getImplicit2 :: SymbolicObj2 -> Obj2
-- Primitives
getImplicit2 (RectR r (x1,y1) (x2,y2)) =
getImplicit2 (SquareR r (dx, dy)) =
\(x,y) -> let
(dx, dy) = (x2-x1, y2-y1)
in
rmaximum r [abs (x-dx/2-x1) - dx/2, abs (y-dy/2-y1) - dy/2]
rmaximum r [abs (x-dx/2) - dx/2, abs (y-dy/2) - dy/2]
getImplicit2 (Circle r) =
\(x,y) -> sqrt (x * x + y * y) - r
-- FIXME: stop ignoring rounding for polygons.

View File

@ -9,7 +9,7 @@ import Prelude (Either(Left, Right), abs, (-), (/), (*), sqrt, (+), atan2, max,
import Graphics.Implicit.Definitions (, , 2, 3, (/), Obj3,
SymbolicObj3(Shell3, UnionR3, IntersectR3, DifferenceR3, Translate3, Scale3, Rotate3,
Outset3, Rect3R, Sphere, Cylinder, Complement3, EmbedBoxedObj3, Rotate3V,
Outset3, CubeR, Sphere, Cylinder, Complement3, EmbedBoxedObj3, Rotate3V,
ExtrudeR, ExtrudeRM, ExtrudeOnEdgeOf, RotateExtrude, ExtrudeRotateR), fromto, toScaleFn, (), min)
import Graphics.Implicit.MathUtil (rmaximum, rminimum, rmax)
@ -30,10 +30,8 @@ default ()
-- Get a function that describes the surface of the object.
getImplicit3 :: SymbolicObj3 -> Obj3
-- Primitives
getImplicit3 (Rect3R r (x1,y1,z1) (x2,y2,z2)) =
\(x,y,z) -> let (dx, dy, dz) = (x2-x1, y2-y1, z2-z1)
in
rmaximum r [abs (x-dx/2-x1) - dx/2, abs (y-dy/2-y1) - dy/2, abs (z-dz/2-z1) - dz/2]
getImplicit3 (CubeR r (dx, dy, dz)) =
\(x,y,z) -> rmaximum r [abs (x-dx/2) - dx/2, abs (y-dy/2) - dy/2, abs (z-dz/2) - dz/2]
getImplicit3 (Sphere r) =
\(x,y,z) -> sqrt (x*x + y*y + z*z) - r
getImplicit3 (Cylinder h r1 r2) = \(x,y,z) ->

View File

@ -21,11 +21,11 @@ module Graphics.Implicit.Primitives (
extrudeRotateR,
extrudeOnEdgeOf,
sphere,
rect3R,
cubeR, rect3R,
circle,
cylinder,
cylinder2,
rectR,
squareR, rectR,
polygonR,
rotateExtrude,
rotate3,
@ -37,11 +37,11 @@ module Graphics.Implicit.Primitives (
Object
) where
import Prelude(Maybe(Just, Nothing), Either, fmap, ($))
import Prelude((/), (.), negate, Bool(True, False), Maybe(Just, Nothing), Either, fmap, ($))
import Graphics.Implicit.Definitions (, 2, 3, Box2,
import Graphics.Implicit.Definitions (both, allthree, , 2, 3, Box2,
SymbolicObj2(
RectR,
SquareR,
Circle,
PolygonR,
Complement2,
@ -56,7 +56,7 @@ import Graphics.Implicit.Definitions (, 2, 3, Box2,
EmbedBoxedObj2
),
SymbolicObj3(
Rect3R,
CubeR,
Sphere,
Cylinder,
Complement3,
@ -80,6 +80,7 @@ import Graphics.Implicit.Definitions (, 2, 3, Box2,
)
import Graphics.Implicit.MathUtil (pack)
import Graphics.Implicit.ObjectUtil (getBox2, getBox3, getImplicit2, getImplicit3)
import Data.VectorSpace (AdditiveGroup((^-^)))
-- $ 3D Primitives
@ -94,9 +95,20 @@ rect3R ::
-- ^ Rounding of corners
-> 3 -- ^ Bottom.. corner
-> 3 -- ^ Top right... corner
-> SymbolicObj3 -- ^ Resuting cube - (0,0,0) is bottom left...
-> SymbolicObj3 -- ^ Resuting cube
rect3R r xyz1 xyz2 = translate xyz1 $ CubeR r (xyz2 ^-^ xyz1)
-- | A rectangular prism, with rounded corners.
cubeR ::
-- ^ Rounding of corners
-> Bool -- ^ Centered?
-> 3 -- ^ Size
-> SymbolicObj3 -- ^ Resuting cube. (0,0,0) is bottom left if @center = False@,
-- otherwise it's the center.
cubeR r False size = CubeR r size
cubeR r True size = translate (allthree (negate . (/ 2)) $ size) $ CubeR r size
rect3R = Rect3R
-- | A conical frustum --- ie. a cylinder with different radii at either end.
cylinder2 ::
@ -127,9 +139,18 @@ rectR ::
-- ^ Rounding radius (in mm) of corners
-> 2 -- ^ Bottom left corner
-> 2 -- ^ Top right corner
-> SymbolicObj2 -- ^ Resulting square (bottom right = (0,0) )
-> SymbolicObj2 -- ^ Resulting square
rectR = RectR
rectR r xy1 xy2 = translate xy1 $ SquareR r (xy2 ^-^ xy1)
-- | A rectangle, with rounded corners.
squareR ::
-- ^ Rounding radius (in mm) of corners
-> Bool -- ^ Centered?
-> 2 -- ^ Size
-> SymbolicObj2 -- ^ Resulting square (bottom right = (0,0) )
squareR r False size = SquareR r size
squareR r True size = translate (both (negate . (/ 2)) $ size) $ SquareR r size
-- | A 2D polygon, with rounded corners.
polygonR ::

View File

@ -151,7 +151,7 @@ and put it in `Graphics.Implicit.Primitives`. However, to allow more powerful op
```haskell
data SymbolicObj3 =
Rect3R 3 3
CubeR 3 3
| Sphere
...
```