License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Operations on affine spaces.
Synopsis
- class Additive (Diff p) => Affine p where
- qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a
- distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a
- newtype Point f a = P (f a)
- lensP :: Lens (Point f a) (Point g b) (f a) (g b)
- _Point :: Iso (Point f a) (Point g b) (f a) (g b)
- (.#) :: Coercible b a => (b -> c) -> (a -> b) -> a -> c
- (#.) :: Coercible c b => (b -> c) -> (a -> b) -> a -> c
- unP :: Point f a -> f a
- origin :: (Additive f, Num a) => Point f a
- relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a)
Documentation
class Additive (Diff p) => Affine p where Source #
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@
(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 Source #
Get the difference between two points as a vector offset.
(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 Source #
Add a vector offset to a point.
(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 Source #
Subtract a vector offset from a point.
Instances
Affine ZipList Source # | |
Affine Complex Source # | |
Affine Identity Source # | |
Affine IntMap Source # | |
Affine Plucker Source # | |
Affine Quaternion Source # | |
Defined in Linear.Affine (.-.) :: Num a => Quaternion a -> Quaternion a -> Diff Quaternion a Source # (.+^) :: Num a => Quaternion a -> Diff Quaternion a -> Quaternion a Source # (.-^) :: Num a => Quaternion a -> Diff Quaternion a -> Quaternion a Source # | |
Affine V0 Source # | |
Affine V1 Source # | |
Affine V2 Source # | |
Affine V3 Source # | |
Affine V4 Source # | |
Affine Vector Source # | |
Affine Maybe Source # | |
Affine [] Source # | |
Ord k => Affine (Map k) Source # | |
Additive f => Affine (Point f) Source # | |
(Eq k, Hashable k) => Affine (HashMap k) Source # | |
Dim n => Affine (V n) Source # | |
(Affine f, Affine g) => Affine (Product f g) Source # | |
Defined in Linear.Affine | |
Affine ((->) b) Source # | |
qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a Source #
Compute the quadrance of the difference (the square of the distance)
distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a Source #
Distance between two points in an affine space
A handy wrapper to help distinguish points from vectors at the type level
P (f a) |
Instances
Generic1 (Point f :: Type -> Type) Source # | |
Unbox (f a) => Vector Vector (Point f a) Source # | |
Defined in Linear.Affine basicUnsafeFreeze :: Mutable Vector s (Point f a) -> ST s (Vector (Point f a)) # basicUnsafeThaw :: Vector (Point f a) -> ST s (Mutable Vector s (Point f a)) # basicLength :: Vector (Point f a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) # basicUnsafeIndexM :: Vector (Point f a) -> Int -> Box (Point f a) # basicUnsafeCopy :: Mutable Vector s (Point f a) -> Vector (Point f a) -> ST s () # | |
Unbox (f a) => MVector MVector (Point f a) Source # | |
Defined in Linear.Affine basicLength :: MVector s (Point f a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a) # basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Point f a)) # basicInitialize :: MVector s (Point f a) -> ST s () # basicUnsafeReplicate :: Int -> Point f a -> ST s (MVector s (Point f a)) # basicUnsafeRead :: MVector s (Point f a) -> Int -> ST s (Point f a) # basicUnsafeWrite :: MVector s (Point f a) -> Int -> Point f a -> ST s () # basicClear :: MVector s (Point f a) -> ST s () # basicSet :: MVector s (Point f a) -> Point f a -> ST s () # basicUnsafeCopy :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () # basicUnsafeMove :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () # basicUnsafeGrow :: MVector s (Point f a) -> Int -> ST s (MVector s (Point f a)) # | |
Representable f => Representable (Point f) Source # | |
Foldable f => Foldable (Point f) Source # | |
Defined in Linear.Affine fold :: Monoid m => Point f m -> m # foldMap :: Monoid m => (a -> m) -> Point f a -> m # foldMap' :: Monoid m => (a -> m) -> Point f a -> m # foldr :: (a -> b -> b) -> b -> Point f a -> b # foldr' :: (a -> b -> b) -> b -> Point f a -> b # foldl :: (b -> a -> b) -> b -> Point f a -> b # foldl' :: (b -> a -> b) -> b -> Point f a -> b # foldr1 :: (a -> a -> a) -> Point f a -> a # foldl1 :: (a -> a -> a) -> Point f a -> a # elem :: Eq a => a -> Point f a -> Bool # maximum :: Ord a => Point f a -> a # minimum :: Ord a => Point f a -> a # | |
Eq1 f => Eq1 (Point f) Source # | |
Ord1 f => Ord1 (Point f) Source # | |
Defined in Linear.Affine | |
Read1 f => Read1 (Point f) Source # | |
Defined in Linear.Affine | |
Show1 f => Show1 (Point f) Source # | |
Traversable f => Traversable (Point f) Source # | |
Applicative f => Applicative (Point f) Source # | |
Functor f => Functor (Point f) Source # | |
Monad f => Monad (Point f) Source # | |
Serial1 f => Serial1 (Point f) Source # | |
Defined in Linear.Affine serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () # deserializeWith :: MonadGet m => m a -> m (Point f a) # | |
Distributive f => Distributive (Point f) Source # | |
Hashable1 f => Hashable1 (Point f) Source # | |
Defined in Linear.Affine | |
Additive f => Affine (Point f) Source # | |
Metric f => Metric (Point f) Source # | |
Finite f => Finite (Point f) Source # | |
R1 f => R1 (Point f) Source # | |
R2 f => R2 (Point f) Source # | |
R3 f => R3 (Point f) Source # | |
R4 f => R4 (Point f) Source # | |
Additive f => Additive (Point f) Source # | |
Defined in Linear.Affine zero :: Num a => Point f a Source # (^+^) :: Num a => Point f a -> Point f a -> Point f a Source # (^-^) :: Num a => Point f a -> Point f a -> Point f a Source # lerp :: Num a => a -> Point f a -> Point f a -> Point f a Source # liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a Source # liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c Source # | |
Apply f => Apply (Point f) Source # | |
Bind f => Bind (Point f) Source # | |
(Typeable f, Typeable a, Data (f a)) => Data (Point f a) Source # | |
Defined in Linear.Affine gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point f a -> c (Point f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a) # toConstr :: Point f a -> Constr # dataTypeOf :: Point f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a)) # gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) # | |
Storable (f a) => Storable (Point f a) Source # | |
Defined in Linear.Affine | |
Monoid (f a) => Monoid (Point f a) Source # | |
Semigroup (f a) => Semigroup (Point f a) Source # | |
Generic (Point f a) Source # | |
Ix (f a) => Ix (Point f a) Source # | |
Defined in Linear.Affine range :: (Point f a, Point f a) -> [Point f a] # index :: (Point f a, Point f a) -> Point f a -> Int # unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int # inRange :: (Point f a, Point f a) -> Point f a -> Bool # rangeSize :: (Point f a, Point f a) -> Int # unsafeRangeSize :: (Point f a, Point f a) -> Int # | |
Num (f a) => Num (Point f a) Source # | |
Read (f a) => Read (Point f a) Source # | |
Fractional (f a) => Fractional (Point f a) Source # | |
Show (f a) => Show (Point f a) Source # | |
Binary (f a) => Binary (Point f a) Source # | |
Serial (f a) => Serial (Point f a) Source # | |
Defined in Linear.Affine | |
Serialize (f a) => Serialize (Point f a) Source # | |
NFData (f a) => NFData (Point f a) Source # | |
Defined in Linear.Affine | |
Eq (f a) => Eq (Point f a) Source # | |
Ord (f a) => Ord (Point f a) Source # | |
Defined in Linear.Affine | |
Hashable (f a) => Hashable (Point f a) Source # | |
Defined in Linear.Affine | |
Ixed (f a) => Ixed (Point f a) Source # | |
Defined in Linear.Affine | |
Wrapped (Point f a) Source # | |
Epsilon (f a) => Epsilon (Point f a) Source # | |
Random (f a) => Random (Point f a) Source # | |
Unbox (f a) => Unbox (Point f a) Source # | |
Defined in Linear.Affine | |
t ~ Point g b => Rewrapped (Point f a) t Source # | |
Defined in Linear.Affine | |
Traversable f => Each (Point f a) (Point f b) a b Source # | |
type Rep1 (Point f :: Type -> Type) Source # | |
newtype MVector s (Point f a) Source # | |
Defined in Linear.Affine | |
type Rep (Point f) Source # | |
Defined in Linear.Affine | |
type Diff (Point f) Source # | |
Defined in Linear.Affine | |
type Size (Point f) Source # | |
Defined in Linear.Affine | |
type Rep (Point f a) Source # | |
Defined in Linear.Affine | |
type Index (Point f a) Source # | |
Defined in Linear.Affine | |
type IxValue (Point f a) Source # | |
Defined in Linear.Affine | |
type Unwrapped (Point f a) Source # | |
Defined in Linear.Affine | |
newtype Vector (Point f a) Source # | |
Defined in Linear.Affine |