Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Graphics.Implicit.Primitives
Synopsis
- translate :: Object obj f a => f a -> obj -> obj
- mirror :: Object obj f a => f a -> obj -> obj
- scale :: Object obj f a => f a -> obj -> obj
- outset :: Object obj f a => ℝ -> obj -> obj
- complement :: Object obj f a => obj -> obj
- union :: Object obj f a => [obj] -> obj
- intersect :: Object obj f a => [obj] -> obj
- difference :: Object obj f a => obj -> [obj] -> obj
- unionR :: Object obj f a => ℝ -> [obj] -> obj
- intersectR :: Object obj f a => ℝ -> [obj] -> obj
- differenceR :: Object obj f a => ℝ -> obj -> [obj] -> obj
- shell :: Object obj f a => ℝ -> obj -> obj
- getBox :: Object obj f a => obj -> (f a, f a)
- getImplicit :: Object obj f a => obj -> f a -> a
- getImplicit' :: Object obj f a => ObjectContext -> obj -> f a -> a
- extrude :: SymbolicObj2 -> ℝ -> SymbolicObj3
- extrudeM :: Either ℝ (ℝ -> ℝ) -> ExtrudeMScale -> Either ℝ2 (ℝ -> ℝ2) -> SymbolicObj2 -> Either ℝ (ℝ2 -> ℝ) -> SymbolicObj3
- extrudeOnEdgeOf :: SymbolicObj2 -> SymbolicObj2 -> SymbolicObj3
- sphere :: ℝ -> SymbolicObj3
- cube :: Bool -> ℝ3 -> SymbolicObj3
- rect3 :: ℝ3 -> ℝ3 -> SymbolicObj3
- circle :: ℝ -> SymbolicObj2
- cylinder :: ℝ -> ℝ -> SymbolicObj3
- cylinder2 :: ℝ -> ℝ -> ℝ -> SymbolicObj3
- cone :: ℝ -> ℝ -> SymbolicObj3
- torus :: ℝ -> ℝ -> SymbolicObj3
- ellipsoid :: ℝ -> ℝ -> ℝ -> SymbolicObj3
- square :: Bool -> ℝ2 -> SymbolicObj2
- rect :: ℝ2 -> ℝ2 -> SymbolicObj2
- polygon :: [ℝ2] -> SymbolicObj2
- rotateExtrude :: ℝ -> Either ℝ2 (ℝ -> ℝ2) -> Either ℝ (ℝ -> ℝ) -> SymbolicObj2 -> SymbolicObj3
- rotate3 :: ℝ3 -> SymbolicObj3 -> SymbolicObj3
- rotateQ :: Quaternion ℝ -> SymbolicObj3 -> SymbolicObj3
- rotate3V :: ℝ -> ℝ3 -> SymbolicObj3 -> SymbolicObj3
- transform3 :: M44 ℝ -> SymbolicObj3 -> SymbolicObj3
- pack3 :: ℝ2 -> ℝ -> [SymbolicObj3] -> Maybe SymbolicObj3
- rotate :: ℝ -> SymbolicObj2 -> SymbolicObj2
- transform :: M33 ℝ -> SymbolicObj2 -> SymbolicObj2
- pack2 :: ℝ2 -> ℝ -> [SymbolicObj2] -> Maybe SymbolicObj2
- implicit :: Object obj f a => (f a -> a) -> (f a, f a) -> obj
- emptySpace :: Object obj f a => obj
- fullSpace :: Object obj f a => obj
- withRounding :: Object obj f a => ℝ -> obj -> obj
- _Shared :: Object obj f a => Prism' obj (SharedObj obj f a)
- pattern Shared :: Object obj f a => SharedObj obj f a -> obj
- class (Applicative f, Eq a, Eq (f a), Foldable f, Num a, Num (f a)) => Object obj f a | obj -> f a where
- type Space obj :: Type -> Type
- canonicalize :: obj -> obj
Documentation
Arguments
:: Object obj f a | |
=> f a | Vector to translate by |
-> obj | Object to translate |
-> obj | Resulting object |
Translate an object by a vector of appropriate dimension.
Arguments
:: Object obj f a | |
=> f a | Vector defining the hyperplane |
-> obj | Object to mirror |
-> obj | Resulting object |
Mirror an object across the hyperplane whose normal is a given vector.
Arguments
:: Object obj f a | |
=> f a | Amount to scale by |
-> obj | Object to scale |
-> obj | Resulting scaled object |
Scale an object
Outset of an object.
Arguments
:: Object obj f a | |
=> obj | Object to complement |
-> obj | Result |
Complement an Object
difference :: Object obj f a => obj -> [obj] -> obj Source #
Arguments
:: Object obj f a | |
=> ℝ | The radius (in mm) of rounding |
-> [obj] | objects to union |
-> obj | Resulting object |
Rounded union
Arguments
:: Object obj f a | |
=> ℝ | The radius (in mm) of rounding |
-> [obj] | Objects to intersect |
-> obj | Resulting object |
Rounded minimum
Arguments
:: Object obj f a | |
=> ℝ | The radius (in mm) of rounding |
-> obj | Base object |
-> [obj] | Objects to subtract from the base |
-> obj | Resulting object |
Rounded difference
Make a shell of an object.
Arguments
:: Object obj f a | |
=> obj | Object to get box of |
-> (f a, f a) | Bounding box |
Get the bounding box an object
Arguments
:: Object obj f a | |
=> obj | Object to get implicit function of |
-> f a -> a | Implicit function |
Get the implicit function for an object
Arguments
:: Object obj f a | |
=> ObjectContext | |
-> obj | Object to get implicit function of |
-> f a -> a | Implicit function |
Get the implicit function for an object
Arguments
:: SymbolicObj2 | |
-> ℝ | Extrusion height |
-> SymbolicObj3 |
Extrude a 2d object upwards. The current object-rounding value set by
withRounding
is used to round the caps, but is not used by the 2D object.
Arguments
:: Either ℝ (ℝ -> ℝ) | twist |
-> ExtrudeMScale | scale |
-> Either ℝ2 (ℝ -> ℝ2) | translate |
-> SymbolicObj2 | object to extrude |
-> Either ℝ (ℝ2 -> ℝ) | height to extrude to |
-> SymbolicObj3 |
The current object-rounding value set by withRounding
is used to round
the caps, but is not used by the 2D object.
Arguments
:: ℝ | Radius of the sphere |
-> SymbolicObj3 | Resulting sphere |
Arguments
:: Bool | Centered? |
-> ℝ3 | Size |
-> SymbolicObj3 | Resuting cube. (0,0,0) is bottom left if |
A cube
Arguments
:: ℝ3 | Bottom.. corner |
-> ℝ3 | Top right... corner |
-> SymbolicObj3 | Resuting cube |
A rectangular prism
Arguments
:: ℝ | radius of the circle |
-> SymbolicObj2 | resulting circle |
Arguments
:: ℝ | Radius of the cylinder |
-> ℝ | Height of the cylinder |
-> SymbolicObj3 | Resulting cylinder |
Arguments
:: ℝ | Radius of the cylinder |
-> ℝ | Second radius of the cylinder |
-> ℝ | Height of the cylinder |
-> SymbolicObj3 | Resulting cylinder |
A conical frustum --- ie. a cylinder with different radii at either end.
Arguments
:: ℝ | Radius of the cylinder |
-> ℝ | Height of the cylinder |
-> SymbolicObj3 | Resulting cylinder |
Arguments
:: Bool | Centered? |
-> ℝ2 | Size |
-> SymbolicObj2 | Resulting square (bottom right = (0,0) ) |
A square
Arguments
:: ℝ2 | Bottom left corner |
-> ℝ2 | Top right corner |
-> SymbolicObj2 | Resulting square |
A rectangle
Arguments
:: [ℝ2] | Verticies of the polygon |
-> SymbolicObj2 | Resulting polygon |
A 2D polygon
rotate3 :: ℝ3 -> SymbolicObj3 -> SymbolicObj3 Source #
Rotate a 3D object via an Euler angle, measured in radians, along the world axis.
rotateQ :: Quaternion ℝ -> SymbolicObj3 -> SymbolicObj3 Source #
Arguments
:: ℝ | Angle of rotation |
-> ℝ3 | Axis of rotation |
-> SymbolicObj3 | |
-> SymbolicObj3 |
Rotate a 3D object along an arbitrary axis.
transform3 :: M44 ℝ -> SymbolicObj3 -> SymbolicObj3 Source #
Transform a 3D object using a 4x4 matrix representing affine transformation (OpenSCAD multmatrix)
Arguments
:: ℝ2 | Area to pack |
-> ℝ | Separation between objects |
-> [SymbolicObj3] | Objects to pack |
-> Maybe SymbolicObj3 |
|
Attempt to pack multiple 3D objects into a fixed area. The z
coordinate
of each object is dropped, and the resulting packed objects will all be on
the same plane.
FIXME: shouldn't this pack into a 3d area, or have a 3d equivalent?
rotate :: ℝ -> SymbolicObj2 -> SymbolicObj2 Source #
transform :: M33 ℝ -> SymbolicObj2 -> SymbolicObj2 Source #
Transform a 2D object using a 3x3 matrix representing affine transformation (OpenSCAD multmatrix)
Arguments
:: ℝ2 | Area to pack |
-> ℝ | Separation between objects |
-> [SymbolicObj2] | Objects to pack |
-> Maybe SymbolicObj2 |
|
Attempt to pack multiple 2D objects into a fixed area.
Arguments
:: Object obj f a | |
=> (f a -> a) | Implicit function |
-> (f a, f a) | Bounding box |
-> obj | Resulting object |
emptySpace :: Object obj f a => obj Source #
The object that fills no space
withRounding :: Object obj f a => ℝ -> obj -> obj Source #
Set the current object-rounding value for the given object. The rounding value is measured in units of distance, and describes the radius of rounded corners.
This can be used to change the shape of more primitive forms, for example,
we can make a cube with rounded corners via withRounding 5 (
.cube
True
20)
applies the rounding withRounding
r objr
all primitives objects in
obj
, so long as they have the same dimensionality. That is to say,
the current object-rounding value set in 3D will not apply to extruded 2D
shapes.
class (Applicative f, Eq a, Eq (f a), Foldable f, Num a, Num (f a)) => Object obj f a | obj -> f a where Source #
Operations available on both 2D and 3D objects. The obvious omission of
rotation operations from this class are a technical limitation, and are
instead provided by rotate
and rotate3
.
Library users shouldn't need to provide new instances of this class.
Minimal complete definition
Associated Types
type Space obj :: Type -> Type Source #
Type representing a space this object belongs to. V3 for 3D objects, V2 for 2D
Methods
canonicalize :: obj -> obj Source #
Canonicalization function used to rewrite / normalize abstract syntax tree representing an object
Instances
Object SymbolicObj2 V2 ℝ Source # | |
Defined in Graphics.Implicit.Primitives Methods _Shared :: Prism' SymbolicObj2 (SharedObj SymbolicObj2 V2 ℝ) Source # getBox :: SymbolicObj2 -> (V2 ℝ, V2 ℝ) Source # getImplicit' :: ObjectContext -> SymbolicObj2 -> V2 ℝ -> ℝ Source # | |
Object SymbolicObj3 V3 ℝ Source # | |
Defined in Graphics.Implicit.Primitives Methods _Shared :: Prism' SymbolicObj3 (SharedObj SymbolicObj3 V3 ℝ) Source # getBox :: SymbolicObj3 -> (V3 ℝ, V3 ℝ) Source # getImplicit' :: ObjectContext -> SymbolicObj3 -> V3 ℝ -> ℝ Source # |