Skip to content

Commit

Permalink
Merge remote-tracking branch 'upstream/master' into more-primitives
Browse files Browse the repository at this point in the history
  • Loading branch information
lepsa committed Jan 4, 2024
2 parents 0e4606b + eacfe58 commit 9cd6c5e
Show file tree
Hide file tree
Showing 8 changed files with 388 additions and 432 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
* Other changes
* Fixing `shell` so that it doesn't increase the outside dimentions of objects.
* Fixing an issue with bounding boxes for infinite functions. [#412](https://github.com/Haskell-Things/ImplicitCAD/issues/412)
* Making `torus` and `ellipsoid` primitive objects, rather than being defined implicitly. [#450](https://github.com/Haskell-Things/ImplicitCAD/issues/450)

# Version [0.4.1.0](https://github.com/Haskell-Things/ImplicitCAD/compare/v0.4.0.0...v0.4.1.0) (2023-12-18)

Expand Down
10 changes: 10 additions & 0 deletions Graphics/Implicit/Canon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,8 @@ import Graphics.Implicit.Definitions
, Transform3
, BoxFrame
, Link
, Torus
, Ellipsoid
)
, hasZeroComponent
)
Expand Down Expand Up @@ -175,6 +177,8 @@ fmapObj3 f _ _ (Sphere r) = f $ Sphere r
fmapObj3 f _ _ (Cylinder r1 r2 h) = f $ Cylinder r1 r2 h
fmapObj3 f _ _ (BoxFrame b e) = f $ BoxFrame b e
fmapObj3 f _ _ (Link le r1 r2) = f $ Link le r1 r2
fmapObj3 f _ _ (Torus r1 r2) = f $ Torus r1 r2
fmapObj3 f _ _ (Ellipsoid a b c) = f $ Ellipsoid a b c
fmapObj3 f g s (Rotate3 q o) = f $ Rotate3 q (fmapObj3 f g s o)
fmapObj3 f g s (Transform3 m o) = f $ Transform3 m (fmapObj3 f g s o)
fmapObj3 f g s (Extrude o2 h) = f $ Extrude (fmapObj2 g f s o2) h
Expand Down Expand Up @@ -229,6 +233,8 @@ instance EqObj SymbolicObj2 where
instance EqObj SymbolicObj3 where
Cube a =^= Cube b = a == b
Sphere a =^= Sphere b = a == b
Torus a1 a2 =^= Torus b1 b2 = a1 == b1 && a2 == b2
Ellipsoid a1 b1 c1 =^= Ellipsoid a2 b2 c2 = a1 == a2 && b1 == b2 && c1 == c2
Cylinder r1a r2a ha =^= Cylinder r1b r2b hb = r1a == r1b && r2a == r2b && ha == hb
BoxFrame b1 e1 =^= BoxFrame b2 e2 = b1 == b2 && e1 == e2
Link a1 b1 c1 =^= Link a2 b2 c2 = a1 == a2 && b1 == b2 && c1 == c2
Expand Down Expand Up @@ -307,6 +313,10 @@ canon3 (Sphere 0) = emptySpace
canon3 (Cylinder 0 _ _) = emptySpace
canon3 (BoxFrame _ 0) = emptySpace
canon3 (Extrude _o2 0) = emptySpace
canon3 (Torus _ 0) = emptySpace
canon3 (Ellipsoid 0 _ _) = emptySpace
canon3 (Ellipsoid _ 0 _) = emptySpace
canon3 (Ellipsoid _ _ 0) = emptySpace
canon3 (Rotate3 0 o) = o
canon3 (RotateExtrude 0 _t _r _o) = emptySpace
canon3 (RotateExtrude _theta _t _r (Shared Empty)) = emptySpace
Expand Down
6 changes: 6 additions & 0 deletions Graphics/Implicit/Definitions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,8 @@ module Graphics.Implicit.Definitions (
Transform3,
BoxFrame,
Link,
Torus,
Ellipsoid,
Extrude,
ExtrudeM,
ExtrudeOnEdgeOf,
Expand Down Expand Up @@ -328,6 +330,8 @@ data SymbolicObj3 =
| Cylinder --
| BoxFrame ℝ3 -- b e from https://iquilezles.org/articles/distfunctions/
| Link -- le r1 r2 from https://iquilezles.org/articles/distfunctions/
| Torus
| Ellipsoid
-- Simple transforms
| Rotate3 (Quaternion ) SymbolicObj3
| Transform3 (M44 ) SymbolicObj3
Expand Down Expand Up @@ -373,6 +377,8 @@ instance Show SymbolicObj3 where
ExtrudeOnEdgeOf s s1 ->
showCon "extrudeOnEdgeOf" @| s @| s1
Shared3 s -> flip showsPrec s
Torus r1 r2 -> showCon "torus" @| r1 @| r2
Ellipsoid a b c -> showCon "ellipsoid" @| a @| b @| c

infixl 2 @||
------------------------------------------------------------------------------
Expand Down
5 changes: 4 additions & 1 deletion Graphics/Implicit/Export/SymbolicFormats.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module Graphics.Implicit.Export.SymbolicFormats (scad2, scad3) where

import Prelude((.), fmap, Either(Left, Right), ($), (*), ($!), (-), (/), pi, error, (+), (==), take, floor, (&&), const, pure, (<>), sequenceA, (<$>))

import Graphics.Implicit.Definitions(, SymbolicObj2(Shared2, Square, Circle, Polygon, Rotate2, Transform2), SymbolicObj3(Shared3, Cube, Sphere, Cylinder, BoxFrame, Rotate3, Transform3, Extrude, ExtrudeM, RotateExtrude, ExtrudeOnEdgeOf, Link), isScaleID, SharedObj(Empty, Full, Complement, UnionR, IntersectR, DifferenceR, Translate, Scale, Mirror, Outset, Shell, EmbedBoxedObj, WithRounding), quaternionToEuler)
import Graphics.Implicit.Definitions(, SymbolicObj2(Shared2, Square, Circle, Polygon, Rotate2, Transform2), SymbolicObj3(Shared3, Cube, Sphere, Cylinder, BoxFrame, Rotate3, Transform3, Extrude, ExtrudeM, RotateExtrude, ExtrudeOnEdgeOf, Link, Torus, Ellipsoid), isScaleID, SharedObj(Empty, Full, Complement, UnionR, IntersectR, DifferenceR, Translate, Scale, Mirror, Outset, Shell, EmbedBoxedObj, WithRounding), quaternionToEuler)
import Graphics.Implicit.Export.TextBuilderUtils(Text, Builder, toLazyText, fromLazyText, bf)

import Control.Monad.Reader (Reader, runReader, ask)
Expand Down Expand Up @@ -134,6 +134,9 @@ buildS3 (BoxFrame (V3 w d h) e) = callNaked "boxFrame"
buildS3 (Link le r1 r2) = callNaked "link"
["le = " <> bf le, "r1 = " <> bf r1, "r2 = " <> bf r2]
[]
buildS3 (Torus r1 r2) = callNaked "torus" ["r1 = " <> bf r1, "r2 = " <> bf r2] []

buildS3 (Ellipsoid a b c) = callNaked "ellipsoid" ["a = " <> bf a, "b = " <> bf b, "c = " <> bf c] []

buildS3 (Cylinder h r1 r2) = callNaked "cylinder" [
"r1 = " <> bf r1
Expand Down
6 changes: 5 additions & 1 deletion Graphics/Implicit/ObjectUtil/GetBox3.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Graphics.Implicit.Definitions
( Fastℕ,
fromFastℕ,
ExtrudeMScale(C2, C1),
SymbolicObj3(Shared3, Cube, Sphere, Cylinder, Rotate3, Transform3, Extrude, ExtrudeOnEdgeOf, ExtrudeM, RotateExtrude, BoxFrame, Link),
SymbolicObj3(Shared3, Cube, Sphere, Cylinder, Rotate3, Transform3, Extrude, ExtrudeOnEdgeOf, ExtrudeM, RotateExtrude, BoxFrame, Link, Torus, Ellipsoid),
Box3,
,
fromFastℕtoℝ,
Expand Down Expand Up @@ -40,6 +40,10 @@ getBox3 (Link le r1 r2) =
v = V3 (le + r) (r1*2) (r2*2)
-- V3 (le+(r*2)) r (r2*2)
in (-v, v)
getBox3 (Torus r1 r2) =
let r = r1 + r2
in (V3 (-r) (-r) (-r2), V3 r r r2)
getBox3 (Ellipsoid a b c) = (V3 (-a) (-b) (-c), V3 a b c)
-- (Rounded) CSG
-- Simple transforms
getBox3 (Rotate3 q symbObj) =
Expand Down
16 changes: 4 additions & 12 deletions Graphics/Implicit/ObjectUtil/GetImplicit3.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,20 +6,10 @@

module Graphics.Implicit.ObjectUtil.GetImplicit3 (getImplicit3) where

import Prelude (id, (||), (/=), either, round, fromInteger, Either(Left, Right), abs, (-), (/), (*), sqrt, (+), atan2, max, cos, minimum, ($), sin, pi, (.), Bool(True, False), ceiling, floor, pure, (==), otherwise, min, Num, Applicative)
import Prelude (id, (||), (/=), either, round, fromInteger, Either(Left, Right), abs, (-), (/), (*), sqrt, (+), atan2, max, cos, minimum, ($), sin, pi, (.), Bool(True, False), ceiling, floor, pure, (==), otherwise, (**), Applicative, Num, min)

import Graphics.Implicit.Definitions
( objectRounding,
ObjectContext,
,
SymbolicObj3(Cube, Sphere, Cylinder, Rotate3, Transform3, Extrude,
ExtrudeM, ExtrudeOnEdgeOf, RotateExtrude, Shared3, BoxFrame, Link),
Obj3,
ℝ2,
,
fromℕtoℝ,
toScaleFn,
ℝ3 )
( objectRounding, ObjectContext, , SymbolicObj3(Cube, Sphere, Cylinder, Rotate3, Transform3, Extrude, ExtrudeM, ExtrudeOnEdgeOf, RotateExtrude, Shared3, Torus, Ellipsoid, BoxFrame, Link), Obj3, ℝ2, , fromℕtoℝ, toScaleFn, ℝ3 )

import Graphics.Implicit.MathUtil ( rmax, rmaximum )

Expand Down Expand Up @@ -52,6 +42,8 @@ getImplicit3 ctx (Cube (V3 dx dy dz)) =
\(V3 x y z) -> rmaximum (objectRounding ctx) [abs (x-dx/2) - dx/2, abs (y-dy/2) - dy/2, abs (z-dz/2) - dz/2]
getImplicit3 _ (Sphere r) =
\(V3 x y z) -> sqrt (x*x + y*y + z*z) - r
getImplicit3 _ (Torus r1 r2) = \(V3 x y z) -> let a = (sqrt (x**2 + y**2) - r1) in a**2 + z**2 - r2**2
getImplicit3 _ (Ellipsoid a b c) = \(V3 x y z) -> (x**2/a**2) + (y**2/b**2) + (z**2/c**2) - 1
getImplicit3 _ (Cylinder h r1 r2) = \(V3 x y z) ->
let
d = sqrt (x*x + y*y) - ((r2-r1)/h*z+r1)
Expand Down
16 changes: 6 additions & 10 deletions Graphics/Implicit/Primitives.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ module Graphics.Implicit.Primitives (
pattern Shared,
Object(Space, canonicalize)) where

import Prelude(Applicative, Eq, Foldable, Num, abs, (<), otherwise, Num, (+), (-), (*), (/), (.), negate, Bool(True, False), Maybe(Just, Nothing), Either, fmap, ($), (**), sqrt, (<=), (&&), max, Ord)
import Prelude(Applicative, Eq, Foldable, Num, abs, (<), otherwise, Num, (-), (*), (/), (.), negate, Bool(True, False), Maybe(Just, Nothing), Either, fmap, ($), (<=), (&&), max, Ord)

import Graphics.Implicit.Canon (canonicalize2, canonicalize3)
import Graphics.Implicit.Definitions (ObjectContext, , ℝ2, ℝ3, Box2,
Expand Down Expand Up @@ -87,14 +87,16 @@ import Graphics.Implicit.Definitions (ObjectContext, ℝ, ℝ2, ℝ3, Box2,
Sphere,
Cylinder,
BoxFrame,
Torus,
Rotate3,
Transform3,
Extrude,
ExtrudeM,
RotateExtrude,
ExtrudeOnEdgeOf,
Shared3,
Link
Link,
Ellipsoid
),
ExtrudeMScale,
defaultObjectContext
Expand Down Expand Up @@ -157,16 +159,10 @@ cone ::
cone = cylinder2 0

torus :: -> -> SymbolicObj3 -- Major radius, minor radius
torus r1 r2 = implicit
(\(V3 x y z) -> let a = (sqrt (x**2 + y**2) - r1) in a**2 + z**2 - r2**2)
(V3 (-r) (-r) (-r2), V3 r r r2)
where
r = r1 + r2
torus = Torus

ellipsoid :: -> -> -> SymbolicObj3 -- a, b, c
ellipsoid a b c = implicit
(\(V3 x y z) -> (x**2/a**2) + (y**2/b**2) + (z**2/c**2) - 1)
(V3 (-a) (-b) (-c), V3 a b c)
ellipsoid = Ellipsoid

-- $ 2D Primitives

Expand Down
Loading

0 comments on commit 9cd6c5e

Please sign in to comment.