gasp-1.2.0.0: A framework of algebraic classes

Safe HaskellNone
LanguageHaskell2010

Algebra.Linear

Synopsis

Documentation

data VZero a Source #

Constructors

VZero 
Instances
Functor (VZero :: Type -> Type) Source # 
Instance details

Defined in Algebra.Linear

Methods

fmap :: (a -> b) -> VZero a -> VZero b #

(<$) :: a -> VZero b -> VZero a #

Applicative (VZero :: Type -> Type) Source # 
Instance details

Defined in Algebra.Linear

Methods

pure :: a -> VZero a #

(<*>) :: VZero (a -> b) -> VZero a -> VZero b #

liftA2 :: (a -> b -> c) -> VZero a -> VZero b -> VZero c #

(*>) :: VZero a -> VZero b -> VZero b #

(<*) :: VZero a -> VZero b -> VZero a #

Foldable (VZero :: Type -> Type) Source # 
Instance details

Defined in Algebra.Linear

Methods

fold :: Monoid m => VZero m -> m #

foldMap :: Monoid m => (a -> m) -> VZero a -> m #

foldr :: (a -> b -> b) -> b -> VZero a -> b #

foldr' :: (a -> b -> b) -> b -> VZero a -> b #

foldl :: (b -> a -> b) -> b -> VZero a -> b #

foldl' :: (b -> a -> b) -> b -> VZero a -> b #

foldr1 :: (a -> a -> a) -> VZero a -> a #

foldl1 :: (a -> a -> a) -> VZero a -> a #

toList :: VZero a -> [a] #

null :: VZero a -> Bool #

length :: VZero a -> Int #

elem :: Eq a => a -> VZero a -> Bool #

maximum :: Ord a => VZero a -> a #

minimum :: Ord a => VZero a -> a #

sum :: Num a => VZero a -> a #

product :: Num a => VZero a -> a #

Traversable (VZero :: Type -> Type) Source # 
Instance details

Defined in Algebra.Linear

Methods

traverse :: Applicative f => (a -> f b) -> VZero a -> f (VZero b) #

sequenceA :: Applicative f => VZero (f a) -> f (VZero a) #

mapM :: Monad m => (a -> m b) -> VZero a -> m (VZero b) #

sequence :: Monad m => VZero (m a) -> m (VZero a) #

