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

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry

Description

Basic Geometry Types

Synopsis

Documentation

replicate :: Vector v a => a -> v a #

Replicate value n times.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2)
>>> replicate 1 :: Vec2 Int
fromList [1,1]
>>> replicate 2 :: (Double,Double,Double)
(2.0,2.0,2.0)
>>> import Data.Vector.Fixed.Boxed (Vec4)
>>> replicate "foo" :: Vec4 String
fromList ["foo","foo","foo","foo"]

distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a #

Distance between two points in an affine space

qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a #

Compute the quadrance of the difference (the square of the distance)

class Additive (Diff p) => Affine (p :: Type -> Type) where #

An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.

a .+^ (b .-. a)  =  b@
(a .+^ u) .+^ v  =  a .+^ (u ^+^ v)@
(a .-. b) ^+^ v  =  (a .+^ v) .-. q@

Minimal complete definition

(.-.), (.+^)

Associated Types

type Diff (p :: Type -> Type) :: Type -> Type #

Methods

(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 #

Get the difference between two points as a vector offset.

(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 #

Add a vector offset to a point.

(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 #

Subtract a vector offset from a point.

Instances
Affine [] 
Instance details

Defined in Linear.Affine

Associated Types

type Diff [] :: Type -> Type #

Methods

(.-.) :: Num a => [a] -> [a] -> Diff [] a #

(.+^) :: Num a => [a] -> Diff [] a -> [a] #

(.-^) :: Num a => [a] -> Diff [] a -> [a] #

Affine Maybe 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Maybe :: Type -> Type #

Methods

(.-.) :: Num a => Maybe a -> Maybe a -> Diff Maybe a #

(.+^) :: Num a => Maybe a -> Diff Maybe a -> Maybe a #

(.-^) :: Num a => Maybe a -> Diff Maybe a -> Maybe a #

Affine Complex 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Complex :: Type -> Type #

Methods

(.-.) :: Num a => Complex a -> Complex a -> Diff Complex a #

(.+^) :: Num a => Complex a -> Diff Complex a -> Complex a #

(.-^) :: Num a => Complex a -> Diff Complex a -> Complex a #

Affine ZipList 
Instance details

Defined in Linear.Affine

Associated Types

type Diff ZipList :: Type -> Type #

Methods

(.-.) :: Num a => ZipList a -> ZipList a -> Diff ZipList a #

(.+^) :: Num a => ZipList a -> Diff ZipList a -> ZipList a #

(.-^) :: Num a => ZipList a -> Diff ZipList a -> ZipList a #

Affine Identity 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Identity :: Type -> Type #

Methods

(.-.) :: Num a => Identity a -> Identity a -> Diff Identity a #

(.+^) :: Num a => Identity a -> Diff Identity a -> Identity a #

(.-^) :: Num a => Identity a -> Diff Identity a -> Identity a #

Affine IntMap 
Instance details

Defined in Linear.Affine

Associated Types

type Diff IntMap :: Type -> Type #

Methods

(.-.) :: Num a => IntMap a -> IntMap a -> Diff IntMap a #

(.+^) :: Num a => IntMap a -> Diff IntMap a -> IntMap a #

(.-^) :: Num a => IntMap a -> Diff IntMap a -> IntMap a #

Affine Vector 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Vector :: Type -> Type #

Methods

(.-.) :: Num a => Vector a -> Vector a -> Diff Vector a #

(.+^) :: Num a => Vector a -> Diff Vector a -> Vector a #

(.-^) :: Num a => Vector a -> Diff Vector a -> Vector a #

Affine Plucker 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Plucker :: Type -> Type #

Methods

(.-.) :: Num a => Plucker a -> Plucker a -> Diff Plucker a #

(.+^) :: Num a => Plucker a -> Diff Plucker a -> Plucker a #

(.-^) :: Num a => Plucker a -> Diff Plucker a -> Plucker a #

Affine Quaternion 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Quaternion :: Type -> Type #

Affine V0 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V0 :: Type -> Type #

Methods

(.-.) :: Num a => V0 a -> V0 a -> Diff V0 a #

(.+^) :: Num a => V0 a -> Diff V0 a -> V0 a #

(.-^) :: Num a => V0 a -> Diff V0 a -> V0 a #

Affine V4 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V4 :: Type -> Type #

Methods

(.-.) :: Num a => V4 a -> V4 a -> Diff V4 a #

(.+^) :: Num a => V4 a -> Diff V4 a -> V4 a #

(.-^) :: Num a => V4 a -> Diff V4 a -> V4 a #

Affine V3 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V3 :: Type -> Type #

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a #

(.+^) :: Num a => V3 a -> Diff V3 a -> V3 a #

(.-^) :: Num a => V3 a -> Diff V3 a -> V3 a #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a #

Affine V1 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V1 :: Type -> Type #

Methods

(.-.) :: Num a => V1 a -> V1 a -> Diff V1 a #

(.+^) :: Num a => V1 a -> Diff V1 a -> V1 a #

(.-^) :: Num a => V1 a -> Diff V1 a -> V1 a #

(Eq k, Hashable k) => Affine (HashMap k) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (HashMap k) :: Type -> Type #

Methods

(.-.) :: Num a => HashMap k a -> HashMap k a -> Diff (HashMap k) a #

(.+^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a #

(.-^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a #

Ord k => Affine (Map k) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Map k) :: Type -> Type #

Methods

(.-.) :: Num a => Map k a -> Map k a -> Diff (Map k) a #

(.+^) :: Num a => Map k a -> Diff (Map k) a -> Map k a #

(.-^) :: Num a => Map k a -> Diff (Map k) a -> Map k a #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) :: Type -> Type #

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

Arity d => Affine (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFixed

Associated Types

type Diff (Vector d) :: Type -> Type #

Methods

(.-.) :: Num a => Vector d a -> Vector d a -> Diff (Vector d) a #

(.+^) :: Num a => Vector d a -> Diff (Vector d) a -> Vector d a #

(.-^) :: Num a => Vector d a -> Diff (Vector d) a -> Vector d a #

ImplicitArity d => Affine (VectorFamily d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamilyPeano

Associated Types

type Diff (VectorFamily d) :: Type -> Type #

Methods

(.-.) :: Num a => VectorFamily d a -> VectorFamily d a -> Diff (VectorFamily d) a #

(.+^) :: Num a => VectorFamily d a -> Diff (VectorFamily d) a -> VectorFamily d a #

(.-^) :: Num a => VectorFamily d a -> Diff (VectorFamily d) a -> VectorFamily d a #

Arity d => Affine (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Associated Types

type Diff (Vector d) :: Type -> Type #

Methods

(.-.) :: Num a => Vector d a -> Vector d a -> Diff (Vector d) a #

(.+^) :: Num a => Vector d a -> Diff (Vector d) a -> Vector d a #

(.-^) :: Num a => Vector d a -> Diff (Vector d) a -> Vector d a #

Arity d => Affine (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Associated Types

type Diff (Point d) :: Type -> Type #

Methods

(.-.) :: Num a => Point d a -> Point d a -> Diff (Point d) a #

(.+^) :: Num a => Point d a -> Diff (Point d) a -> Point d a #

(.-^) :: Num a => Point d a -> Diff (Point d) a -> Point d a #

Dim n => Affine (V n) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (V n) :: Type -> Type #

Methods

(.-.) :: Num a => V n a -> V n a -> Diff (V n) a #

(.+^) :: Num a => V n a -> Diff (V n) a -> V n a #

(.-^) :: Num a => V n a -> Diff (V n) a -> V n a #

Affine ((->) b :: Type -> Type) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff ((->) b) :: Type -> Type #

Methods

(.-.) :: Num a => (b -> a) -> (b -> a) -> Diff ((->) b) a #

(.+^) :: Num a => (b -> a) -> Diff ((->) b) a -> b -> a #

(.-^) :: Num a => (b -> a) -> Diff ((->) b) a -> b -> a #

(Affine f, Affine g) => Affine (Product f g) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Product f g) :: Type -> Type #

Methods

(.-.) :: Num a => Product f g a -> Product f g a -> Diff (Product f g) a #

(.+^) :: Num a => Product f g a -> Diff (Product f g) a -> Product f g a #

(.-^) :: Num a => Product f g a -> Diff (Product f g) a -> Product f g a #

dot :: (Metric f, Num a) => f a -> f a -> a #

Compute the inner product of two vectors or (equivalently) convert a vector f a into a covector f a -> a.

>>> V2 1 2 `dot` V2 3 4
11

quadrance :: (Metric f, Num a) => f a -> a #

Compute the squared norm. The name quadrance arises from Norman J. Wildberger's rational trigonometry.

norm :: (Metric f, Floating a) => f a -> a #

Compute the norm of a vector in a metric space

signorm :: (Metric f, Floating a) => f a -> f a #

Convert a non-zero vector to unit vector.

outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a) #

Outer (tensor) product of two vectors

unit :: (Additive t, Num a) => ASetter' (t a) a -> t a #

Create a unit vector.

>>> unit _x :: V2 Int
V2 1 0

scaled :: (Traversable t, Num a) => t a -> t (t a) #

Produce a diagonal (scale) matrix from a vector.

>>> scaled (V2 2 3)
V2 (V2 2 0) (V2 0 3)

basisFor :: (Traversable t, Num a) => t b -> [t a] #

Produce a default basis for a vector space from which the argument is drawn.

basis :: (Additive t, Traversable t, Num a) => [t a] #

Produce a default basis for a vector space. If the dimensionality of the vector space is not statically known, see basisFor.

(^/) :: (Functor f, Fractional a) => f a -> a -> f a infixl 7 #

Compute division by a scalar on the right.

(^*) :: (Functor f, Num a) => f a -> a -> f a infixl 7 #

Compute the right scalar product

>>> V2 3 4 ^* 2
V2 6 8

(*^) :: (Functor f, Num a) => a -> f a -> f a infixl 7 #

Compute the left scalar product

>>> 2 *^ V2 3 4
V2 6 8

sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a #

Sum over multiple vectors

>>> sumV [V2 1 1, V2 3 4]
V2 4 5

negated :: (Functor f, Num a) => f a -> f a #

Compute the negation of a vector

>>> negated (V2 2 4)
V2 (-2) (-4)

class Functor f => Additive (f :: Type -> Type) where #

A vector is an additive group with additional structure.

Minimal complete definition

Nothing

Methods

zero :: Num a => f a #

The zero vector

(^+^) :: Num a => f a -> f a -> f a infixl 6 #

Compute the sum of two vectors

>>> V2 1 2 ^+^ V2 3 4
V2 4 6

(^-^) :: Num a => f a -> f a -> f a infixl 6 #

Compute the difference between two vectors

>>> V2 4 5 ^-^ V2 3 1
V2 1 4

lerp :: Num a => a -> f a -> f a -> f a #

Linearly interpolate between two vectors.

liftU2 :: (a -> a -> a) -> f a -> f a -> f a #

Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.

  • For a dense vector this is equivalent to liftA2.
  • For a sparse vector this is equivalent to unionWith.

liftI2 :: (a -> b -> c) -> f a -> f b -> f c #

Apply a function to the components of two vectors.

Instances
Additive [] 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => [a] #

(^+^) :: Num a => [a] -> [a] -> [a] #

(^-^) :: Num a => [a] -> [a] -> [a] #

lerp :: Num a => a -> [a] -> [a] -> [a] #

liftU2 :: (a -> a -> a) -> [a] -> [a] -> [a] #

liftI2 :: (a -> b -> c) -> [a] -> [b] -> [c] #

Additive Maybe 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Maybe a #

(^+^) :: Num a => Maybe a -> Maybe a -> Maybe a #

(^-^) :: Num a => Maybe a -> Maybe a -> Maybe a #

lerp :: Num a => a -> Maybe a -> Maybe a -> Maybe a #

liftU2 :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a #

liftI2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

Additive Complex 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Complex a #

(^+^) :: Num a => Complex a -> Complex a -> Complex a #

(^-^) :: Num a => Complex a -> Complex a -> Complex a #

lerp :: Num a => a -> Complex a -> Complex a -> Complex a #

liftU2 :: (a -> a -> a) -> Complex a -> Complex a -> Complex a #

liftI2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c #

Additive ZipList 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => ZipList a #

(^+^) :: Num a => ZipList a -> ZipList a -> ZipList a #

(^-^) :: Num a => ZipList a -> ZipList a -> ZipList a #

lerp :: Num a => a -> ZipList a -> ZipList a -> ZipList a #

liftU2 :: (a -> a -> a) -> ZipList a -> ZipList a -> ZipList a #

liftI2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c #

Additive Identity 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Identity a #

(^+^) :: Num a => Identity a -> Identity a -> Identity a #

(^-^) :: Num a => Identity a -> Identity a -> Identity a #

lerp :: Num a => a -> Identity a -> Identity a -> Identity a #

liftU2 :: (a -> a -> a) -> Identity a -> Identity a -> Identity a #

liftI2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

Additive IntMap 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => IntMap a #

(^+^) :: Num a => IntMap a -> IntMap a -> IntMap a #

(^-^) :: Num a => IntMap a -> IntMap a -> IntMap a #

lerp :: Num a => a -> IntMap a -> IntMap a -> IntMap a #

liftU2 :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a #

liftI2 :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c #

Additive Vector 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Vector a #

(^+^) :: Num a => Vector a -> Vector a -> Vector a #

(^-^) :: Num a => Vector a -> Vector a -> Vector a #

lerp :: Num a => a -> Vector a -> Vector a -> Vector a #

liftU2 :: (a -> a -> a) -> Vector a -> Vector a -> Vector a #

liftI2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c #

Additive Plucker 
Instance details

Defined in Linear.Plucker

Methods

zero :: Num a => Plucker a #

(^+^) :: Num a => Plucker a -> Plucker a -> Plucker a #

(^-^) :: Num a => Plucker a -> Plucker a -> Plucker a #

lerp :: Num a => a -> Plucker a -> Plucker a -> Plucker a #

liftU2 :: (a -> a -> a) -> Plucker a -> Plucker a -> Plucker a #

liftI2 :: (a -> b -> c) -> Plucker a -> Plucker b -> Plucker c #

Additive Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

zero :: Num a => Quaternion a #

(^+^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

(^-^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

lerp :: Num a => a -> Quaternion a -> Quaternion a -> Quaternion a #

liftU2 :: (a -> a -> a) -> Quaternion a -> Quaternion a -> Quaternion a #

liftI2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

Additive V0 
Instance details

Defined in Linear.V0

Methods

zero :: Num a => V0 a #

(^+^) :: Num a => V0 a -> V0 a -> V0 a #

(^-^) :: Num a => V0 a -> V0 a -> V0 a #

lerp :: Num a => a -> V0 a -> V0 a -> V0 a #

liftU2 :: (a -> a -> a) -> V0 a -> V0 a -> V0 a #

liftI2 :: (a -> b -> c) -> V0 a -> V0 b -> V0 c #

Additive V4 
Instance details

Defined in Linear.V4

Methods

zero :: Num a => V4 a #

(^+^) :: Num a => V4 a -> V4 a -> V4 a #

(^-^) :: Num a => V4 a -> V4 a -> V4 a #

lerp :: Num a => a -> V4 a -> V4 a -> V4 a #

liftU2 :: (a -> a -> a) -> V4 a -> V4 a -> V4 a #

liftI2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

Additive V3 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a #

(^+^) :: Num a => V3 a -> V3 a -> V3 a #

(^-^) :: Num a => V3 a -> V3 a -> V3 a #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a #

(^+^) :: Num a => V2 a -> V2 a -> V2 a #

(^-^) :: Num a => V2 a -> V2 a -> V2 a #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Additive V1 
Instance details

Defined in Linear.V1

Methods

zero :: Num a => V1 a #

(^+^) :: Num a => V1 a -> V1 a -> V1 a #

(^-^) :: Num a => V1 a -> V1 a -> V1 a #

lerp :: Num a => a -> V1 a -> V1 a -> V1 a #

liftU2 :: (a -> a -> a) -> V1 a -> V1 a -> V1 a #

liftI2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

(Eq k, Hashable k) => Additive (HashMap k) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => HashMap k a #

(^+^) :: Num a => HashMap k a -> HashMap k a -> HashMap k a #

(^-^) :: Num a => HashMap k a -> HashMap k a -> HashMap k a #

lerp :: Num a => a -> HashMap k a -> HashMap k a -> HashMap k a #

liftU2 :: (a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a #

liftI2 :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c #

Ord k => Additive (Map k) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Map k a #

(^+^) :: Num a => Map k a -> Map k a -> Map k a #

(^-^) :: Num a => Map k a -> Map k a -> Map k a #

lerp :: Num a => a -> Map k a -> Map k a -> Map k a #

liftU2 :: (a -> a -> a) -> Map k a -> Map k a -> Map k a #

liftI2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c #

Additive f => Additive (Point f) 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a #

(^+^) :: Num a => Point f a -> Point f a -> Point f a #

(^-^) :: Num a => Point f a -> Point f a -> Point f a #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a #

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a #

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Arity d => Additive (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFixed

Methods

zero :: Num a => Vector d a #

(^+^) :: Num a => Vector d a -> Vector d a -> Vector d a #

(^-^) :: Num a => Vector d a -> Vector d a -> Vector d a #

lerp :: Num a => a -> Vector d a -> Vector d a -> Vector d a #

liftU2 :: (a -> a -> a) -> Vector d a -> Vector d a -> Vector d a #

liftI2 :: (a -> b -> c) -> Vector d a -> Vector d b -> Vector d c #

ImplicitArity d => Additive (VectorFamily d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamilyPeano

Methods

zero :: Num a => VectorFamily d a #

(^+^) :: Num a => VectorFamily d a -> VectorFamily d a -> VectorFamily d a #

(^-^) :: Num a => VectorFamily d a -> VectorFamily d a -> VectorFamily d a #

lerp :: Num a => a -> VectorFamily d a -> VectorFamily d a -> VectorFamily d a #

liftU2 :: (a -> a -> a) -> VectorFamily d a -> VectorFamily d a -> VectorFamily d a #

liftI2 :: (a -> b -> c) -> VectorFamily d a -> VectorFamily d b -> VectorFamily d c #

Arity d => Additive (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

zero :: Num a => Vector d a #

(^+^) :: Num a => Vector d a -> Vector d a -> Vector d a #

(^-^) :: Num a => Vector d a -> Vector d a -> Vector d a #

lerp :: Num a => a -> Vector d a -> Vector d a -> Vector d a #

liftU2 :: (a -> a -> a) -> Vector d a -> Vector d a -> Vector d a #

liftI2 :: (a -> b -> c) -> Vector d a -> Vector d b -> Vector d c #

Dim n => Additive (V n) 
Instance details

Defined in Linear.V

Methods

zero :: Num a => V n a #

(^+^) :: Num a => V n a -> V n a -> V n a #

(^-^) :: Num a => V n a -> V n a -> V n a #

lerp :: Num a => a -> V n a -> V n a -> V n a #

liftU2 :: (a -> a -> a) -> V n a -> V n a -> V n a #

liftI2 :: (a -> b -> c) -> V n a -> V n b -> V n c #

Additive ((->) b :: Type -> Type) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => b -> a #

(^+^) :: Num a => (b -> a) -> (b -> a) -> b -> a #

(^-^) :: Num a => (b -> a) -> (b -> a) -> b -> a #

lerp :: Num a => a -> (b -> a) -> (b -> a) -> b -> a #

liftU2 :: (a -> a -> a) -> (b -> a) -> (b -> a) -> b -> a #

liftI2 :: (a -> b0 -> c) -> (b -> a) -> (b -> b0) -> b -> c #

(Additive f, Additive g) => Additive (Product f g) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Product f g a #

(^+^) :: Num a => Product f g a -> Product f g a -> Product f g a #

(^-^) :: Num a => Product f g a -> Product f g a -> Product f g a #

lerp :: Num a => a -> Product f g a -> Product f g a -> Product f g a #

liftU2 :: (a -> a -> a) -> Product f g a -> Product f g a -> Product f g a #

liftI2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c #

(Additive f, Additive g) => Additive (Compose f g) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Compose f g a #

(^+^) :: Num a => Compose f g a -> Compose f g a -> Compose f g a #

(^-^) :: Num a => Compose f g a -> Compose f g a -> Compose f g a #

lerp :: Num a => a -> Compose f g a -> Compose f g a -> Compose f g a #

liftU2 :: (a -> a -> a) -> Compose f g a -> Compose f g a -> Compose f g a #

liftI2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c #

data C (n :: Nat) Source #

A proxy which can be used for the coordinates.

Constructors

C 
Instances
Eq (C n) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFixed

Methods

(==) :: C n -> C n -> Bool #

(/=) :: C n -> C n -> Bool #

Ord (C n) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFixed

Methods

compare :: C n -> C n -> Ordering #

(<) :: C n -> C n -> Bool #

(<=) :: C n -> C n -> Bool #

(>) :: C n -> C n -> Bool #

(>=) :: C n -> C n -> Bool #

max :: C n -> C n -> C n #

min :: C n -> C n -> C n #

Read (C n) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFixed

Methods

readsPrec :: Int -> ReadS (C n) #

readList :: ReadS [C n] #

readPrec :: ReadPrec (C n) #

readListPrec :: ReadPrec [C n] #

Show (C n) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFixed

Methods

showsPrec :: Int -> C n -> ShowS #

show :: C n -> String #

showList :: [C n] -> ShowS #

class (ImplicitArity (Peano d), KnownNat d) => Arity d Source #

Instances
(ImplicitArity (Peano d), KnownNat d) => Arity d Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

newtype Vector (d :: Nat) (r :: *) Source #

Datatype representing d dimensional vectors. The default implementation is based n VectorFixed. However, for small vectors we automatically select a more efficient representation.

Constructors

MKVector 

Fields

Instances
Arity d => FunctorWithIndex Int (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

imap :: (Int -> a -> b) -> Vector d a -> Vector d b #

imapped :: IndexedSetter Int (Vector d a) (Vector d b) a b #

Arity d => FoldableWithIndex Int (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Vector d a -> m #

ifolded :: IndexedFold Int (Vector d a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> Vector d a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> Vector d a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> Vector d a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Vector d a -> b #

Arity d => TraversableWithIndex Int (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Vector d a -> f (Vector d b) #

itraversed :: IndexedTraversal Int (Vector d a) (Vector d b) a b #

Arity d => Functor (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

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

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

Arity d => Applicative (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

pure :: a -> Vector d a #

(<*>) :: Vector d (a -> b) -> Vector d a -> Vector d b #

liftA2 :: (a -> b -> c) -> Vector d a -> Vector d b -> Vector d c #

(*>) :: Vector d a -> Vector d b -> Vector d b #

(<*) :: Vector d a -> Vector d b -> Vector d a #

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

Defined in Data.Geometry.Vector.VectorFamily

Methods

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

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

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

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

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

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

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

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

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

null :: Vector d a -> Bool #

length :: Vector d a -> Int #

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

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

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

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

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

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

Defined in Data.Geometry.Vector.VectorFamily

Methods

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

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

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

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

Arity d => Affine (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Associated Types

type Diff (Vector d) :: Type -> Type #

Methods

(.-.) :: Num a => Vector d a -> Vector d a -> Diff (Vector d) a #

(.+^) :: Num a => Vector d a -> Diff (Vector d) a -> Vector d a #

(.-^) :: Num a => Vector d a -> Diff (Vector d) a -> Vector d a #

Arity d => Metric (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

dot :: Num a => Vector d a -> Vector d a -> a #

quadrance :: Num a => Vector d a -> a #

qd :: Num a => Vector d a -> Vector d a -> a #

distance :: Floating a => Vector d a -> Vector d a -> a #

norm :: Floating a => Vector d a -> a #

signorm :: Floating a => Vector d a -> Vector d a #

Arity d => Additive (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

zero :: Num a => Vector d a #

(^+^) :: Num a => Vector d a -> Vector d a -> Vector d a #

(^-^) :: Num a => Vector d a -> Vector d a -> Vector d a #

lerp :: Num a => a -> Vector d a -> Vector d a -> Vector d a #

liftU2 :: (a -> a -> a) -> Vector d a -> Vector d a -> Vector d a #

liftI2 :: (a -> b -> c) -> Vector d a -> Vector d b -> Vector d c #

Arity d => Vector (Vector d) r Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

construct :: Fun (Peano (Dim (Vector d))) r (Vector d r) #

inspect :: Vector d r -> Fun (Peano (Dim (Vector d))) r b -> b #

basicIndex :: Vector d r -> Int -> r #

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

Defined in Data.Geometry.Vector.VectorFamily

Methods

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

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

(Ord r, Arity d) => Ord (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

compare :: Vector d r -> Vector d r -> Ordering #

(<) :: Vector d r -> Vector d r -> Bool #

(<=) :: Vector d r -> Vector d r -> Bool #

(>) :: Vector d r -> Vector d r -> Bool #

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

max :: Vector d r -> Vector d r -> Vector d r #

min :: Vector d r -> Vector d r -> Vector d r #

(Read r, Arity d) => Read (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

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

Defined in Data.Geometry.Vector.VectorFamily

Methods

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

show :: Vector d r -> String #

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

(Random r, Arity d) => Random (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector

Methods

randomR :: RandomGen g => (Vector d r, Vector d r) -> g -> (Vector d r, g) #

random :: RandomGen g => g -> (Vector d r, g) #

randomRs :: RandomGen g => (Vector d r, Vector d r) -> g -> [Vector d r] #

randoms :: RandomGen g => g -> [Vector d r] #

(Arbitrary r, Arity d) => Arbitrary (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector

Methods

arbitrary :: Gen (Vector d r) #

shrink :: Vector d r -> [Vector d r] #

(Arity d, Hashable r) => Hashable (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

hashWithSalt :: Int -> Vector d r -> Int #

hash :: Vector d r -> Int #

(ToJSON r, Arity d) => ToJSON (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

toJSON :: Vector d r -> Value #

toEncoding :: Vector d r -> Encoding #

toJSONList :: [Vector d r] -> Value #

toEncodingList :: [Vector d r] -> Encoding #

(FromJSON r, Arity d) => FromJSON (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

parseJSON :: Value -> Parser (Vector d r) #

parseJSONList :: Value -> Parser [Vector d r] #

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

Defined in Data.Geometry.Vector.VectorFamily

Methods

rnf :: Vector d r -> () #

Arity d => Ixed (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

Methods

ix :: Index (Vector d r) -> Traversal' (Vector d r) (IxValue (Vector d r)) #

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

Defined in Data.Geometry.Transformation

Methods

transformBy :: Transformation (Dimension (Vector d r)) (NumType (Vector d r)) -> Vector d r -> Vector d r Source #

type Dim (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

type Dim (Vector d) = FromPeano (Peano d)
type Diff (Vector d) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

type Diff (Vector d) = Vector d
type Index (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

type Index (Vector d r) = Int
type IxValue (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector.VectorFamily

type IxValue (Vector d r) = r
type NumType (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector

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

Defined in Data.Geometry.Vector

type Dimension (Vector d r) = d

pattern Vector4 :: r -> r -> r -> r -> Vector 4 r Source #

pattern Vector3 :: r -> r -> r -> Vector 3 r Source #

pattern Vector2 :: r -> r -> Vector 2 r Source #

pattern Vector1 :: r -> Vector 1 r Source #

pattern Vector :: VectorFamilyF (Peano d) r -> Vector d r Source #

unV :: Lens (Vector d r) (Vector d s) (VectorFamily (Peano d) r) (VectorFamily (Peano d) s) Source #

readVec :: forall d r. (Arity d, Read r) => ReadP (Vector d r) Source #

vectorFromList :: Arity d => [r] -> Maybe (Vector d r) Source #

destruct :: (Arity d, Arity (d + 1)) => Vector (d + 1) r -> (r, Vector d r) Source #

head :: (Arity d, 1 <= d) => Vector d r -> r Source #

element :: forall proxy i d r. (Arity d, KnownNat i, (i + 1) <= d) => proxy i -> Lens' (Vector d r) r Source #

Lens into the i th element

element' :: forall d r. Arity d => Int -> Traversal' (Vector d r) r Source #

Similar to element above. Except that we don't have a static guarantee that the index is in bounds. Hence, we can only return a Traversal

cons :: (Arity d, Arity (d + 1)) => r -> Vector d r -> Vector (d + 1) r Source #

snoc :: (Arity (d + 1), Arity d) => Vector d r -> r -> Vector (d + 1) r Source #

Add an element at the back of the vector

init :: (Arity d, Arity (d + 1)) => Vector (d + 1) r -> Vector d r Source #

Get a vector of the first d - 1 elements.

prefix :: forall i d r. (Arity d, Arity i, i <= d) => Vector d r -> Vector i r Source #

Get a prefix of i elements of a vector

cross :: Num r => Vector 3 r -> Vector 3 r -> Vector 3 r Source #

Cross product of two three-dimensional vectors

isScalarMultipleOf :: (Eq r, Fractional r, Arity d) => Vector d r -> Vector d r -> Bool Source #

'isScalarmultipleof u v' test if v is a scalar multiple of u.

>>> Vector2 1 1 `isScalarMultipleOf` Vector2 10 10
True
>>> Vector3 1 1 2 `isScalarMultipleOf` Vector3 10 10 20
True
>>> Vector2 1 1 `isScalarMultipleOf` Vector2 10 1
False
>>> Vector2 1 1 `isScalarMultipleOf` Vector2 (-1) (-1)
True
>>> Vector2 1 1 `isScalarMultipleOf` Vector2 11.1 11.1
True
>>> Vector2 1 1 `isScalarMultipleOf` Vector2 11.1 11.2
False
>>> Vector2 2 1 `isScalarMultipleOf` Vector2 11.1 11.2
False
>>> Vector2 2 1 `isScalarMultipleOf` Vector2 4 2
True
>>> Vector2 2 1 `isScalarMultipleOf` Vector2 4 0
False
>>> Vector3 2 1 0 `isScalarMultipleOf` Vector3 4 0 5
False
>>> Vector3 0 0 0 `isScalarMultipleOf` Vector3 4 0 5
True

scalarMultiple :: (Eq r, Fractional r, Arity d) => Vector d r -> Vector d r -> Maybe r Source #

scalarMultiple u v computes the scalar labmda s.t. v = lambda * u (if it exists)

xComponent :: (1 <= d, Arity d) => Lens' (Vector d r) r Source #

yComponent :: (2 <= d, Arity d) => Lens' (Vector d r) r Source #

zComponent :: (3 <= d, Arity d) => Lens' (Vector d r) r Source #

newtype PolyLine d p r Source #

A Poly line in R^d has at least 2 vertices

Constructors

PolyLine 

Fields

Instances
Arity d => Bifunctor (PolyLine d) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

bimap :: (a -> b) -> (c -> d0) -> PolyLine d a c -> PolyLine d b d0 #

first :: (a -> b) -> PolyLine d a c -> PolyLine d b c #

second :: (b -> c) -> PolyLine d a b -> PolyLine d a c #

Arity d => Bitraversable (PolyLine d) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d0) -> PolyLine d a b -> f (PolyLine d c d0) #

Arity d => Bifoldable (PolyLine d) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

bifold :: Monoid m => PolyLine d m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> PolyLine d a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> PolyLine d a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> PolyLine d a b -> c #

Arity d => Functor (PolyLine d p) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

fmap :: (a -> b) -> PolyLine d p a -> PolyLine d p b #

(<$) :: a -> PolyLine d p b -> PolyLine d p a #

PointFunctor (PolyLine d p) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

pmap :: (Point (Dimension (PolyLine d p r)) r -> Point (Dimension (PolyLine d p s)) s) -> PolyLine d p r -> PolyLine d p s Source #

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

Defined in Data.Geometry.PolyLine

Methods

(==) :: PolyLine d p r -> PolyLine d p r -> Bool #

(/=) :: PolyLine d p r -> PolyLine d p r -> Bool #

(Ord r, Ord p, Arity d) => Ord (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

compare :: PolyLine d p r -> PolyLine d p r -> Ordering #

(<) :: PolyLine d p r -> PolyLine d p r -> Bool #

(<=) :: PolyLine d p r -> PolyLine d p r -> Bool #

(>) :: PolyLine d p r -> PolyLine d p r -> Bool #

(>=) :: PolyLine d p r -> PolyLine d p r -> Bool #

max :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r #

min :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r #

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

Defined in Data.Geometry.PolyLine

Methods

showsPrec :: Int -> PolyLine d p r -> ShowS #

show :: PolyLine d p r -> String #

showList :: [PolyLine d p r] -> ShowS #

Generic (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Associated Types

type Rep (PolyLine d p r) :: Type -> Type #

Methods

from :: PolyLine d p r -> Rep (PolyLine d p r) x #

to :: Rep (PolyLine d p r) x -> PolyLine d p r #

Semigroup (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

(<>) :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r #

sconcat :: NonEmpty (PolyLine d p r) -> PolyLine d p r #

stimes :: Integral b => b -> PolyLine d p r -> PolyLine d p r #

(ToJSON p, ToJSON r, Arity d) => ToJSON (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

toJSON :: PolyLine d p r -> Value #

toEncoding :: PolyLine d p r -> Encoding #

toJSONList :: [PolyLine d p r] -> Value #

toEncodingList :: [PolyLine d p r] -> Encoding #

(FromJSON p, FromJSON r, Arity d, KnownNat d) => FromJSON (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

parseJSON :: Value -> Parser (PolyLine d p r) #

parseJSONList :: Value -> Parser [PolyLine d p r] #

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

Defined in Data.Geometry.PolyLine

Methods

transformBy :: Transformation (Dimension (PolyLine d p r)) (NumType (PolyLine d p r)) -> PolyLine d p r -> PolyLine d p r Source #

Arity d => IsBoxable (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

boundingBox :: PolyLine d p r -> Box (Dimension (PolyLine d p r)) () (NumType (PolyLine d p r)) Source #

type Rep (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type Rep (PolyLine d p r) = D1 (MetaData "PolyLine" "Data.Geometry.PolyLine" "hgeometry-0.11.0.0-5Q7X7STHtn33ZJbJEL0QVy" True) (C1 (MetaCons "PolyLine" PrefixI True) (S1 (MetaSel (Just "_points") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LSeq 2 (Point d r :+ p)))))
type NumType (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

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

Defined in Data.Geometry.PolyLine

type Dimension (PolyLine d p r) = d

points :: forall d p r d p r. Iso (PolyLine d p r) (PolyLine d p r) (LSeq 2 ((:+) (Point d r) p)) (LSeq 2 ((:+) (Point d r) p)) Source #

fromPointsUnsafe :: [Point d r :+ p] -> PolyLine d p r Source #

pre: The input list contains at least two points

fromPointsUnsafe' :: Monoid p => [Point d r] -> PolyLine d p r Source #

pre: The input list contains at least two points. All extra vields are initialized with mempty.

fromLineSegment :: LineSegment d p r -> PolyLine d p r Source #

We consider the line-segment as closed.

asLineSegment :: PolyLine d p r -> LineSegment d p r Source #

Convert to a closed line segment by taking the first two points.

asLineSegment' :: PolyLine d p r -> Maybe (LineSegment d p r) Source #

Stricter version of asLineSegment that fails if the Polyline contains more than two points.

edgeSegments :: Arity d => PolyLine d p r -> LSeq 1 (LineSegment d p r) Source #

Computes the edges, as linesegments, of an LSeq

interpolatePoly :: (RealFrac r, Arity d) => r -> PolyLine d p r -> Point d r Source #

Linearly interpolate the polyline with a value in the range \([0,n-1]\), where \(n\) is the number of vertices of the polyline.

running time: \(O(\log n)\)

>>> interpolatePoly 0.5 myPolyLine
Point2 [5.0,5.0]
>>> interpolatePoly 1.5 myPolyLine
Point2 [10.0,15.0]

type SomePolygon p r = Either (Polygon Simple p r) (Polygon Multi p r) Source #

Either a simple or multipolygon

data Polygon (t :: PolygonType) p r where Source #

Constructors

SimplePolygon :: CSeq (Point 2 r :+ p) -> Polygon Simple p r 
MultiPolygon :: CSeq (Point 2 r :+ p) -> [Polygon Simple p r] -> Polygon Multi p r 
Instances
Bifunctor (Polygon t) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

bimap :: (a -> b) -> (c -> d) -> Polygon t a c -> Polygon t b d #

first :: (a -> b) -> Polygon t a c -> Polygon t b c #

second :: (b -> c) -> Polygon t a b -> Polygon t a c #

Bitraversable (Polygon t) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Polygon t a b -> f (Polygon t c d) #

Bifoldable (Polygon t) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

bifold :: Monoid m => Polygon t m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Polygon t a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Polygon t a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Polygon t a b -> c #

PointFunctor (Polygon t p) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

pmap :: (Point (Dimension (Polygon t p r)) r -> Point (Dimension (Polygon t p s)) s) -> Polygon t p r -> Polygon t p s Source #

(Fractional r, Ord r) => IsIntersectableWith (Point 2 r) (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

intersect :: Point 2 r -> Polygon t p r -> Intersection (Point 2 r) (Polygon t p r) #

intersects :: Point 2 r -> Polygon t p r -> Bool #

nonEmptyIntersection :: proxy (Point 2 r) -> proxy (Polygon t p r) -> Intersection (Point 2 r) (Polygon t p r) -> Bool #

(Eq p, Eq r) => Eq (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

(==) :: Polygon t p r -> Polygon t p r -> Bool #

(/=) :: Polygon t p r -> Polygon t p r -> Bool #

(Show p, Show r) => Show (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

showsPrec :: Int -> Polygon t p r -> ShowS #

show :: Polygon t p r -> String #

showList :: [Polygon t p r] -> ShowS #

(NFData p, NFData r) => NFData (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

rnf :: Polygon t p r -> () #

Fractional r => IsTransformable (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

transformBy :: Transformation (Dimension (Polygon t p r)) (NumType (Polygon t p r)) -> Polygon t p r -> Polygon t p r Source #

IsBoxable (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

boundingBox :: Polygon t p r -> Box (Dimension (Polygon t p r)) () (NumType (Polygon t p r)) Source #

type NumType (SomePolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

type NumType (SomePolygon p r) = r
type Dimension (SomePolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

type Dimension (SomePolygon p r) = 2
type IntersectionOf (Line 2 r) (Boundary (Polygon t p r)) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

type IntersectionOf (Line 2 r) (Boundary (Polygon t p r)) = Seq (Either (Point 2 r) (LineSegment 2 () r)) ': ([] :: [Type])
type IntersectionOf (Point 2 r) (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

type IntersectionOf (Point 2 r) (Polygon t p r) = NoIntersection ': (Point 2 r ': ([] :: [Type]))
type NumType (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

type NumType (Polygon t p r) = r
type Dimension (Polygon t p r) Source #

Polygons are per definition 2 dimensional

Instance details

Defined in Data.Geometry.Polygon.Core

type Dimension (Polygon t p r) = 2

data PolygonType Source #

We distinguish between simple polygons (without holes) and Polygons with holes.

Constructors

Simple 
Multi 

_SimplePolygon :: Prism' (Polygon Simple p r) (CSeq (Point 2 r :+ p)) Source #

Prism to test if we are a simple polygon

_MultiPolygon :: Prism' (Polygon Multi p r) (CSeq (Point 2 r :+ p), [Polygon Simple p r]) Source #

Prism to test if we are a Multi polygon

outerBoundary :: forall t p r. Lens' (Polygon t p r) (CSeq (Point 2 r :+ p)) Source #

polygonHoles :: forall p r. Lens' (Polygon Multi p r) [Polygon Simple p r] Source #

outerVertex :: Int -> Lens' (Polygon t p r) (Point 2 r :+ p) Source #

Access the i^th vertex on the outer boundary

holeList :: Polygon t p r -> [Polygon Simple p r] Source #

Get all holes in a polygon

polygonVertices :: Polygon t p r -> NonEmpty (Point 2 r :+ p) Source #

The vertices in the polygon. No guarantees are given on the order in which they appear!

outerBoundaryEdges :: Polygon t p r -> CSeq (LineSegment 2 p r) Source #

The edges along the outer boundary of the polygon. The edges are half open.

running time: \(O(n)\)

listEdges :: Polygon t p r -> [LineSegment 2 p r] Source #

Lists all edges. The edges on the outer boundary are given before the ones on the holes. However, no other guarantees are given on the order.

running time: \(O(n)\)

withIncidentEdges :: Polygon t p r -> Polygon t (Two (LineSegment 2 p r)) r Source #

Pairs every vertex with its incident edges. The first one is its predecessor edge, the second one its successor edge (in terms of the ordering along the boundary).

>>> mapM_ print . polygonVertices $ withIncidentEdges simplePoly
Point2 [0,0] :+ V2 LineSegment (Closed (Point2 [1,11] :+ ())) (Closed (Point2 [0,0] :+ ())) LineSegment (Closed (Point2 [0,0] :+ ())) (Closed (Point2 [10,0] :+ ()))
Point2 [10,0] :+ V2 LineSegment (Closed (Point2 [0,0] :+ ())) (Closed (Point2 [10,0] :+ ())) LineSegment (Closed (Point2 [10,0] :+ ())) (Closed (Point2 [10,10] :+ ()))
Point2 [10,10] :+ V2 LineSegment (Closed (Point2 [10,0] :+ ())) (Closed (Point2 [10,10] :+ ())) LineSegment (Closed (Point2 [10,10] :+ ())) (Closed (Point2 [5,15] :+ ()))
Point2 [5,15] :+ V2 LineSegment (Closed (Point2 [10,10] :+ ())) (Closed (Point2 [5,15] :+ ())) LineSegment (Closed (Point2 [5,15] :+ ())) (Closed (Point2 [1,11] :+ ()))
Point2 [1,11] :+ V2 LineSegment (Closed (Point2 [5,15] :+ ())) (Closed (Point2 [1,11] :+ ())) LineSegment (Closed (Point2 [1,11] :+ ())) (Closed (Point2 [0,0] :+ ()))

onBoundary :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool Source #

Test if q lies on the boundary of the polygon. Running time: O(n)

>>> Point2 1 1 `onBoundary` simplePoly
False
>>> Point2 0 0 `onBoundary` simplePoly
True
>>> Point2 10 0 `onBoundary` simplePoly
True
>>> Point2 5 13 `onBoundary` simplePoly
False
>>> Point2 5 10 `onBoundary` simplePoly
False
>>> Point2 10 5 `onBoundary` simplePoly
True
>>> Point2 20 5 `onBoundary` simplePoly
False

TODO: testcases multipolygon

inPolygon :: forall t p r. (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> PointLocationResult Source #

Check if a point lies inside a polygon, on the boundary, or outside of the polygon. Running time: O(n).

>>> Point2 1 1 `inPolygon` simplePoly
Inside
>>> Point2 0 0 `inPolygon` simplePoly
OnBoundary
>>> Point2 10 0 `inPolygon` simplePoly
OnBoundary
>>> Point2 5 13 `inPolygon` simplePoly
Inside
>>> Point2 5 10 `inPolygon` simplePoly
Inside
>>> Point2 10 5 `inPolygon` simplePoly
OnBoundary
>>> Point2 20 5 `inPolygon` simplePoly
Outside

TODO: Add some testcases with multiPolygons TODO: Add some more onBoundary testcases

insidePolygon :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool Source #

Test if a point lies strictly inside the polgyon.

area :: Fractional r => Polygon t p r -> r Source #

Compute the area of a polygon

signedArea :: Fractional r => SimplePolygon p r -> r Source #

Compute the signed area of a simple polygon. The the vertices are in clockwise order, the signed area will be negative, if the verices are given in counter clockwise order, the area will be positive.

centroid :: Fractional r => SimplePolygon p r -> Point 2 r Source #

Compute the centroid of a simple polygon.

pickPoint :: (Ord r, Fractional r) => Polygon p t r -> Point 2 r Source #

Pick a point that is inside the polygon.

(note: if the polygon is degenerate; i.e. has <3 vertices, we report a vertex of the polygon instead.)

pre: the polygon is given in CCW order

running time: \(O(n)\)

isTriangle :: Polygon p t r -> Bool Source #

Test if the polygon is a triangle

running time: \(O(1)\)

findDiagonal :: (Ord r, Fractional r) => Polygon t p r -> LineSegment 2 p r Source #

Find a diagonal of the polygon.

pre: the polygon is given in CCW order

running time: \(O(n)\)

isCounterClockwise :: (Eq r, Fractional r) => Polygon t p r -> Bool Source #

Test if the outer boundary of the polygon is in clockwise or counter clockwise order.

running time: \(O(n)\)

toClockwiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #

Make sure that every edge has the polygon's interior on its right, by orienting the outer boundary into clockwise order, and the inner borders (i.e. any holes, if they exist) into counter-clockwise order.

running time: \(O(n)\) | Orient the outer boundary of the polygon to clockwise order

toClockwiseOrder' :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #

Orient the outer boundary into clockwise order. Leaves any holes as they are.

toCounterClockWiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #

Make sure that every edge has the polygon's interior on its left, by orienting the outer boundary into counter-clockwise order, and the inner borders (i.e. any holes, if they exist) into clockwise order.

running time: \(O(n)\)

toCounterClockWiseOrder' :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #

Orient the outer boundary into counter-clockwise order. Leaves any holes as they are.

asSimplePolygon :: Polygon t p r -> SimplePolygon p r Source #

Convert a Polygon to a simple polygon by forgetting about any holes.

numberVertices :: Polygon t p r -> Polygon t (SP Int p) r Source #

assigns unique integer numbers to all vertices. Numbers start from 0, and are increasing along the outer boundary. The vertices of holes will be numbered last, in the same order.

>>> numberVertices simplePoly
SimplePolygon (CSeq [Point2 [0,0] :+ SP 0 (),Point2 [10,0] :+ SP 1 (),Point2 [10,10] :+ SP 2 (),Point2 [5,15] :+ SP 3 (),Point2 [1,11] :+ SP 4 ()])

cmpExtreme :: (Num r, Ord r) => Vector 2 r -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering Source #

Comparison that compares which point is larger in the direction given by the vector u.

extremesLinear :: (Ord r, Num r) => Vector 2 r -> Polygon t p r -> (Point 2 r :+ p, Point 2 r :+ p) Source #

Finds the extreme points, minimum and maximum, in a given direction

running time: \(O(n)\)

isStarShaped :: (MonadRandom m, Ord r, Fractional r) => SimplePolygon p r -> m (Maybe (Point 2 r)) Source #

Test if a Simple polygon is star-shaped. Returns a point in the kernel (i.e. from which the entire polygon is visible), if it exists.

\(O(n)\) expected time