hgeometry-0.8.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.HyperPlane

Contents

Synopsis

Documentation

data HyperPlane (d :: Nat) (r :: *) Source #

Hyperplanes embedded in a \(d\) dimensional space.

Constructors

HyperPlane 

Fields

Instances
Arity d => Functor (HyperPlane d) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

fmap :: (a -> b) -> HyperPlane d a -> HyperPlane d b #

(<$) :: a -> HyperPlane d b -> HyperPlane d a #

Arity d => Foldable (HyperPlane d) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

fold :: Monoid m => HyperPlane d m -> m #

foldMap :: Monoid m => (a -> m) -> HyperPlane d a -> m #

foldr :: (a -> b -> b) -> b -> HyperPlane d a -> b #

foldr' :: (a -> b -> b) -> b -> HyperPlane d a -> b #

foldl :: (b -> a -> b) -> b -> HyperPlane d a -> b #

foldl' :: (b -> a -> b) -> b -> HyperPlane d a -> b #

foldr1 :: (a -> a -> a) -> HyperPlane d a -> a #

foldl1 :: (a -> a -> a) -> HyperPlane d a -> a #

toList :: HyperPlane d a -> [a] #

null :: HyperPlane d a -> Bool #

length :: HyperPlane d a -> Int #

elem :: Eq a => a -> HyperPlane d a -> Bool #

maximum :: Ord a => HyperPlane d a -> a #

minimum :: Ord a => HyperPlane d a -> a #

sum :: Num a => HyperPlane d a -> a #

product :: Num a => HyperPlane d a -> a #

Arity d => Traversable (HyperPlane d) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

traverse :: Applicative f => (a -> f b) -> HyperPlane d a -> f (HyperPlane d b) #

sequenceA :: Applicative f => HyperPlane d (f a) -> f (HyperPlane d a) #

mapM :: Monad m => (a -> m b) -> HyperPlane d a -> m (HyperPlane d b) #

sequence :: Monad m => HyperPlane d (m a) -> m (HyperPlane d a) #

(Arity d, Eq r) => Eq (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

(==) :: HyperPlane d r -> HyperPlane d r -> Bool #

(/=) :: HyperPlane d r -> HyperPlane d r -> Bool #

(Arity d, Show r) => Show (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

showsPrec :: Int -> HyperPlane d r -> ShowS #

show :: HyperPlane d r -> String #

showList :: [HyperPlane d r] -> ShowS #

Generic (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Associated Types

type Rep (HyperPlane d r) :: Type -> Type #

Methods

from :: HyperPlane d r -> Rep (HyperPlane d r) x #

to :: Rep (HyperPlane d r) x -> HyperPlane d r #

(NFData r, Arity d) => NFData (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

rnf :: HyperPlane d r -> () #

(Arity d, Arity (d + 1), Fractional r) => IsTransformable (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

HasSupportingPlane (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

(Eq r, Fractional r) => IsIntersectableWith (Line 3 r) (Plane r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

intersect :: Line 3 r -> Plane r -> Intersection (Line 3 r) (Plane r) Source #

intersects :: Line 3 r -> Plane r -> Bool Source #

nonEmptyIntersection :: proxy (Line 3 r) -> proxy (Plane r) -> Intersection (Line 3 r) (Plane r) -> Bool Source #

type Rep (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

type Rep (HyperPlane d r) = D1 (MetaData "HyperPlane" "Data.Geometry.HyperPlane" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "HyperPlane" PrefixI True) (S1 (MetaSel (Just "_inPlane") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Point d r)) :*: S1 (MetaSel (Just "_normalVec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector d r))))
type NumType (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

type NumType (HyperPlane d r) = r
type Dimension (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

type Dimension (HyperPlane d r) = d
type IntersectionOf (Line 3 r) (Plane r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

type IntersectionOf (Line 3 r) (Plane r) = NoIntersection ': (Point 3 r ': (Line 3 r ': ([] :: [Type])))

normalVec :: forall d r. Lens' (HyperPlane d r) (Vector d r) Source #

inPlane :: forall d r. Lens' (HyperPlane d r) (Point d r) Source #

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

pattern Plane :: Point 3 r -> Vector 3 r -> Plane r 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.

Instances
HasSupportingPlane (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Num r => HasSupportingPlane (Triangle 3 p r) Source # 
Instance details

Defined in Data.Geometry.Triangle