Eq (VZero a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(==) :: VZero a -> VZero a -> Bool #

(/=) :: VZero a -> VZero a -> Bool #

Ord (VZero a) Source # 
Instance details

Defined in Algebra.Linear

Methods

compare :: VZero a -> VZero a -> Ordering #

(<) :: VZero a -> VZero a -> Bool #

(<=) :: VZero a -> VZero a -> Bool #

(>) :: VZero a -> VZero a -> Bool #

(>=) :: VZero a -> VZero a -> Bool #

max :: VZero a -> VZero a -> VZero a #

min :: VZero a -> VZero a -> VZero a #

Show (VZero a) Source # 
Instance details

Defined in Algebra.Linear

Methods

showsPrec :: Int -> VZero a -> ShowS #

show :: VZero a -> String #

showList :: [VZero a] -> ShowS #

data VNext v a Source #

Constructors

VNext !(v a) !a 
Instances
Functor v => Functor (VNext v) Source # 
Instance details

Defined in Algebra.Linear

Methods

fmap :: (a -> b) -> VNext v a -> VNext v b #

(<$) :: a -> VNext v b -> VNext v a #

Applicative v => Applicative (VNext v) Source # 
Instance details

Defined in Algebra.Linear

Methods

pure :: a -> VNext v a #

(<*>) :: VNext v (a -> b) -> VNext v a -> VNext v b #

liftA2 :: (a -> b -> c) -> VNext v a -> VNext v b -> VNext v c #

(*>) :: VNext v a -> VNext v b -> VNext v b #

(<*) :: VNext v a -> VNext v b -> VNext v a #

Foldable v => Foldable (VNext v) Source # 
Instance details

Defined in Algebra.Linear

Methods

fold :: Monoid m => VNext v m -> m #

foldMap :: Monoid m => (a -> m) -> VNext v a -> m #

foldr :: (a -> b -> b) -> b -> VNext v a -> b #

foldr' :: (a -> b -> b) -> b -> VNext v a -> b #

foldl :: (b -> a -> b) -> b -> VNext v a -> b #

foldl' :: (b -> a -> b) -> b -> VNext v a -> b #

foldr1 :: (a -> a -> a) -> VNext v a -> a #

foldl1 :: (a -> a -> a) -> VNext v a -> a #

toList :: VNext v a -> [a] #

null :: VNext v a -> Bool #

length :: VNext v a -> Int #

elem :: Eq a => a -> VNext v a -> Bool #

maximum :: Ord a => VNext v a -> a #

minimum :: Ord a => VNext v a -> a #

sum :: Num a => VNext v a -> a #

product :: Num a => VNext v a -> a #

Traversable v => Traversable (VNext v) Source # 
Instance details

Defined in Algebra.Linear

Methods

traverse :: Applicative f => (a -> f b) -> VNext v a -> f (VNext v b) #

sequenceA :: Applicative f => VNext v (f a) -> f (VNext v a) #

mapM :: Monad m => (a -> m b) -> VNext v a -> m (VNext v b) #

sequence :: Monad m => VNext v (m a) -> m (VNext v a) #

(Eq a, Eq (v a)) => Eq (VNext v a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(==) :: VNext v a -> VNext v a -> Bool #

(/=) :: VNext v a -> VNext v a -> Bool #

(Ord a, Ord (v a)) => Ord (VNext v a) Source # 
Instance details

Defined in Algebra.Linear

Methods

compare :: VNext v a -> VNext v a -> Ordering #

(<) :: VNext v a -> VNext v a -> Bool #

(<=) :: VNext v a -> VNext v a -> Bool #

(>) :: VNext v a -> VNext v a -> Bool #

(>=) :: VNext v a -> VNext v a -> Bool #

max :: VNext v a -> VNext v a -> VNext v a #

min :: VNext v a -> VNext v a -> VNext v a #

(Show a, Show (v a)) => Show (VNext v a) Source # 
Instance details

Defined in Algebra.Linear

Methods

showsPrec :: Int -> VNext v a -> ShowS #

show :: VNext v a -> String #

showList :: [VNext v a] -> ShowS #

pattern V1' :: a -> V1' a Source #

pattern V2' :: forall a. a -> a -> V2' a Source #

pattern V3' :: forall a. a -> a -> a -> V3' a Source #

newtype Euclid f a Source #

Make a Euclidean vector out of a traversable functor

Constructors

Euclid 

Fields

Instances
(Applicative f, Module s a) => Module s (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(*^) :: s -> Euclid f a -> Euclid f a Source #

Functor f => Functor (Euclid f) Source # 
Instance details

Defined in Algebra.Linear

Methods

fmap :: (a -> b) -> Euclid f a -> Euclid f b #

(<$) :: a -> Euclid f b -> Euclid f a #

Applicative f => Applicative (Euclid f) Source # 
Instance details

Defined in Algebra.Linear

Methods

pure :: a -> Euclid f a #

(<*>) :: Euclid f (a -> b) -> Euclid f a -> Euclid f b #

liftA2 :: (a -> b -> c) -> Euclid f a -> Euclid f b -> Euclid f c #

(*>) :: Euclid f a -> Euclid f b -> Euclid f b #

(<*) :: Euclid f a -> Euclid f b -> Euclid f a #

Foldable f => Foldable (Euclid f) Source # 
Instance details

Defined in Algebra.Linear

Methods

fold :: Monoid m => Euclid f m -> m #

foldMap :: Monoid m => (a -> m) -> Euclid f a -> m #

foldr :: (a -> b -> b) -> b -> Euclid f a -> b #

foldr' :: (a -> b -> b) -> b -> Euclid f a -> b #

foldl :: (b -> a -> b) -> b -> Euclid f a -> b #

foldl' :: (b -> a -> b) -> b -> Euclid f a -> b #

foldr1 :: (a -> a -> a) -> Euclid f a -> a #

foldl1 :: (a -> a -> a) -> Euclid f a -> a #

toList :: Euclid f a -> [a] #

null :: Euclid f a -> Bool #

length :: Euclid f a -> Int #

elem :: Eq a => a -> Euclid f a -> Bool #

maximum :: Ord a => Euclid f a -> a #

minimum :: Ord a => Euclid f a -> a #

sum :: Num a => Euclid f a -> a #

product :: Num a => Euclid f a -> a #

Traversable f => Traversable (Euclid f) Source # 
Instance details

Defined in Algebra.Linear

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Euclid f a -> f0 (Euclid f b) #

sequenceA :: Applicative f0 => Euclid f (f0 a) -> f0 (Euclid f a) #

mapM :: Monad m => (a -> m b) -> Euclid f a -> m (Euclid f b) #

sequence :: Monad m => Euclid f (m a) -> m (Euclid f a) #

Eq (f a) => Eq (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(==) :: Euclid f a -> Euclid f a -> Bool #

(/=) :: Euclid f a -> Euclid f a -> Bool #

Ord (f a) => Ord (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

compare :: Euclid f a -> Euclid f a -> Ordering #

(<) :: Euclid f a -> Euclid f a -> Bool #

(<=) :: Euclid f a -> Euclid f a -> Bool #

(>) :: Euclid f a -> Euclid f a -> Bool #

(>=) :: Euclid f a -> Euclid f a -> Bool #

max :: Euclid f a -> Euclid f a -> Euclid f a #

min :: Euclid f a -> Euclid f a -> Euclid f a #

Show (f a) => Show (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

showsPrec :: Int -> Euclid f a -> ShowS #

show :: Euclid f a -> String #

showList :: [Euclid f a] -> ShowS #

(Applicative f, Group a) => Group (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(-) :: Euclid f a -> Euclid f a -> Euclid f a Source #

negate :: Euclid f a -> Euclid f a Source #

mult :: Integer -> Euclid f a -> Euclid f a Source #

(Applicative f, AbelianAdditive a) => AbelianAdditive (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

(Applicative f, Additive a) => Additive (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Methods

(+) :: Euclid f a -> Euclid f a -> Euclid f a Source #

zero :: Euclid f a Source #

times :: Natural -> Euclid f a -> Euclid f a Source #

(Ring a, Field a, Applicative f, Foldable f) => InnerProdSpace (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Associated Types

type Scalar (Euclid f a) :: Type Source #

Methods

dotProd :: Euclid f a -> Euclid f a -> Scalar (Euclid f a) Source #

type Scalar (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

type Scalar (Euclid f a) = a

pattern V2 :: forall a. a -> a -> Euclid V2' a Source #

pattern V3 :: forall a. a -> a -> a -> Euclid V3' a Source #

pureMat :: (Applicative v, Applicative w) => s -> Mat s v w Source #

(>*<) :: (Applicative v, Applicative w) => Mat (a -> s) v w -> Mat a v w -> Mat s v w Source #

(>$<) :: (Applicative v, Applicative w) => (a -> s) -> Mat a v w -> Mat s v w Source #

class VectorSpace (Scalar v) v => InnerProdSpace v where Source #

Associated Types

type Scalar v Source #

Methods

dotProd :: v -> v -> Scalar v Source #

Instances
(Ring a, Field a, Applicative f, Foldable f) => InnerProdSpace (Euclid f a) Source # 
Instance details

Defined in Algebra.Linear

Associated Types

type Scalar (Euclid f a) :: Type Source #

Methods

dotProd :: Euclid f a -> Euclid f a -> Scalar (Euclid f a) Source #

(⊙) :: Applicative v => Multiplicative s => v s -> v s -> v s Source #

(·) :: InnerProdSpace v => v -> v -> Scalar v Source #

type SqMat v s = Mat s v v Source #

newtype Mat s w v Source #

Constructors

Mat 

Fields

Instances
(Applicative f, Applicative g, Module s a) => Module s (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

Methods

(*^) :: s -> Mat a f g -> Mat a f g Source #

Ring s => Category (Mat s :: (Type -> Type) -> (Type -> Type) -> Type) Source # 
Instance details

Defined in Algebra.Linear

Associated Types

type Con a :: Constraint Source #

Methods

(.) :: (Con a, Con b, Con c) => Mat s b c -> Mat s a b -> Mat s a c Source #

id :: Con a => Mat s a a Source #

Show (v (w s)) => Show (Mat s w v) Source # 
Instance details

Defined in Algebra.Linear

Methods

showsPrec :: Int -> Mat s w v -> ShowS #

show :: Mat s w v -> String #

showList :: [Mat s w v] -> ShowS #

(Applicative f, Applicative g, Group a) => Group (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

Methods

(-) :: Mat a f g -> Mat a f g -> Mat a f g Source #

negate :: Mat a f g -> Mat a f g Source #

mult :: Integer -> Mat a f g -> Mat a f g Source #

(Applicative f, Applicative g, AbelianAdditive a) => AbelianAdditive (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

(Applicative f, Applicative g, Additive a) => Additive (Mat a f g) Source # 
Instance details

Defined in Algebra.Linear

Methods

(+) :: Mat a f g -> Mat a f g -> Mat a f g Source #

zero :: Mat a f g Source #

times :: Natural -> Mat a f g -> Mat a f g Source #

type Mat3x3 s = SqMat V3' s Source #

type Mat2x2 s = SqMat V2' s Source #

pattern Mat2x2 :: forall s. s -> s -> s -> s -> Mat s V2' V2' Source #

pattern Mat3x3 :: forall s. s -> s -> s -> s -> s -> s -> s -> s -> s -> Mat s V3' V3' Source #

matVecMul :: (Foldable f1, Ring b, Applicative f1, Functor f2) => Mat b f1 f2 -> Euclid f1 b -> Euclid f2 b Source #

(⊗) :: (Applicative v, Applicative w, Multiplicative s) => Euclid w s -> Euclid v s -> Mat s w v Source #

Tensor product

tensorWith :: (Applicative v, Applicative w) => (s -> t -> u) -> w s -> v t -> Mat u v w Source #

diagonal :: Traversable v => Ring s => Applicative v => Euclid v s -> SqMat v s Source #

rotation3d :: Ring a => Floating a => a -> V3 a -> Mat3x3 a Source #

3d rotation around given axis

rotationFromTo :: (Floating a, Module a a, Field a) => V3 a -> V3 a -> Mat3x3 a Source #

transpose :: Applicative f => Traversable g => Mat a f g -> Mat a g f Source #

matMul' :: (Traversable u, Ring s, Applicative w, Applicative v, Applicative u) => Mat s v u -> Mat s u w -> Mat s v w Source #

matMul :: (Traversable u, Ring s, Applicative w, Applicative v, Applicative u) => Mat s u w -> Mat s v u -> Mat s v w Source #

newtype OrthoMat v s Source #

Constructors

OrthoMat (SqMat v s) 
Instances
(Ring s, Applicative v, Traversable v) => Division (OrthoMat v s) Source # 
Instance details

Defined in Algebra.Linear

Methods

recip :: OrthoMat v s -> OrthoMat v s Source #

(/) :: OrthoMat v s -> OrthoMat v s -> OrthoMat v s Source #

(Ring s, Applicative v, Traversable v) => Multiplicative (OrthoMat v s) Source # 
Instance details

Defined in Algebra.Linear

Methods

(*) :: OrthoMat v s -> OrthoMat v s -> OrthoMat v s Source #

one :: OrthoMat v s Source #

(^) :: OrthoMat v s -> Natural -> OrthoMat v s Source #