| Copyright | 2014 Edward Kmett Charles Durham [2015..2018] Trevor L. McDonell |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Array.Accelerate.Linear.Plucker
Description
Plücker coordinates for lines in 3d homogeneous space.
- data Plucker a :: * -> * = Plucker !a !a !a !a !a !a
- squaredError :: forall a. Num a => Exp (Plucker a) -> Exp a
- isotropic :: Epsilon a => Exp (Plucker a) -> Exp Bool
- (><) :: forall a. Num a => Exp (Plucker a) -> Exp (Plucker a) -> Exp a
- plucker :: forall a. Num a => Exp (V4 a) -> Exp (V4 a) -> Exp (Plucker a)
- plucker3D :: forall a. Num a => Exp (V3 a) -> Exp (V3 a) -> Exp (Plucker a)
- data LinePass :: *
- parallel :: Epsilon a => Exp (Plucker a) -> Exp (Plucker a) -> Exp Bool
- intersects :: (Epsilon a, Ord a) => Exp (Plucker a) -> Exp (Plucker a) -> Exp Bool
- passes :: (Epsilon a, Ord a) => Exp (Plucker a) -> Exp (Plucker a) -> Exp LinePass
- quadranceToOrigin :: Fractional a => Exp (Plucker a) -> Exp a
- closestToOrigin :: Fractional a => Exp (Plucker a) -> Exp (V3 a)
- isLine :: Epsilon a => Exp (Plucker a) -> Exp Bool
- p01 :: Elt a => Lens' (Exp (Plucker a)) (Exp a)
- p02 :: Elt a => Lens' (Exp (Plucker a)) (Exp a)
- p03 :: Elt a => Lens' (Exp (Plucker a)) (Exp a)
- p10 :: Num a => Lens' (Exp (Plucker a)) (Exp a)
- p12 :: Elt a => Lens' (Exp (Plucker a)) (Exp a)
- p13 :: Num a => Lens' (Exp (Plucker a)) (Exp a)
- p20 :: Num a => Lens' (Exp (Plucker a)) (Exp a)
- p21 :: Num a => Lens' (Exp (Plucker a)) (Exp a)
- p23 :: Elt a => Lens' (Exp (Plucker a)) (Exp a)
- p30 :: Num a => Lens' (Exp (Plucker a)) (Exp a)
- p31 :: Elt a => Lens' (Exp (Plucker a)) (Exp a)
- p32 :: Num a => Lens' (Exp (Plucker a)) (Exp a)
Documentation
Plücker coordinates for lines in a 3-dimensional space.
Constructors
| Plucker !a !a !a !a !a !a |
Instances
squaredError :: forall a. Num a => Exp (Plucker a) -> Exp a Source #
Valid Plücker coordinates p will have squaredError p == 0
That said, floating point makes a mockery of this claim, so you may want to
use nearZero.
isotropic :: Epsilon a => Exp (Plucker a) -> Exp Bool Source #
Checks if the line is near-isotropic (isotropic vectors in this quadratic space represent lines in real 3D space).
(><) :: forall a. Num a => Exp (Plucker a) -> Exp (Plucker a) -> Exp a infixl 5 Source #
This isn't the actual metric because this bilinear form gives rise to an isotropic quadratic space.
plucker :: forall a. Num a => Exp (V4 a) -> Exp (V4 a) -> Exp (Plucker a) Source #
Given a pair of points represented by homogeneous coordinates generate Plücker coordinates for the line through them, directed from the second towards the first.
plucker3D :: forall a. Num a => Exp (V3 a) -> Exp (V3 a) -> Exp (Plucker a) Source #
Given a pair of 3D points, generate Plücker coordinates for the line through them, directed from the second towards the first.
operations on lines
Describe how two lines pass each other.
Constructors
| Coplanar | The lines are coplanar (parallel or intersecting). |
| Clockwise | The lines pass each other clockwise (right-handed screw) |
| Counterclockwise | The lines pass each other counterclockwise (left-handed screw). |
parallel :: Epsilon a => Exp (Plucker a) -> Exp (Plucker a) -> Exp Bool Source #
Checks if two lines are parallel.
intersects :: (Epsilon a, Ord a) => Exp (Plucker a) -> Exp (Plucker a) -> Exp Bool Source #
Checks if two lines intersect (or nearly intersect).
passes :: (Epsilon a, Ord a) => Exp (Plucker a) -> Exp (Plucker a) -> Exp LinePass Source #
Check how two lines pass each other. passes l1 l2 describes l2 when
looking down l1.
quadranceToOrigin :: Fractional a => Exp (Plucker a) -> Exp a Source #
The minimum squared distance of a line from the origin.
closestToOrigin :: Fractional a => Exp (Plucker a) -> Exp (V3 a) Source #
The point where a line is closest to the origin.
isLine :: Epsilon a => Exp (Plucker a) -> Exp Bool Source #
Not all 6-dimensional points correspond to a line in 3D. This predicate tests that a Plücker coordinate lies on the Grassmann manifold, and does indeed represent a 3D line.
Basis elements
p10 :: Num a => Lens' (Exp (Plucker a)) (Exp a) Source #
These elements form an alternate basis for the Plücker space, or the
Grassmanian manifold Gr(2,V4).
p10::Numa =>Lens'(Pluckera) ap20::Numa =>Lens'(Pluckera) ap30::Numa =>Lens'(Pluckera) ap32::Numa =>Lens'(Pluckera) ap13::Numa =>Lens'(Pluckera) ap21::Numa =>Lens'(Pluckera) a
p13 :: Num a => Lens' (Exp (Plucker a)) (Exp a) Source #
These elements form an alternate basis for the Plücker space, or the
Grassmanian manifold Gr(2,V4).
p10::Numa =>Lens'(Pluckera) ap20::Numa =>Lens'(Pluckera) ap30::Numa =>Lens'(Pluckera) ap32::Numa =>Lens'(Pluckera) ap13::Numa =>Lens'(Pluckera) ap21::Numa =>Lens'(Pluckera) a
p20 :: Num a => Lens' (Exp (Plucker a)) (Exp a) Source #
These elements form an alternate basis for the Plücker space, or the
Grassmanian manifold Gr(2,V4).
p10::Numa =>Lens'(Pluckera) ap20::Numa =>Lens'(Pluckera) ap30::Numa =>Lens'(Pluckera) ap32::Numa =>Lens'(Pluckera) ap13::Numa =>Lens'(Pluckera) ap21::Numa =>Lens'(Pluckera) a
p21 :: Num a => Lens' (Exp (Plucker a)) (Exp a) Source #
These elements form an alternate basis for the Plücker space, or the
Grassmanian manifold Gr(2,V4).
p10::Numa =>Lens'(Pluckera) ap20::Numa =>Lens'(Pluckera) ap30::Numa =>Lens'(Pluckera) ap32::Numa =>Lens'(Pluckera) ap13::Numa =>Lens'(Pluckera) ap21::Numa =>Lens'(Pluckera) a
p30 :: Num a => Lens' (Exp (Plucker a)) (Exp a) Source #
These elements form an alternate basis for the Plücker space, or the
Grassmanian manifold Gr(2,V4).
p10::Numa =>Lens'(Pluckera) ap20::Numa =>Lens'(Pluckera) ap30::Numa =>Lens'(Pluckera) ap32::Numa =>Lens'(Pluckera) ap13::Numa =>Lens'(Pluckera) ap21::Numa =>Lens'(Pluckera) a
p32 :: Num a => Lens' (Exp (Plucker a)) (Exp a) Source #
These elements form an alternate basis for the Plücker space, or the
Grassmanian manifold Gr(2,V4).
p10::Numa =>Lens'(Pluckera) ap20::Numa =>Lens'(Pluckera) ap30::Numa =>Lens'(Pluckera) ap32::Numa =>Lens'(Pluckera) ap13::Numa =>Lens'(Pluckera) ap21::Numa =>Lens'(Pluckera) a
Orphan instances
| Eq LinePass Source # | |
| Functor Plucker Source # | |
| Elt LinePass Source # | |
| Additive Plucker Source # | |
| Metric Plucker Source # | |
| cst a => IsProduct cst (Plucker a) Source # | |
| (Lift Exp a, Elt (Plain a)) => Lift Exp (Plucker a) Source # | |
| Elt a => Unlift Exp (Plucker (Exp a)) Source # | |
| Floating a => Floating (Exp (Plucker a)) Source # | |
| Fractional a => Fractional (Exp (Plucker a)) Source # | |
| Num a => Num (Exp (Plucker a)) Source # | |
| Ord a => Ord (Plucker a) Source # | |
| Eq a => Eq (Plucker a) Source # | |
| Elt a => Elt (Plucker a) Source # | |
| Epsilon a => Epsilon (Plucker a) Source # | |
| (Elt a, Elt b) => Each (Exp (Plucker a)) (Exp (Plucker b)) (Exp a) (Exp b) Source # | |