Safe Haskell | Safe-Inferred |
---|---|
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 ℝ
- newtype ℝ3' = ℝ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 -> V3 a
- hasZeroComponent :: (Foldable f, Num a, Eq a) => f a -> Bool
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
Representable V2 | |
MonadFix V2 | |
MonadZip V2 | |
Foldable V2 | |
Defined in Linear.V2 Methods fold :: Monoid m => V2 m -> m # foldMap :: Monoid m => (a -> m) -> V2 a -> m # foldMap' :: Monoid m => (a -> m) -> V2 a -> m # foldr :: (a -> b -> b) -> b -> V2 a -> b # foldr' :: (a -> b -> b) -> b -> V2 a -> b # foldl :: (b -> a -> b) -> b -> V2 a -> b # foldl' :: (b -> a -> b) -> b -> V2 a -> b # foldr1 :: (a -> a -> a) -> V2 a -> a # foldl1 :: (a -> a -> a) -> V2 a -> a # elem :: Eq a => a -> V2 a -> Bool # maximum :: Ord a => V2 a -> a # | |
Eq1 V2 | |
Ord1 V2 | |
Read1 V2 | |
Show1 V2 | |
Traversable V2 | |
Applicative V2 | |
Functor V2 | |
Monad V2 | |
Serial1 V2 | |
Defined in Linear.V2 Methods serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () # deserializeWith :: MonadGet m => m a -> m (V2 a) # | |
Distributive V2 | |
Foldable1 V2 | |
Defined in Linear.V2 Methods fold1 :: Semigroup m => V2 m -> m # foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m # foldMap1' :: Semigroup m => (a -> m) -> V2 a -> m # toNonEmpty :: V2 a -> NonEmpty a # maximum :: Ord a => V2 a -> a # minimum :: Ord a => V2 a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V2 a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V2 a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V2 a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V2 a -> b # | |
Hashable1 V2 | |
ComponentWiseMultable ℝ2 Source # | |
Affine V2 | |
Metric V2 | |
Finite V2 | |
R1 V2 | |
R2 V2 | |
Additive V2 | |
Apply V2 | |
Bind V2 | |
Traversable1 V2 | |
Generic1 V2 | |
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 # | |
Unbox a => Vector Vector (V2 a) | |
Defined in Linear.V2 Methods basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) # basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) # basicLength :: Vector (V2 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) # basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) # basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () # | |
Unbox a => MVector MVector (V2 a) | |
Defined in Linear.V2 Methods basicLength :: MVector s (V2 a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) # basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) # basicInitialize :: MVector s (V2 a) -> ST s () # basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) # basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) # basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () # basicClear :: MVector s (V2 a) -> ST s () # basicSet :: MVector s (V2 a) -> V2 a -> ST s () # basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () # basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () # basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) # | |
Data a => Data (V2 a) | |
Defined in Linear.V2 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V2 a -> c (V2 a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V2 a) # dataTypeOf :: V2 a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V2 a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a)) # gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r # gmapQ :: (forall d. Data d => d -> u) -> V2 a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> V2 a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) # | |
Storable a => Storable (V2 a) | |
Monoid a => Monoid (V2 a) | |
Semigroup a => Semigroup (V2 a) | |
Bounded a => Bounded (V2 a) | |
Floating a => Floating (V2 a) | |
Generic (V2 a) | |
Ix a => Ix (V2 a) | |
Num a => Num (V2 a) | |
Read a => Read (V2 a) | |
Fractional a => Fractional (V2 a) | |
Show a => Show (V2 a) | |
Binary a => Binary (V2 a) | |
Serial a => Serial (V2 a) | |
Serialize a => Serialize (V2 a) | |
NFData a => NFData (V2 a) | |
Eq a => Eq (V2 a) | |
Ord a => Ord (V2 a) | |
Hashable a => Hashable (V2 a) | |
Ixed (V2 a) | |
Epsilon a => Epsilon (V2 a) | |
Random a => Random (V2 a) | |
Unbox a => Unbox (V2 a) | |
Defined in Linear.V2 | |
FoldableWithIndex (E V2) V2 | |
FunctorWithIndex (E V2) V2 | |
TraversableWithIndex (E V2) V2 | |
Lift a => Lift (V2 a :: Type) | |
Each (V2 a) (V2 b) a b | |
Field1 (V2 a) (V2 a) a a | |
Field2 (V2 a) (V2 a) a a | |
type Rep V2 | |
type Diff V2 | |
Defined in Linear.Affine | |
type Size V2 | |
type Rep1 V2 | |
Defined in Linear.V2 type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)) | |
data MVector s (V2 a) | |
type Rep (V2 a) | |
Defined in Linear.V2 type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) | |
type Index (V2 a) | |
type IxValue (V2 a) | |
data Vector (V2 a) | |
A 3-dimensional vector
Constructors
V3 !a !a !a |
Instances
Representable V3 | |
MonadFix V3 | |
MonadZip V3 | |
Foldable V3 | |
Defined in Linear.V3 Methods fold :: Monoid m => V3 m -> m # foldMap :: Monoid m => (a -> m) -> V3 a -> m # foldMap' :: Monoid m => (a -> m) -> V3 a -> m # foldr :: (a -> b -> b) -> b -> V3 a -> b # foldr' :: (a -> b -> b) -> b -> V3 a -> b # foldl :: (b -> a -> b) -> b -> V3 a -> b # foldl' :: (b -> a -> b) -> b -> V3 a -> b # foldr1 :: (a -> a -> a) -> V3 a -> a # foldl1 :: (a -> a -> a) -> V3 a -> a # elem :: Eq a => a -> V3 a -> Bool # maximum :: Ord a => V3 a -> a # | |
Eq1 V3 | |
Ord1 V3 | |
Read1 V3 | |
Show1 V3 | |
Traversable V3 | |
Applicative V3 | |
Functor V3 | |
Monad V3 | |
Serial1 V3 | |
Defined in Linear.V3 Methods serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () # deserializeWith :: MonadGet m => m a -> m (V3 a) # | |
Distributive V3 | |
Foldable1 V3 | |
Defined in Linear.V3 Methods fold1 :: Semigroup m => V3 m -> m # foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m # foldMap1' :: Semigroup m => (a -> m) -> V3 a -> m # toNonEmpty :: V3 a -> NonEmpty a # maximum :: Ord a => V3 a -> a # minimum :: Ord a => V3 a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V3 a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V3 a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V3 a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V3 a -> b # | |
Hashable1 V3 | |
ComponentWiseMultable ℝ3 Source # | |
Affine V3 | |
Metric V3 | |
Finite V3 | |
R1 V3 | |
R2 V3 | |
R3 V3 | |
Additive V3 | |
Apply V3 | |
Bind V3 | |
Traversable1 V3 | |
Generic1 V3 | |
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 # | |
Unbox a => Vector Vector (V3 a) | |
Defined in Linear.V3 Methods basicUnsafeFreeze :: Mutable Vector s (V3 a) -> ST s (Vector (V3 a)) # basicUnsafeThaw :: Vector (V3 a) -> ST s (Mutable Vector s (V3 a)) # basicLength :: Vector (V3 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) # basicUnsafeIndexM :: Vector (V3 a) -> Int -> Box (V3 a) # basicUnsafeCopy :: Mutable Vector s (V3 a) -> Vector (V3 a) -> ST s () # | |
Unbox a => MVector MVector (V3 a) | |
Defined in Linear.V3 Methods basicLength :: MVector s (V3 a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) # basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (V3 a)) # basicInitialize :: MVector s (V3 a) -> ST s () # basicUnsafeReplicate :: Int -> V3 a -> ST s (MVector s (V3 a)) # basicUnsafeRead :: MVector s (V3 a) -> Int -> ST s (V3 a) # basicUnsafeWrite :: MVector s (V3 a) -> Int -> V3 a -> ST s () # basicClear :: MVector s (V3 a) -> ST s () # basicSet :: MVector s (V3 a) -> V3 a -> ST s () # basicUnsafeCopy :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () # basicUnsafeMove :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () # basicUnsafeGrow :: MVector s (V3 a) -> Int -> ST s (MVector s (V3 a)) # | |
Data a => Data (V3 a) | |
Defined in Linear.V3 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V3 a -> c (V3 a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V3 a) # dataTypeOf :: V3 a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V3 a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a)) # gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r # gmapQ :: (forall d. Data d => d -> u) -> V3 a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> V3 a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) # | |
Storable a => Storable (V3 a) | |
Monoid a => Monoid (V3 a) | |
Semigroup a => Semigroup (V3 a) | |
Bounded a => Bounded (V3 a) | |
Floating a => Floating (V3 a) | |
Generic (V3 a) | |
Ix a => Ix (V3 a) | |
Num a => Num (V3 a) | |
Read a => Read (V3 a) | |
Fractional a => Fractional (V3 a) | |
Show a => Show (V3 a) | |
Binary a => Binary (V3 a) | |
Serial a => Serial (V3 a) | |
Serialize a => Serialize (V3 a) | |
NFData a => NFData (V3 a) | |
Eq a => Eq (V3 a) | |
Ord a => Ord (V3 a) | |
Hashable a => Hashable (V3 a) | |
Ixed (V3 a) | |
Epsilon a => Epsilon (V3 a) | |
Random a => Random (V3 a) | |
Unbox a => Unbox (V3 a) | |
Defined in Linear.V3 | |
FoldableWithIndex (E V3) V3 | |
FunctorWithIndex (E V3) V3 | |
TraversableWithIndex (E V3) V3 | |
Lift a => Lift (V3 a :: Type) | |
Each (V3 a) (V3 b) a b | |
Field1 (V3 a) (V3 a) a a | |
Field2 (V3 a) (V3 a) a a | |
Field3 (V3 a) (V3 a) a a | |
type Rep V3 | |
type Diff V3 | |
Defined in Linear.Affine | |
type Size V3 | |
type Rep1 V3 | |
Defined in Linear.V3 type Rep1 V3 = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))) | |
data MVector s (V3 a) | |
type Rep (V3 a) | |
Defined in Linear.V3 type Rep (V3 a) = D1 ('MetaData "V3" "Linear.V3" "linear-1.22-RQ2AYz1OLxFCpCY5CLqBO" 'False) (C1 ('MetaCons "V3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))) | |
type Index (V3 a) | |
type IxValue (V3 a) | |
data Vector (V3 a) | |
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
newtype ObjectContext Source #
Constructors
ObjectContext | |
Fields
|
Instances
Show ObjectContext Source # | |
Defined in Graphics.Implicit.Definitions Methods showsPrec :: Int -> ObjectContext -> ShowS # show :: ObjectContext -> String # showList :: [ObjectContext] -> ShowS # | |
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 # |
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 -> V3 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