Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data HyperPlane (d :: Nat) (r :: *) = HyperPlane {
- _inPlane :: !(Point d r)
- _normalVec :: !(Vector d r)
- normalVec :: forall d r. Lens' (HyperPlane d r) (Vector d r)
- inPlane :: forall d r. Lens' (HyperPlane d r) (Point d r)
- onHyperPlane :: (Num r, Eq r, Arity d) => Point d r -> HyperPlane d r -> Bool
- type Plane = HyperPlane 3
- pattern Plane :: Point 3 r -> Vector 3 r -> Plane r
- from3Points :: Num r => Point 3 r -> Point 3 r -> Point 3 r -> HyperPlane 3 r
- class HasSupportingPlane t where
- supportingPlane :: t -> HyperPlane (Dimension t) (NumType t)
Documentation
data HyperPlane (d :: Nat) (r :: *) Source #
Hyperplanes embedded in a \(d\) dimensional space.
HyperPlane | |
|
Instances
onHyperPlane :: (Num r, Eq r, Arity d) => Point d r -> HyperPlane d r -> Bool Source #
Test if a point lies on a hyperplane.
3 Dimensional planes
type Plane = HyperPlane 3 Source #
from3Points :: Num r => Point 3 r -> Point 3 r -> Point 3 r -> HyperPlane 3 r Source #
Supporting Planes
class HasSupportingPlane t where Source #
Types for which we can compute a supporting hyperplane, i.e. a hyperplane that contains the thing of type t.
supportingPlane :: t -> HyperPlane (Dimension t) (NumType t) Source #
Instances
HasSupportingPlane (HyperPlane d r) Source # | |
Defined in Data.Geometry.HyperPlane supportingPlane :: HyperPlane d r -> HyperPlane (Dimension (HyperPlane d r)) (NumType (HyperPlane d r)) Source # | |
Num r => HasSupportingPlane (Triangle 3 p r) Source # | |
Defined in Data.Geometry.Triangle supportingPlane :: Triangle 3 p r -> HyperPlane (Dimension (Triangle 3 p r)) (NumType (Triangle 3 p r)) Source # |