Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Implicit.Definitions
Synopsis
- newtype Fastℕ = Fastℕ Int
- fromFastℕ :: FastN n => Fastℕ -> n
- toFastℕ :: FastN n => n -> Fastℕ
- data ℕ
- fromℕ :: N n => ℕ -> n
- toℕ :: N n => n -> ℕ
- type ℝ = Double
- type ℝ2 = V2 ℝ
- type ℝ3 = V3 ℝ
- minℝ :: ℝ
- class ComponentWiseMultable a
- (⋯*) :: ComponentWiseMultable a => a -> a -> a
- (⋯/) :: ComponentWiseMultable a => a -> a -> a
- newtype Polyline = Polyline {
- getSegments :: [ℝ2]
- newtype Polytri = Polytri (ℝ2, ℝ2, ℝ2)
- newtype Triangle = Triangle (ℝ3, ℝ3, ℝ3)
- newtype NormedTriangle = NormedTriangle ((ℝ3, ℝ3), (ℝ3, ℝ3), (ℝ3, ℝ3))
- newtype TriangleMesh = TriangleMesh {
- getTriangles :: [Triangle]
- newtype NormedTriangleMesh = NormedTriangleMesh {}
- type Obj2 = ℝ2 -> ℝ
- type Obj3 = ℝ3 -> ℝ
- type Box2 = (ℝ2, ℝ2)
- type Box3 = (ℝ3, ℝ3)
- type Boxed2 a = (a, Box2)
- type Boxed3 a = (a, Box3)
- type BoxedObj2 = Boxed2 Obj2
- type BoxedObj3 = Boxed3 Obj3
- data SharedObj obj f a
- = Empty
- | Full
- | Complement obj
- | UnionR ℝ [obj]
- | DifferenceR ℝ obj [obj]
- | IntersectR ℝ [obj]
- | Translate (f a) obj
- | Scale (f a) obj
- | Mirror (f a) obj
- | Outset ℝ obj
- | Shell ℝ obj
- | EmbedBoxedObj (f a -> a, (f a, f a))
- | WithRounding ℝ obj
- data V2 a = V2 !a !a
- data V3 a = V3 !a !a !a
- data SymbolicObj2
- = Square ℝ2
- | Circle ℝ
- | Polygon [ℝ2]
- | Rotate2 ℝ SymbolicObj2
- | Transform2 (M33 ℝ) SymbolicObj2
- | Shared2 (SharedObj SymbolicObj2 V2 ℝ)
- data SymbolicObj3
- = Cube ℝ3
- | Sphere ℝ
- | Cylinder ℝ ℝ ℝ
- | Rotate3 (Quaternion ℝ) SymbolicObj3
- | Transform3 (M44 ℝ) SymbolicObj3
- | Extrude SymbolicObj2 ℝ
- | ExtrudeM (Either ℝ (ℝ -> ℝ)) ExtrudeMScale (Either ℝ2 (ℝ -> ℝ2)) SymbolicObj2 (Either ℝ (ℝ2 -> ℝ))
- | RotateExtrude ℝ (Either ℝ2 (ℝ -> ℝ2)) (Either ℝ (ℝ -> ℝ)) SymbolicObj2
- | ExtrudeOnEdgeOf SymbolicObj2 SymbolicObj2
- | Shared3 (SharedObj SymbolicObj3 V3 ℝ)
- data ExtrudeMScale
- newtype ObjectContext = ObjectContext {
- objectRounding :: ℝ
- defaultObjectContext :: ObjectContext
- fromℕtoℝ :: ℕ -> ℝ
- fromFastℕtoℝ :: Fastℕ -> ℝ
- fromℝtoFloat :: ℝ -> Float
- toScaleFn :: ExtrudeMScale -> ℝ -> ℝ2
- isScaleID :: ExtrudeMScale -> Bool
- quaternionToEuler :: RealFloat a => Quaternion a -> (a, a, a)
Documentation
A type synonym for Double
. When used in the context of positions or
sizes, measured in units of millimeters. When used as in the context of
a rotation, measured in radians.
A pair of two Double
s. When used as an area or position vector, measured
in millimeters squared.
A triple of Double
s. When used as a volume or position vector, measured
in millimeters cubed. When used as a rotation, interpreted as Euler angles
measured in radians.
A give up point for dividing ℝs, and for the maximum difference between abs(n) and abs(-n).
class ComponentWiseMultable a Source #
Add multiply and divide operators for two ℝ2s or ℝ3s.
(⋯*) :: ComponentWiseMultable a => a -> a -> a Source #
(⋯/) :: ComponentWiseMultable a => a -> a -> a Source #
A chain of line segments, as in SVG or DXF. eg. [(0,0), (0.5,1), (1,0)] ---> / FIXME: May not be empty. expose to type system.
Constructors
Polyline | |
Fields
|
Instances
NFData Polyline Source # | |
Defined in Graphics.Implicit.Definitions | |
DiscreteAproxable SymbolicObj2 [Polyline] Source # | |
Defined in Graphics.Implicit.Export.DiscreteAproxable Methods discreteAprox :: ℝ -> SymbolicObj2 -> [Polyline] Source # |
A triangle in 2D space (a,b,c).
A triangle in 3D space (a,b,c) = a triangle with vertices a, b and c
newtype NormedTriangle Source #
A triangle ((v1,n1),(v2,n2),(v3,n3)) has vertices v1, v2, v3 with corresponding normals n1, n2, and n3
Instances
NFData NormedTriangle Source # | |
Defined in Graphics.Implicit.Definitions Methods rnf :: NormedTriangle -> () # |
newtype TriangleMesh Source #
A triangle mesh is a bunch of triangles, attempting to be a surface.
Constructors
TriangleMesh | |
Fields
|
Instances
NFData TriangleMesh Source # | |
Defined in Graphics.Implicit.Definitions Methods rnf :: TriangleMesh -> () # | |
DiscreteAproxable SymbolicObj3 TriangleMesh Source # | |
Defined in Graphics.Implicit.Export.DiscreteAproxable Methods discreteAprox :: ℝ -> SymbolicObj3 -> TriangleMesh Source # |
newtype NormedTriangleMesh Source #
A normed triangle mesh is a mesh of normed triangles.
Constructors
NormedTriangleMesh | |
Fields |
Instances
DiscreteAproxable SymbolicObj3 NormedTriangleMesh Source # | |
Defined in Graphics.Implicit.Export.DiscreteAproxable Methods discreteAprox :: ℝ -> SymbolicObj3 -> NormedTriangleMesh Source # |
data SharedObj obj f a Source #
Means of constructing symbolic objects that are common between the 2D and
3D case. This type is parameterized on obj
and vec
so that
SymbolicObj2
and SymbolicObj3
can instantiate it for their own purposes.
Constructors
Empty | The empty object |
Full | The entirely full object |
Complement obj | |
UnionR ℝ [obj] | |
DifferenceR ℝ obj [obj] | |
IntersectR ℝ [obj] | |
Translate (f a) obj | |
Scale (f a) obj | |
Mirror (f a) obj | Mirror across the line whose normal is defined by the vector |
Outset ℝ obj | |
Shell ℝ obj | |
EmbedBoxedObj (f a -> a, (f a, f a)) | |
WithRounding ℝ obj |
Instances
A 2-dimensional vector
>>>
pure 1 :: V2 Int
V2 1 1
>>>
V2 1 2 + V2 3 4
V2 4 6
>>>
V2 1 2 * V2 3 4
V2 3 8
>>>
sum (V2 1 2)
3
Constructors
V2 !a !a |
Instances
A 3-dimensional vector
Constructors
V3 !a !a !a |
Instances
data SymbolicObj2 Source #
A symbolic 2D object format. We want to have symbolic objects so that we can accelerate rendering & give ideal meshes for simple cases.
Constructors
Square ℝ2 | |
Circle ℝ | |
Polygon [ℝ2] | |
Rotate2 ℝ SymbolicObj2 | |
Transform2 (M33 ℝ) SymbolicObj2 | |
Shared2 (SharedObj SymbolicObj2 V2 ℝ) |
Instances
data SymbolicObj3 Source #
A symbolic 3D format!
Constructors
Cube ℝ3 | |
Sphere ℝ | |
Cylinder ℝ ℝ ℝ | |
Rotate3 (Quaternion ℝ) SymbolicObj3 | |
Transform3 (M44 ℝ) SymbolicObj3 | |
Extrude SymbolicObj2 ℝ | |
ExtrudeM (Either ℝ (ℝ -> ℝ)) ExtrudeMScale (Either ℝ2 (ℝ -> ℝ2)) SymbolicObj2 (Either ℝ (ℝ2 -> ℝ)) | |
RotateExtrude ℝ (Either ℝ2 (ℝ -> ℝ2)) (Either ℝ (ℝ -> ℝ)) SymbolicObj2 | |
ExtrudeOnEdgeOf SymbolicObj2 SymbolicObj2 | |
Shared3 (SharedObj SymbolicObj3 V3 ℝ) |
Instances
data ExtrudeMScale Source #
Instances
Show ExtrudeMScale Source # | |
Defined in Graphics.Implicit.Definitions Methods showsPrec :: Int -> ExtrudeMScale -> ShowS # show :: ExtrudeMScale -> String # showList :: [ExtrudeMScale] -> ShowS # | |
Generic ExtrudeMScale Source # | |
Defined in Graphics.Implicit.Definitions Associated Types type Rep ExtrudeMScale :: Type -> Type # | |
type Rep ExtrudeMScale Source # | |
Defined in Graphics.Implicit.Definitions type Rep ExtrudeMScale = D1 ('MetaData "ExtrudeMScale" "Graphics.Implicit.Definitions" "implicit-0.4.0.0-2QFrzNvv6lKFGu3kPbjLAC" 'False) (C1 ('MetaCons "C1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ℝ)) :+: (C1 ('MetaCons "C2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ℝ2)) :+: C1 ('MetaCons "Fn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ℝ -> Either ℝ ℝ2))))) |
newtype ObjectContext Source #
Constructors
ObjectContext | |
Fields
|
Instances
Eq ObjectContext Source # | |
Defined in Graphics.Implicit.Definitions Methods (==) :: ObjectContext -> ObjectContext -> Bool # (/=) :: ObjectContext -> ObjectContext -> Bool # | |
Ord ObjectContext Source # | |
Defined in Graphics.Implicit.Definitions Methods compare :: ObjectContext -> ObjectContext -> Ordering # (<) :: ObjectContext -> ObjectContext -> Bool # (<=) :: ObjectContext -> ObjectContext -> Bool # (>) :: ObjectContext -> ObjectContext -> Bool # (>=) :: ObjectContext -> ObjectContext -> Bool # max :: ObjectContext -> ObjectContext -> ObjectContext # min :: ObjectContext -> ObjectContext -> ObjectContext # | |
Show ObjectContext Source # | |
Defined in Graphics.Implicit.Definitions Methods showsPrec :: Int -> ObjectContext -> ShowS # show :: ObjectContext -> String # showList :: [ObjectContext] -> ShowS # |
fromFastℕtoℝ :: Fastℕ -> ℝ Source #
Convert from our Fast Integer (int32) to ℝ.
fromℝtoFloat :: ℝ -> Float Source #
Convert from our rational to a float, for output to a file.
isScaleID :: ExtrudeMScale -> Bool Source #
quaternionToEuler :: RealFloat a => Quaternion a -> (a, a, a) Source #
Convert a Quaternion
to its constituent euler angles.
From https://en.wikipedia.org/wiki/Conversion_between_quaternions_and_Euler_angles#Source_code_2