----------------------------------------------------------------------------- -- | -- Module : Linear.Plucker -- Copyright : (C) 2012-2013 Edward Kmett, -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : non-portable -- -- Plücker coordinates for lines in 3d homogeneous space. ---------------------------------------------------------------------------- module Linear.Plucker ( Plucker(..) , squaredError , isotropic , (><) , plucker , intersects ) where import Control.Applicative import Data.Distributive import Data.Foldable as Foldable import Data.Monoid import Data.Traversable import Linear.Epsilon import GHC.Arr (Ix(..)) import Linear.Metric import Control.Lens import Linear.V4 -- | Plücker coordinates for lines in a 3-dimensional space. data Plucker a = Plucker a a a a a a deriving (Eq,Ord,Show,Read) instance Functor Plucker where fmap g (Plucker a b c d e f) = Plucker (g a) (g b) (g c) (g d) (g e) (g f) {-# INLINE fmap #-} instance Applicative Plucker where pure a = Plucker a a a a a a {-# INLINE pure #-} Plucker a b c d e f <*> Plucker g h i j k l = Plucker (a g) (b h) (c i) (d j) (e k) (f l) {-# INLINE (<*>) #-} instance Monad Plucker where return a = Plucker a a a a a a {-# INLINE return #-} (>>=) = bindRep {-# INLINE (>>=) #-} instance Distributive Plucker where distribute = distributeRep {-# INLINE distribute #-} instance Representable Plucker where rep f = Plucker (f p01) (f p02) (f p03) (f p23) (f p31) (f p12) {-# INLINE rep #-} instance Foldable Plucker where foldMap g (Plucker a b c d e f) = g a `mappend` g b `mappend` g c `mappend` g d `mappend` g e `mappend` g f {-# INLINE foldMap #-} instance Traversable Plucker where traverse g (Plucker a b c d e f) = Plucker <$> g a <*> g b <*> g c <*> g d <*> g e <*> g f {-# INLINE traverse #-} instance Ix a => Ix (Plucker a) where range (Plucker l1 l2 l3 l4 l5 l6,Plucker u1 u2 u3 u4 u5 u6) = [Plucker i1 i2 i3 i4 i5 i6 | i1 <- range (l1,u1) , i2 <- range (l2,u2) , i3 <- range (l3,u3) , i4 <- range (l4,u4) , i5 <- range (l5,u5) , i6 <- range (l6,u6) ] {-# INLINE range #-} unsafeIndex (Plucker l1 l2 l3 l4 l5 l6,Plucker u1 u2 u3 u4 u5 u6) (Plucker i1 i2 i3 i4 i5 i6) = unsafeIndex (l6,u6) i6 + unsafeRangeSize (l6,u6) * ( unsafeIndex (l5,u5) i5 + unsafeRangeSize (l5,u5) * ( unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * ( unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * ( unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * ( unsafeIndex (l1,u1) i1))))) {-# INLINE unsafeIndex #-} inRange (Plucker l1 l2 l3 l4 l5 l6,Plucker u1 u2 u3 u4 u5 u6) (Plucker i1 i2 i3 i4 i5 i6) = inRange (l1,u1) i1 && inRange (l2,u2) i2 && inRange (l3,u3) i3 && inRange (l4,u4) i4 && inRange (l5,u5) i5 && inRange (l6,u6) i6 {-# INLINE inRange #-} instance Num a => Num (Plucker a) where (+) = liftA2 (+) {-# INLINE (+) #-} (-) = liftA2 (-) {-# INLINE (-) #-} (*) = liftA2 (*) {-# INLINE (*) #-} negate = fmap negate {-# INLINE negate #-} abs = fmap abs {-# INLINE abs #-} signum = fmap signum {-# INLINE signum #-} fromInteger = pure . fromInteger {-# INLINE fromInteger #-} instance Fractional a => Fractional (Plucker a) where recip = fmap recip {-# INLINE recip #-} (/) = liftA2 (/) {-# INLINE (/) #-} fromRational = pure . fromRational {-# INLINE fromRational #-} -- | Given a pair of points represented by homogeneous coordinates generate Plücker coordinates -- for the line through them. plucker :: Num a => V4 a -> V4 a -> Plucker a plucker (V4 a b c d) (V4 e f g h) = Plucker (a*f-b*e) (a*g-c*e) (a*d-h*e) (c*h-d*g) (d*f-b*h) (b*g-c*f) {-# INLINE plucker #-} -- | These elements form a basis for the Plücker space, or the Grassmanian manifold @Gr(2,V4)@. p01, p02, p03, p23, p31, p12 :: Functor f => (a -> f a) -> Plucker a -> f (Plucker a) p01 g (Plucker a b c d e f) = (\a' -> Plucker a' b c d e f) <$> g a p02 g (Plucker a b c d e f) = (\b' -> Plucker a b' c d e f) <$> g b p03 g (Plucker a b c d e f) = (\c' -> Plucker a b c' d e f) <$> g c p23 g (Plucker a b c d e f) = (\d' -> Plucker a b c d' e f) <$> g d p31 g (Plucker a b c d e f) = (\e' -> Plucker a b c d e' f) <$> g e p12 g (Plucker a b c d e f) = Plucker a b c d e <$> g f {-# INLINE p01 #-} {-# INLINE p02 #-} {-# INLINE p03 #-} {-# INLINE p23 #-} {-# INLINE p31 #-} {-# INLINE p12 #-} -- | 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'. squaredError :: (Eq a, Num a) => Plucker a -> a squaredError v = v >< v {-# INLINE squaredError #-} -- | This isn't th actual metric because this bilinear form gives rise to an isotropic quadratic space infixl 5 >< (><) :: Num a => Plucker a -> Plucker a -> a Plucker a b c d e f >< Plucker g h i j k l = a*g+b*h+c*i-d*j-e*k-f*l {-# INLINE (><) #-} -- | Checks if the line is near-isotropic (isotropic vectors in this quadratic space represent lines in real 3d space) isotropic :: Epsilon a => Plucker a -> Bool isotropic a = nearZero (a >< a) {-# INLINE isotropic #-} -- | Checks if the two vectors intersect (or nearly intersect) intersects :: Epsilon a => Plucker a -> Plucker a -> Bool intersects a b = nearZero (a >< b) {-# INLINE intersects #-} instance Metric Plucker where dot (Plucker a b c d e f) (Plucker g h i j k l) = a*g+b*h+c*i+d*j+e*k+f*l {-# INLINE dot #-} instance Epsilon a => Epsilon (Plucker a) where nearZero = nearZero . quadrance {-# INLINE nearZero #-} -- TODO: drag some more stuff out of my thesis