{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Numeric.AffineSpace
(
LeftTorsor(..)
, (.+^)
, (^+.)
, (.-.)
, (.-^)
, FractionalVectorSpace(..)
, AffineSpace
) where
import Numeric.Additive
class (AdditiveGroup (Diff t)) => LeftTorsor t where
type Diff t
add :: Diff t -> t -> t
diff :: t -> t -> Diff t
instance LeftTorsor Integer where
type Diff Integer = Integer
add :: Diff Integer -> Integer -> Integer
add = Integer -> Integer -> Integer
Diff Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(+)
diff :: Integer -> Integer -> Diff Integer
diff = (-)
{-# INLINE add #-}
{-# INLINE diff #-}
instance LeftTorsor Rational where
type Diff Rational = Rational
add :: Diff Rational -> Rational -> Rational
add = Rational -> Rational -> Rational
Diff Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
(+)
diff :: Rational -> Rational -> Diff Rational
diff = (-)
{-# INLINE add #-}
{-# INLINE diff #-}
infix 6 .-.
(.-.) :: AdditiveAbelianGroup (Diff t) => LeftTorsor t => t -> t -> Diff t
.-. :: forall t.
(AdditiveAbelianGroup (Diff t), LeftTorsor t) =>
t -> t -> Diff t
(.-.) = t -> t -> Diff t
forall t. LeftTorsor t => t -> t -> Diff t
diff
infixl 6 ^+.
(^+.) :: AdditiveAbelianGroup (Diff t) => LeftTorsor t => Diff t -> t -> t
^+. :: forall t.
(AdditiveAbelianGroup (Diff t), LeftTorsor t) =>
Diff t -> t -> t
(^+.) = Diff t -> t -> t
forall t. LeftTorsor t => Diff t -> t -> t
add
infixl 6 .+^
(.+^) :: AdditiveAbelianGroup (Diff t) => LeftTorsor t => t -> Diff t -> t
.+^ :: forall t.
(AdditiveAbelianGroup (Diff t), LeftTorsor t) =>
t -> Diff t -> t
(.+^) = (Diff t -> t -> t) -> t -> Diff t -> t
forall a b c. (a -> b -> c) -> b -> a -> c
flip Diff t -> t -> t
forall t. LeftTorsor t => Diff t -> t -> t
add
infixl 6 .-^
(.-^) :: AdditiveAbelianGroup (Diff t) => LeftTorsor t => t -> Diff t -> t
.-^ :: forall t.
(AdditiveAbelianGroup (Diff t), LeftTorsor t) =>
t -> Diff t -> t
(.-^) t
t Diff t
d = t
t t -> Diff t -> t
forall t.
(AdditiveAbelianGroup (Diff t), LeftTorsor t) =>
t -> Diff t -> t
.+^ Diff t -> Diff t
forall g. AdditiveGroup g => g -> g
invert Diff t
d
class (AdditiveAbelianGroup v, Fractional (Scalar v)) => FractionalVectorSpace v where
type Scalar v
scale :: Scalar v -> v -> v
instance FractionalVectorSpace Rational where
type Scalar Rational = Rational
scale :: Scalar Rational -> Rational -> Rational
scale = Rational -> Rational -> Rational
Scalar Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
(*)
type AffineSpace t = (FractionalVectorSpace (Diff t), LeftTorsor t)