{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Linear.Metric
( Metric(..), normalize, project
) where
import Control.Applicative
import Data.Foldable as Foldable
import Data.Functor.Compose
import Data.Functor.Identity
import Data.Functor.Product
import Data.Vector (Vector)
import Data.IntMap (IntMap)
import Data.Map (Map)
import Data.HashMap.Strict (HashMap)
import Data.Hashable (Hashable)
import Linear.Epsilon
import Linear.Vector
class Additive f => Metric f where
dot :: Num a => f a -> f a -> a
#ifndef HLINT
default dot :: (Foldable f, Num a) => f a -> f a -> a
dot x y = Foldable.sum $ liftI2 (*) x y
#endif
quadrance :: Num a => f a -> a
quadrance v = dot v v
qd :: Num a => f a -> f a -> a
qd f g = quadrance (f ^-^ g)
distance :: Floating a => f a -> f a -> a
distance f g = norm (f ^-^ g)
norm :: Floating a => f a -> a
norm v = sqrt (quadrance v)
signorm :: Floating a => f a -> f a
signorm v = fmap (/m) v where
m = norm v
instance (Metric f, Metric g) => Metric (Product f g) where
dot (Pair a b) (Pair c d) = dot a c + dot b d
quadrance (Pair a b) = quadrance a + quadrance b
qd (Pair a b) (Pair c d) = qd a c + qd b d
distance p q = sqrt (qd p q)
instance (Metric f, Metric g) => Metric (Compose f g) where
dot (Compose a) (Compose b) = quadrance (liftI2 dot a b)
quadrance = quadrance . fmap quadrance . getCompose
qd (Compose a) (Compose b) = quadrance (liftI2 qd a b)
distance (Compose a) (Compose b) = norm (liftI2 qd a b)
instance Metric Identity where
dot (Identity x) (Identity y) = x * y
instance Metric []
instance Metric Maybe
instance Metric ZipList where
dot (ZipList x) (ZipList y) = dot x y
instance Metric IntMap
instance Ord k => Metric (Map k)
instance (Hashable k, Eq k) => Metric (HashMap k)
instance Metric Vector
normalize :: (Floating a, Metric f, Epsilon a) => f a -> f a
normalize v = if nearZero l || nearZero (1-l) then v else fmap (/sqrt l) v
where l = quadrance v
project :: (Metric v, Fractional a) => v a -> v a -> v a
project u v = ((v `dot` u) / quadrance u) *^ u