cifl-math-library-1.1.1.0: Math libraries
Safe HaskellSafe
LanguageHaskell2010

Math.Matrix.Interface

Description

These should match standard definitions of vector spaces. Used for reference: K. Chandrasekhara Rao: Functional Analysis. also see Warner: Modern algebra.

Synopsis

Documentation

newtype (f :*: g) a infixr 5 Source #

The primary data type for matrices. Note that indices are represented in the functors, If you want to use numeric indices, use Simple. This can be viewed as a bicategory with one object (a). https://ncatlab.org/nlab/show/bicategory or as a monoidal category https://ncatlab.org/nlab/show/monoidal+category or as a matrix over a base field a https://ncatlab.org/nlab/show/matrix or as a tensor product of functors f and g https://ncatlab.org/nlab/show/tensor+product or as a composition of functors f and g

Constructors

Matrix 

Fields

Instances

Instances details
(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector1 (a :: Type) Source #

NOTICE: Linearizable instances for matrices that have similar dimensions are special.

Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, Diagonalizable Stream a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector1 (f a)) (Dual (f a)) -> (Vector1 :*: Dual) (f a) Source #

linear :: (Vector1 :*: Dual) (f a) -> LinearMap (Vector1 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector2 (f a)) (Dual (f a)) -> (Vector2 :*: Dual) (f a) Source #

linear :: (Vector2 :*: Dual) (f a) -> LinearMap (Vector2 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector3 (f a)) (Dual (f a)) -> (Vector3 :*: Dual) (f a) Source #

linear :: (Vector3 :*: Dual) (f a) -> LinearMap (Vector3 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector4 (f a)) (Dual (f a)) -> (Vector4 :*: Dual) (f a) Source #

linear :: (Vector4 :*: Dual) (f a) -> LinearMap (Vector4 (f a)) (Dual (f a)) Source #

(Scalar (f a) ~ f a, Num a, ConjugateSymmetric a, Diagonalizable Dual (f a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Dual (f a)) (Dual (f a)) -> (Dual :*: Dual) (f a) Source #

linear :: (Dual :*: Dual) (f a) -> LinearMap (Dual (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector1 a) (col -> a) -> (Vector1 :*: (->) col) a Source #

linear :: (Vector1 :*: (->) col) a -> LinearMap (Vector1 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector2 a) (col -> a) -> (Vector2 :*: (->) col) a Source #

linear :: (Vector2 :*: (->) col) a -> LinearMap (Vector2 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector3 a) (col -> a) -> (Vector3 :*: (->) col) a Source #

linear :: (Vector3 :*: (->) col) a -> LinearMap (Vector3 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector4 a) (col -> a) -> (Vector4 :*: (->) col) a Source #

linear :: (Vector4 :*: (->) col) a -> LinearMap (Vector4 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector1 a) -> ((->) row :*: Vector1) a Source #

linear :: ((->) row :*: Vector1) a -> LinearMap (row -> a) (Vector1 a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector2 a) -> ((->) row :*: Vector2) a Source #

linear :: ((->) row :*: Vector2) a -> LinearMap (row -> a) (Vector2 a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector3 a) -> ((->) row :*: Vector3) a Source #

linear :: ((->) row :*: Vector3) a -> LinearMap (row -> a) (Vector3 a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector4 a) -> ((->) row :*: Vector4) a Source #

linear :: ((->) row :*: Vector4) a -> LinearMap (row -> a) (Vector4 a) Source #

(Diagonalizable ((->) row) a, Num a, ConjugateSymmetric a, Universe row, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (col -> a) -> ((->) row :*: (->) col) a Source #

linear :: ((->) row :*: (->) col) a -> LinearMap (row -> a) (col -> a) Source #

(Applicative f, Traversable f, Traversable str, Applicative g, Traversable g, Limiting str a) => Limiting str ((f :*: g) a) Source # 
Instance details

Defined in Math.Number.Stream

Associated Types

data Closure str ((f :*: g) a) Source #

Methods

limit :: str ((f :*: g) a) -> Closure str ((f :*: g) a) Source #

approximations :: Closure str ((f :*: g) a) -> str ((f :*: g) a) Source #

Lift ((Vector3 :*: Vector3) Integer) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => (Vector3 :*: Vector3) Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (Vector3 :*: Vector3) Integer -> Code m ((Vector3 :*: Vector3) Integer) #

Lift ((List :*: List) Integer) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => (List :*: List) Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (List :*: List) Integer -> Code m ((List :*: List) Integer) #

Show a => Show (ComplexStream a) Source # 
Instance details

Defined in Math.Number.Complex

(forall b. Transposable g f b, MonadFail f, MonadFail g) => MonadFail (f :*: g) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

fail :: String -> (f :*: g) a #

(MonadZip g, MonadZip f, forall b. Transposable f g b) => MonadZip (g :*: f) Source # 
Instance details

Defined in Math.Matrix.Matrix

Methods

mzip :: (g :*: f) a -> (g :*: f) b -> (g :*: f) (a, b) #

mzipWith :: (a -> b -> c) -> (g :*: f) a -> (g :*: f) b -> (g :*: f) c #

munzip :: (g :*: f) (a, b) -> ((g :*: f) a, (g :*: f) b) #

(Foldable f, Foldable g) => Foldable (f :*: g) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

fold :: Monoid m => (f :*: g) m -> m #

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

foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :*: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :*: g) a -> a #

toList :: (f :*: g) a -> [a] #

null :: (f :*: g) a -> Bool #

length :: (f :*: g) a -> Int #

elem :: Eq a => a -> (f :*: g) a -> Bool #

maximum :: Ord a => (f :*: g) a -> a #

minimum :: Ord a => (f :*: g) a -> a #

sum :: Num a => (f :*: g) a -> a #

product :: Num a => (f :*: g) a -> a #

(Contravariant f, Functor g) => Contravariant (g :*: f) Source # 
Instance details

Defined in Math.Matrix.Matrix

Methods

contramap :: (a' -> a) -> (g :*: f) a -> (g :*: f) a' #

(>$) :: b -> (g :*: f) b -> (g :*: f) a #

(Traversable f, Traversable g) => Traversable (f :*: g) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

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

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

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

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

(Alternative f, Alternative g) => Alternative (g :*: f) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

empty :: (g :*: f) a #

(<|>) :: (g :*: f) a -> (g :*: f) a -> (g :*: f) a #

some :: (g :*: f) a -> (g :*: f) [a] #

many :: (g :*: f) a -> (g :*: f) [a] #

(Applicative f, Applicative g) => Applicative (f :*: g) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

pure :: a -> (f :*: g) a #

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

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c #

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

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

(Functor f, Functor g) => Functor (g :*: f) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

fmap :: (a -> b) -> (g :*: f) a -> (g :*: f) b #

(<$) :: a -> (g :*: f) b -> (g :*: f) a #

(Monad f, Monad g, forall b. Transposable g f b) => Monad (f :*: g) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b #

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

return :: a -> (f :*: g) a #

(MonadPlus g, MonadPlus f, forall b. Transposable f g b) => MonadPlus (g :*: f) Source # 
Instance details

Defined in Math.Matrix.Matrix

Methods

mzero :: (g :*: f) a #

mplus :: (g :*: f) a -> (g :*: f) a -> (g :*: f) a #

(Comonad f, Comonad g, forall a. Transposable g f a, forall b. Transposable f g b, forall a. Diagonalizable f (f (g a)), forall a. LinearTransform g f (f (g a)), forall a. Diagonalizable g (g a), forall a. LinearTransform f g (g a)) => Comonad (f :*: g) Source #

See video by Bartosz Milewski ("Category theory II 7.2: Comonads categorically and examples")

Instance details

Defined in Math.Matrix.Matrix

Methods

extract :: (f :*: g) a -> a Source #

duplicate :: (f :*: g) a -> (f :*: g) ((f :*: g) a) Source #

extend :: ((f :*: g) a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(=>>) :: (f :*: g) a -> ((f :*: g) a -> b) -> (f :*: g) b Source #

(.>>) :: (f :*: g) a -> b -> (f :*: g) b Source #

(Functor f, PpShowVerticalF f, PpShowF g) => PpShowF (f :*: g) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

ppf :: PpShow a => (f :*: g) a -> Doc Source #

Num a => Indexable (Vector2 :*: Vector2) a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Integral a, Indexable f a, Indexable g a) => Indexable (f :*: g) a Source # 
Instance details

Defined in Math.Matrix.Indexable

Methods

diagonal_projections :: (f :*: g) (Index (f :*: g) a) Source #

basis_vector :: Index (f :*: g) a -> (f :*: g) a Source #

index_project :: Index (f :*: g) a -> (f :*: g) a -> a Source #

indexable_indices :: (f :*: g) a Source #

(Transposable f h (g (k a)), Transposable g h (k a), Transposable g k a, Transposable f k (g a), Scalar ((f :*: g) a) ~ Scalar ((h :*: k) a)) => Transposable (f :*: g) (h :*: k) a Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: ((f :*: g) :*: (h :*: k)) a -> ((h :*: k) :*: (f :*: g)) a Source #

(Num a, ConjugateSymmetric a) => Monoid ((Vector2 :*: Vector2) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => Monoid ((Vector3 :*: Vector3) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => Monoid ((Vector4 :*: Vector4) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => Semigroup ((Vector2 :*: Vector2) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector2

(ConjugateSymmetric a, Num a) => Semigroup ((Vector3 :*: Vector3) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => Semigroup ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

(Closed a, RealFloat a) => Floating ((Stream :*: Complex) a) Source # 
Instance details

Defined in Math.Number.Complex

Generic ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Rep ((f :*: g) a) :: Type -> Type #

Methods

from :: (f :*: g) a -> Rep ((f :*: g) a) x #

to :: Rep ((f :*: g) a) x -> (f :*: g) a #

(Num a, ConjugateSymmetric a) => Num ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => Num ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => Num ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Num ((NumExpr v :*: Var) a) Source # 
Instance details

Defined in Math.Number.NumericExpression

Methods

(+) :: (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a #

(-) :: (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a #

(*) :: (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a #

negate :: (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a #

abs :: (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a #

signum :: (NumExpr v :*: Var) a -> (NumExpr v :*: Var) a #

fromInteger :: Integer -> (NumExpr v :*: Var) a #

RealFloat a => Num ((Stream :*: Complex) a) Source # 
Instance details

Defined in Math.Number.Complex

(Fractional a, ConjugateSymmetric a) => Fractional ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Linear

(Fractional a, ConjugateSymmetric a) => Fractional ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

RealFloat a => Fractional ((Stream :*: Complex) a) Source # 
Instance details

Defined in Math.Number.Complex

Show (f a) => Show ((Vector1 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

showsPrec :: Int -> (Vector1 :*: f) a -> ShowS #

show :: (Vector1 :*: f) a -> String #

showList :: [(Vector1 :*: f) a] -> ShowS #

Show (f a) => Show ((Vector2 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

showsPrec :: Int -> (Vector2 :*: f) a -> ShowS #

show :: (Vector2 :*: f) a -> String #

showList :: [(Vector2 :*: f) a] -> ShowS #

Show (f a) => Show ((Vector3 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

showsPrec :: Int -> (Vector3 :*: f) a -> ShowS #

show :: (Vector3 :*: f) a -> String #

showList :: [(Vector3 :*: f) a] -> ShowS #

Show (f a) => Show ((Vector4 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

showsPrec :: Int -> (Vector4 :*: f) a -> ShowS #

show :: (Vector4 :*: f) a -> String #

showList :: [(Vector4 :*: f) a] -> ShowS #

PpShow a => Show ((Stream :*: Stream) a) Source # 
Instance details

Defined in Math.Number.Stream

Show (f a) => Show ((Complex :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

showsPrec :: Int -> (Complex :*: f) a -> ShowS #

show :: (Complex :*: f) a -> String #

showList :: [(Complex :*: f) a] -> ShowS #

Show (f a) => Show ((List :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

showsPrec :: Int -> (List :*: f) a -> ShowS #

show :: (List :*: f) a -> String #

showList :: [(List :*: f) a] -> ShowS #

(Num a, ConjugateSymmetric a) => ConjugateSymmetric ((Vector2 :*: Vector2) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector2

(ConjugateSymmetric a, Num a) => ConjugateSymmetric ((Vector3 :*: Vector3) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector3

ConjugateSymmetric a => ConjugateSymmetric ((Vector4 :*: Vector4) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector4

ConjugateSymmetric a => ConjugateSymmetric ((Stream :*: Stream) a) Source # 
Instance details

Defined in Math.Number.Stream

Methods

conj :: (Stream :*: Stream) a -> (Stream :*: Stream) a Source #

(Floating a, ConjugateSymmetric a) => InnerProductSpace ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Floating a, ConjugateSymmetric a) => InnerProductSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

(Integral col, Integral row, Universe row, Universe col, Num a, ConjugateSymmetric a) => InnerProductSpace (((->) row :*: (->) col) a) Source #

https://en.wikipedia.org/wiki/Frobenius_inner_product

Instance details

Defined in Math.Matrix.Simple

Methods

(%.) :: ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a -> Scalar (((->) row :*: (->) col) a) Source #

(Num a, ConjugateSymmetric a) => LieAlgebra ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

(Num a, ConjugateSymmetric a) => LieAlgebra ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

(Floating a, ConjugateSymmetric a) => NormedSpace ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Floating a, ConjugateSymmetric a) => NormedSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

(Integral row, Integral col, Floating a, Universe row, Universe col, ConjugateSymmetric a) => NormedSpace (((->) row :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

norm :: ((->) row :*: (->) col) a -> Scalar (((->) row :*: (->) col) a) Source #

norm_squared :: ((->) row :*: (->) col) a -> Scalar (((->) row :*: (->) col) a) Source #

(ConjugateSymmetric a, Num a) => StandardBasis ((Dual :*: Vector2) a) Source #

https://en.wikipedia.org/wiki/Dual_space

Instance details

Defined in Math.Matrix.Covector

(Num a, ConjugateSymmetric a) => StandardBasis ((Dual :*: Vector3) a) Source #

https://en.wikipedia.org/wiki/Dual_space

Instance details

Defined in Math.Matrix.Linear

(Functor f, Functor g, Num a, StandardBasis (g a), StandardBasis (f a)) => StandardBasis ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

unit_vectors :: [(f :*: g) a] Source #

Num a => VectorSpace ((Vector1 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Scalar ((Vector1 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector1 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector3) a) Source #

1 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector1 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector4) a) Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector1 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector1 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector1 :*: (->) col) a) Source #

Methods

vzero :: (Vector1 :*: (->) col) a Source #

vnegate :: (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

(%+) :: (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

(%*) :: Scalar ((Vector1 :*: (->) col) a) -> (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

Num a => VectorSpace ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector3) a) Source #

2 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector2 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector4) a) Source #

2 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector2 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector2 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector2 :*: (->) col) a) Source #

Methods

vzero :: (Vector2 :*: (->) col) a Source #

vnegate :: (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

(%+) :: (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

(%*) :: Scalar ((Vector2 :*: (->) col) a) -> (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

Num a => VectorSpace ((Vector3 :*: Vector1) a) Source #

3 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector2) a) Source #

3 x 2 matrices

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector3) a) Source #

3 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector4) a) Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector3 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector3 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector3 :*: (->) col) a) Source #

Methods

vzero :: (Vector3 :*: (->) col) a Source #

vnegate :: (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

(%+) :: (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

(%*) :: Scalar ((Vector3 :*: (->) col) a) -> (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

Num a => VectorSpace ((Vector4 :*: Vector1) a) Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector2) a) Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector3) a) Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector4 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector4 :*: (->) col) a) Source #

Methods

vzero :: (Vector4 :*: (->) col) a Source #

vnegate :: (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

(%+) :: (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

(%*) :: Scalar ((Vector4 :*: (->) col) a) -> (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

Num a => VectorSpace (((->) row :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector1) a) Source #

Methods

vzero :: ((->) row :*: Vector1) a Source #

vnegate :: ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

(%+) :: ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

(%*) :: Scalar (((->) row :*: Vector1) a) -> ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

Num a => VectorSpace (((->) row :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector2) a) Source #

Methods

vzero :: ((->) row :*: Vector2) a Source #

vnegate :: ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

(%+) :: ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

(%*) :: Scalar (((->) row :*: Vector2) a) -> ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

Num a => VectorSpace (((->) row :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector3) a) Source #

Methods

vzero :: ((->) row :*: Vector3) a Source #

vnegate :: ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(%+) :: ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(%*) :: Scalar (((->) row :*: Vector3) a) -> ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

Num a => VectorSpace (((->) row :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector4) a) Source #

Methods

vzero :: ((->) row :*: Vector4) a Source #

vnegate :: ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

(%+) :: ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

(%*) :: Scalar (((->) row :*: Vector4) a) -> ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

Num a => VectorSpace (((->) row :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: (->) col) a) Source #

Methods

vzero :: ((->) row :*: (->) col) a Source #

vnegate :: ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a Source #

(%+) :: ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a Source #

(%*) :: Scalar (((->) row :*: (->) col) a) -> ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a Source #

Optimal ((Vector2 :*: Vector2) Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector2) Int32) Source #

Optimal ((Vector2 :*: Vector2) Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector2) Float) Source #

Optimal ((Vector2 :*: Vector4) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector4) Int16) Source #

Optimal ((Vector4 :*: Vector2) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector4 :*: Vector2) Int16) Source #

Optimal ((Vector4 :*: Vector4) Int8) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector4 :*: Vector4) Int8) Source #

(Fractional a, ConjugateSymmetric a) => Group ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

(Fractional a, ConjugateSymmetric a) => Group ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Fractional a, ConjugateSymmetric a) => Group ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

PpShow (f a) => PpShow ((Vector2 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

pp :: (Vector2 :*: f) a -> Doc Source #

PpShow (f a) => PpShow ((Vector4 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

pp :: (Vector4 :*: f) a -> Doc Source #

(PpShowF g, PpShowVerticalF f, Functor f, PpShow a) => PpShow ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

pp :: (f :*: g) a -> Doc Source #

(Functor f, Functor g) => Builder ((g :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

Associated Types

data Unfold ((g :*: f) a) :: Type -> Type Source #

Methods

build :: Unfold ((g :*: f) a) a0 -> a0 -> (g :*: f) a Source #

Functor g => Visitor ((g :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

data Fold ((g :*: f) a) :: Type -> Type Source #

Methods

visit :: Fold ((g :*: f) a) a0 -> (g :*: f) a -> a0 Source #

Eq (f (g a)) => Eq ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(==) :: (f :*: g) a -> (f :*: g) a -> Bool #

(/=) :: (f :*: g) a -> (f :*: g) a -> Bool #

(Eq a, Applicative f, Applicative g, Foldable f, Foldable g, Ord (f (g a))) => Ord ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

Methods

compare :: (f :*: g) a -> (f :*: g) a -> Ordering #

(<) :: (f :*: g) a -> (f :*: g) a -> Bool #

(<=) :: (f :*: g) a -> (f :*: g) a -> Bool #

(>) :: (f :*: g) a -> (f :*: g) a -> Bool #

(>=) :: (f :*: g) a -> (f :*: g) a -> Bool #

max :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

min :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

data Closure str ((f :*: g) a) Source # 
Instance details

Defined in Math.Number.Stream

data Closure str ((f :*: g) a) = MatrixClosure {}
type Rep ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Interface

type Rep ((f :*: g) a) = D1 ('MetaData ":*:" "Math.Matrix.Interface" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Matrix" 'PrefixI 'True) (S1 ('MetaSel ('Just "cells") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (g a)))))
type Scalar ((Vector1 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

type Scalar ((Vector1 :*: Vector1) a) = a
type Scalar ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector1 :*: Vector2) a) = a
type Scalar ((Vector1 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector1 :*: Vector3) a) = a
type Scalar ((Vector1 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector1 :*: Vector4) a) = a
type Scalar ((Vector1 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector1 :*: (->) col) a) = a
type Scalar ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector2 :*: Vector1) a) = a
type Scalar ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector2 :*: Vector2) a) = a
type Scalar ((Vector2 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector2 :*: Vector3) a) = a
type Scalar ((Vector2 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector2 :*: Vector4) a) = a
type Scalar ((Vector2 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector2 :*: (->) col) a) = a
type Scalar ((Vector3 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector1) a) = a
type Scalar ((Vector3 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector2) a) = a
type Scalar ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector3) a) = a
type Scalar ((Vector3 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector3 :*: Vector4) a) = a
type Scalar ((Vector3 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector3 :*: (->) col) a) = a
type Scalar ((Vector4 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector1) a) = a
type Scalar ((Vector4 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector2) a) = a
type Scalar ((Vector4 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector3) a) = a
type Scalar ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector4) a) = a
type Scalar ((Vector4 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector4 :*: (->) col) a) = a
type Scalar (((->) row :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector1) a) = a
type Scalar (((->) row :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector2) a) = a
type Scalar (((->) row :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector3) a) = a
type Scalar (((->) row :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector4) a) = a
type Scalar (((->) row :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: (->) col) a) = a
type Transpose ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

type Transpose ((f :*: g) a) = (g :*: f) a
type Optimized ((Vector2 :*: Vector2) Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector2 :*: Vector2) Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector2 :*: Vector4) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector4 :*: Vector2) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector4 :*: Vector4) Int8) Source # 
Instance details

Defined in Math.Matrix.SIMD

data Fold ((g :*: f) a) b Source # 
Instance details

Defined in Math.Matrix.Interface

data Fold ((g :*: f) a) b = MatrixFold (g c -> b, f a -> c)
data Unfold ((g :*: f) a) b Source # 
Instance details

Defined in Math.Matrix.Matrix

data Unfold ((g :*: f) a) b = MatrixUnfold (c -> d -> a) (b -> g c) (b -> f d)

data Vector1 a Source #

Constructors

Vector1 

Fields

Instances

Instances details
Foldable Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Vector1 a -> m #

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

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

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

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

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

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

toList :: Vector1 a -> [a] #

null :: Vector1 a -> Bool #

length :: Vector1 a -> Int #

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

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

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

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

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

Traversable Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

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

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

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

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

Applicative Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

pure :: a -> Vector1 a #

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

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

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

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

Functor Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

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

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

Monad Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

(>>=) :: Vector1 a -> (a -> Vector1 b) -> Vector1 b #

(>>) :: Vector1 a -> Vector1 b -> Vector1 b #

return :: a -> Vector1 a #

PpShowF Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

ppf :: PpShow a => Vector1 a -> Doc Source #

PpShowVerticalF Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

ppf_vertical :: PpShow a => Vector1 a -> Doc Source #

AppendableVector Vector1 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Vector1 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector1 a -> (Vector1 :+: Vector1) a Source #

AppendableVector Vector1 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Vector1 :+: Vector2 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector2 a -> (Vector1 :+: Vector2) a Source #

AppendableVector Vector1 Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector1 :+: Vector3 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector3 a -> (Vector1 :+: Vector3) a Source #

AppendableVector Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Vector2 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Vector1 a -> (Vector2 :+: Vector1) a Source #

AppendableVector Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector3 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector3 a -> Vector1 a -> (Vector3 :+: Vector1) a Source #

Num a => Diagonalizable Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Num a => Indexable Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

ProjectionSpace Vector1 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

data (Vector1 \\\ Vector1) a Source #

ProjectionSpace Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data (Vector2 \\\ Vector1) a Source #

ProjectionSpace Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data (Vector3 \\\ Vector1) a Source #

SplittableVector Vector1 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

vsplit :: (Vector1 :+: Vector1) a -> (Vector1 a, Vector1 a) Source #

SplittableVector Vector1 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

vsplit :: (Vector1 :+: Vector2) a -> (Vector1 a, Vector2 a) Source #

SplittableVector Vector1 Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector1 :+: Vector3) a -> (Vector1 a, Vector3 a) Source #

SplittableVector Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

vsplit :: (Vector2 :+: Vector1) a -> (Vector2 a, Vector1 a) Source #

SplittableVector Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector3 :+: Vector1) a -> (Vector3 a, Vector1 a) Source #

Num a => Traceable Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

HasIdentityLinear Vector1 LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

Num a => LinearTransform Vector1 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

(ConjugateSymmetric a, Num a) => LinearTransform Vector1 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => LinearTransform Vector1 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector1 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(ConjugateSymmetric a, Num a) => LinearTransform Vector2 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(ConjugateSymmetric a, Num a) => ProjectionDual Vector1 Dual a Source # 
Instance details

Defined in Math.Matrix.Linear

Transposable Vector1 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Transposable Vector1 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector1 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector1 Vector4 a Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector2 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector3 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector4 Vector1 a Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Stream Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector1 (a :: Type) Source #

NOTICE: Linearizable instances for matrices that have similar dimensions are special.

Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector1 (f a)) (Dual (f a)) -> (Vector1 :*: Dual) (f a) Source #

linear :: (Vector1 :*: Dual) (f a) -> LinearMap (Vector1 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector1 a) (col -> a) -> (Vector1 :*: (->) col) a Source #

linear :: (Vector1 :*: (->) col) a -> LinearMap (Vector1 a) (col -> a) Source #

FunctorArrow Vector1 (->) (->) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

amap :: forall (c :: k) (d :: k). (c -> d) -> Vector1 c -> Vector1 d Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector1 a) -> ((->) row :*: Vector1) a Source #

linear :: ((->) row :*: Vector1) a -> LinearMap (row -> a) (Vector1 a) Source #

Infinitesimal str a => Infinitesimal str (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Limiting str a => Limiting str (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

data Closure str (Vector1 a) Source #

Methods

limit :: str (Vector1 a) -> Closure str (Vector1 a) Source #

approximations :: Closure str (Vector1 a) -> str (Vector1 a) Source #

Lift a => Lift (Vector1 a :: Type) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => Vector1 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector1 a -> Code m (Vector1 a) #

(Num a, Universe col) => LinearTransform Vector1 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector1 :*: (->) col) a -> Vector1 a Source #

(<<*>) :: (Vector1 :*: (->) col) a -> Vector1 a -> col -> a Source #

Transposable Vector1 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

transpose_impl :: (Vector1 :*: (->) row) a -> ((->) row :*: Vector1) a Source #

Data a => Data (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector1 a -> c (Vector1 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector1 a) #

toConstr :: Vector1 a -> Constr #

dataTypeOf :: Vector1 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector1 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector1 a)) #

gmapT :: (forall b. Data b => b -> b) -> Vector1 a -> Vector1 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector1 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector1 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vector1 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector1 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector1 a -> m (Vector1 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector1 a -> m (Vector1 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector1 a -> m (Vector1 a) #

Num a => Monoid (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

mempty :: Vector1 a #

mappend :: Vector1 a -> Vector1 a -> Vector1 a #

mconcat :: [Vector1 a] -> Vector1 a #

Num a => Semigroup (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

(<>) :: Vector1 a -> Vector1 a -> Vector1 a #

sconcat :: NonEmpty (Vector1 a) -> Vector1 a #

stimes :: Integral b => b -> Vector1 a -> Vector1 a #

Floating a => Floating (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

pi :: Vector1 a #

exp :: Vector1 a -> Vector1 a #

log :: Vector1 a -> Vector1 a #

sqrt :: Vector1 a -> Vector1 a #

(**) :: Vector1 a -> Vector1 a -> Vector1 a #

logBase :: Vector1 a -> Vector1 a -> Vector1 a #

sin :: Vector1 a -> Vector1 a #

cos :: Vector1 a -> Vector1 a #

tan :: Vector1 a -> Vector1 a #

asin :: Vector1 a -> Vector1 a #

acos :: Vector1 a -> Vector1 a #

atan :: Vector1 a -> Vector1 a #

sinh :: Vector1 a -> Vector1 a #

cosh :: Vector1 a -> Vector1 a #

tanh :: Vector1 a -> Vector1 a #

asinh :: Vector1 a -> Vector1 a #

acosh :: Vector1 a -> Vector1 a #

atanh :: Vector1 a -> Vector1 a #

log1p :: Vector1 a -> Vector1 a #

expm1 :: Vector1 a -> Vector1 a #

log1pexp :: Vector1 a -> Vector1 a #

log1mexp :: Vector1 a -> Vector1 a #

Generic a => Generic (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Rep (Vector1 a) :: Type -> Type #

Methods

from :: Vector1 a -> Rep (Vector1 a) x #

to :: Rep (Vector1 a) x -> Vector1 a #

Num a => Num (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

(+) :: Vector1 a -> Vector1 a -> Vector1 a #

(-) :: Vector1 a -> Vector1 a -> Vector1 a #

(*) :: Vector1 a -> Vector1 a -> Vector1 a #

negate :: Vector1 a -> Vector1 a #

abs :: Vector1 a -> Vector1 a #

signum :: Vector1 a -> Vector1 a #

fromInteger :: Integer -> Vector1 a #

Read a => Read (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Fractional a => Fractional (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

(/) :: Vector1 a -> Vector1 a -> Vector1 a #

recip :: Vector1 a -> Vector1 a #

fromRational :: Rational -> Vector1 a #

Show a => Show (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

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

show :: Vector1 a -> String #

showList :: [Vector1 a] -> ShowS #

Binary s => Binary (Vector1 s) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

put :: Vector1 s -> Put #

get :: Get (Vector1 s) #

putList :: [Vector1 s] -> Put #

ConjugateSymmetric a => ConjugateSymmetric (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

conj :: Vector1 a -> Vector1 a Source #

Num a => CoordinateSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Coordinate (Vector1 a) Source #

(Num a, ConjugateSymmetric a) => InnerProductSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

(%.) :: Vector1 a -> Vector1 a -> Scalar (Vector1 a) Source #

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Num a => StandardBasis (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Num a => VectorSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Scalar (Vector1 a) Source #

DifferentiallyClosed a => DifferentiallyClosed (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

derivate :: (Vector1 a -> Vector1 a) -> Vector1 a -> Vector1 a Source #

integral :: (Vector1 a, Vector1 a) -> (Vector1 a -> Vector1 a) -> Vector1 a Source #

MedianAlgebra a => MedianAlgebra (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

med :: Vector1 a -> Vector1 a -> Vector1 a -> Vector1 a Source #

PpShow a => PpShow (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

pp :: Vector1 a -> Doc Source #

Universe a => Universe (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Eq a => Eq (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

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

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

Ord a => Ord (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

compare :: Vector1 a -> Vector1 a -> Ordering #

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

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

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

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

max :: Vector1 a -> Vector1 a -> Vector1 a #

min :: Vector1 a -> Vector1 a -> Vector1 a #

(ConjugateSymmetric a, Num a) => Dualizable (Vector1 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector1 a -> Scalar (Vector1 a)) -> Dual (Vector1 a) Source #

bracket :: Dual (Vector1 a) -> Vector1 a -> Scalar (Vector1 a) Source #

(ConjugateSymmetric a, Num a, Closed a) => VectorDerivative (Vector1 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

Num a => DecomposableVectorSpace (Vector1 a) ((->) OneD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector1 a) -> res) -> Vector1 a -> OneD -> res Source #

project :: Vector1 a -> OneD -> Scalar (Vector1 a) Source #

Applicative (Vector2 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

pure :: a -> (Vector2 \\\ Vector1) a #

(<*>) :: (Vector2 \\\ Vector1) (a -> b) -> (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b #

liftA2 :: (a -> b -> c) -> (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) c #

(*>) :: (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) b #

(<*) :: (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) a #

Applicative (Vector3 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pure :: a -> (Vector3 \\\ Vector1) a #

(<*>) :: (Vector3 \\\ Vector1) (a -> b) -> (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b #

liftA2 :: (a -> b -> c) -> (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) c #

(*>) :: (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) b #

(<*) :: (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) a #

Functor (Vector1 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

fmap :: (a -> b) -> (Vector1 \\\ Vector1) a -> (Vector1 \\\ Vector1) b #

(<$) :: a -> (Vector1 \\\ Vector1) b -> (Vector1 \\\ Vector1) a #

Functor (Vector2 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

fmap :: (a -> b) -> (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b #

(<$) :: a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) a #

Functor (Vector3 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

fmap :: (a -> b) -> (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b #

(<$) :: a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) a #

(Num a, ConjugateSymmetric a) => Monoid (Vector1 a :-> Vector1 a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Semigroup (Vector1 a :-> Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Linear

ProjectionSpace (Vector3 \\\ Vector1) Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data ((Vector3 \\\ Vector1) \\\ Vector1) a Source #

Show a => Show ((Vector3 \\\ Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Universe row, Num a) => LinearTransform ((->) row) Vector1 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector1 a -> ((->) row :*: Vector1) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector1) a -> (row -> a) -> Vector1 a Source #

Transposable ((->) row) Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

transpose_impl :: ((->) row :*: Vector1) a -> (Vector1 :*: (->) row) a Source #

Show (f a) => Show ((Vector1 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

showsPrec :: Int -> (Vector1 :*: f) a -> ShowS #

show :: (Vector1 :*: f) a -> String #

showList :: [(Vector1 :*: f) a] -> ShowS #

Num a => VectorSpace ((Vector1 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Scalar ((Vector1 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector1 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector3) a) Source #

1 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector1 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector4) a) Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector1 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector1 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector1 :*: (->) col) a) Source #

Methods

vzero :: (Vector1 :*: (->) col) a Source #

vnegate :: (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

(%+) :: (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

(%*) :: Scalar ((Vector1 :*: (->) col) a) -> (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

Num a => VectorSpace ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector1) a) Source #

3 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector1) a) Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector1) a) Source #

Num a => VectorSpace (((->) row :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector1) a) Source #

Methods

vzero :: ((->) row :*: Vector1) a Source #

vnegate :: ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

(%+) :: ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

(%*) :: Scalar (((->) row :*: Vector1) a) -> ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

type Vector1 :+: Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

type Vector1 :+: Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

type Vector1 :+: Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector2 :+: Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

type Vector3 :+: Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

data (Vector1 \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector1

data (Vector2 \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector2

data (Vector3 \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector3

data Closure str (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

type Rep (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

type Rep (Vector1 a) = D1 ('MetaData "Vector1" "Math.Matrix.Interface" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "Vector1" 'PrefixI 'True) (S1 ('MetaSel ('Just "vector_element") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type Coordinate (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

type Scalar (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

type Scalar (Vector1 a) = a
data ((Vector3 \\\ Vector1) \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector1 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

type Scalar ((Vector1 :*: Vector1) a) = a
type Scalar ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector1 :*: Vector2) a) = a
type Scalar ((Vector1 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector1 :*: Vector3) a) = a
type Scalar ((Vector1 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector1 :*: Vector4) a) = a
type Scalar ((Vector1 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector1 :*: (->) col) a) = a
type Scalar ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector2 :*: Vector1) a) = a
type Scalar ((Vector3 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector1) a) = a
type Scalar ((Vector4 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector1) a) = a
type Scalar (((->) row :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector1) a) = a

data Vector2 s Source #

Constructors

Vector2 

Fields

Instances

Instances details
MonadZip Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

mzip :: Vector2 a -> Vector2 b -> Vector2 (a, b) #

mzipWith :: (a -> b -> c) -> Vector2 a -> Vector2 b -> Vector2 c #

munzip :: Vector2 (a, b) -> (Vector2 a, Vector2 b) #

Foldable Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Vector2 a -> m #

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

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

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

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

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

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

toList :: Vector2 a -> [a] #

null :: Vector2 a -> Bool #

length :: Vector2 a -> Int #

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

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

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

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

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

Traversable Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

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

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

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

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

Applicative Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

pure :: a -> Vector2 a #

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

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

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

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

Functor Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

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

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

Monad Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

(>>=) :: Vector2 a -> (a -> Vector2 b) -> Vector2 b #

(>>) :: Vector2 a -> Vector2 b -> Vector2 b #

return :: a -> Vector2 a #

UpdateableMatrixDimension Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

write_row :: Applicative h => h a -> Vector2 ((Vector2 :*: h) a -> (Vector2 :*: h) a) Source #

write_column :: Applicative h => h a -> Vector2 ((h :*: Vector2) a -> (h :*: Vector2) a) Source #

DifferentialOperator Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

partial :: DifferentiallyClosed a => (Vector2 a -> a) -> Vector2 a -> Vector2 a Source #

CircularComonad Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

rotate :: Vector2 a -> Vector2 a Source #

Comonad Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

extract :: Vector2 a -> a Source #

duplicate :: Vector2 a -> Vector2 (Vector2 a) Source #

extend :: (Vector2 a -> b) -> Vector2 a -> Vector2 b Source #

(=>>) :: Vector2 a -> (Vector2 a -> b) -> Vector2 b Source #

(.>>) :: Vector2 a -> b -> Vector2 b Source #

PpShowF Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

ppf :: PpShow a => Vector2 a -> Doc Source #

PpShowVerticalF Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

ppf_vertical :: PpShow a => Vector2 a -> Doc Source #

AppendableVector Vector1 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Vector1 :+: Vector2 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector2 a -> (Vector1 :+: Vector2) a Source #

AppendableVector Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Vector2 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Vector1 a -> (Vector2 :+: Vector1) a Source #

AppendableVector Vector2 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector2 :+: Vector2 :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Vector2 a -> (Vector2 :+: Vector2) a Source #

AppendableVector Vector2 Stream Source # 
Instance details

Defined in Math.Matrix.VectorConversions

Associated Types

type Vector2 :+: Stream :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Stream a -> (Vector2 :+: Stream) a Source #

CodiagonalMatrix Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data Codiagonal Vector2 a Source #

type Vector2 \\ a Source #

Num a => Diagonalizable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Floating a => EigenDecomposable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => Indexable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Fractional a => Invertible Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

ProjectionSpace Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data (Vector2 \\\ Vector1) a Source #

ProjectionSpace Vector3 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data (Vector3 \\\ Vector2) a Source #

SplittableVector Vector1 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

vsplit :: (Vector1 :+: Vector2) a -> (Vector1 a, Vector2 a) Source #

SplittableVector Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

vsplit :: (Vector2 :+: Vector1) a -> (Vector2 a, Vector1 a) Source #

SplittableVector Vector2 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector2 :+: Vector2) a -> (Vector2 a, Vector2 a) Source #

Num a => Traceable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

HasIdentityLinear Vector2 LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(ConjugateSymmetric a, Fractional a) => LinearInvertible LinearMap Vector2 a Source # 
Instance details

Defined in Math.Matrix.Linear

(ConjugateSymmetric a, Num a) => LinearTraceable LinearMap Vector2 a Source # 
Instance details

Defined in Math.Matrix.Linear

(ConjugateSymmetric a, Num a) => LinearTransform Vector1 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(ConjugateSymmetric a, Num a) => LinearTransform Vector2 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Scalar (SIMDVec 2 Double) ~ Double => LinearTransform Vector2 Vector2 Double Source # 
Instance details

Defined in Math.Matrix.SIMD

(ConjugateSymmetric a, Num a) => LinearTransform Vector2 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => LinearTransform Vector2 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector2 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(ConjugateSymmetric a, Num a) => ProjectionDual Vector2 Dual a Source # 
Instance details

Defined in Math.Matrix.Linear

Transposable Vector1 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector2 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector2 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector2 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector2 Vector4 a Source #

2 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector3 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector4 Vector2 a Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Stream Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

FunctorArrow Vector2 (:==:) (:==:) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

amap :: forall (c :: k) (d :: k). (c :==: d) -> Vector2 c :==: Vector2 d Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector2 (f a)) (Dual (f a)) -> (Vector2 :*: Dual) (f a) Source #

linear :: (Vector2 :*: Dual) (f a) -> LinearMap (Vector2 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector2 a) (col -> a) -> (Vector2 :*: (->) col) a Source #

linear :: (Vector2 :*: (->) col) a -> LinearMap (Vector2 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector2 a) -> ((->) row :*: Vector2) a Source #

linear :: ((->) row :*: Vector2) a -> LinearMap (row -> a) (Vector2 a) Source #

(Limiting str a, Monad str) => Limiting str (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data Closure str (Vector2 a) Source #

Methods

limit :: str (Vector2 a) -> Closure str (Vector2 a) Source #

approximations :: Closure str (Vector2 a) -> str (Vector2 a) Source #

Lift a => Lift (Vector2 a :: Type) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => Vector2 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector2 a -> Code m (Vector2 a) #

(ConjugateSymmetric a, Infinitesimal Stream a, VectorSpace a, Closed a) => VectorCrossProduct (Vector2 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Infinitesimal Stream a, Closed a) => VectorLaplacian (Vector2 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, Universe col) => LinearTransform Vector2 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector2 :*: (->) col) a -> Vector2 a Source #

(<<*>) :: (Vector2 :*: (->) col) a -> Vector2 a -> col -> a Source #

Transposable Vector2 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

transpose_impl :: (Vector2 :*: (->) row) a -> ((->) row :*: Vector2) a Source #

Data a => Data (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector2 a -> c (Vector2 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector2 a) #

toConstr :: Vector2 a -> Constr #

dataTypeOf :: Vector2 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector2 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector2 a)) #

gmapT :: (forall b. Data b => b -> b) -> Vector2 a -> Vector2 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector2 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector2 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vector2 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector2 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector2 a -> m (Vector2 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector2 a -> m (Vector2 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector2 a -> m (Vector2 a) #

Applicative (Codiagonal Vector2) Source # 
Instance details

Defined in Math.Matrix.Vector2

Functor (Codiagonal Vector2) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

fmap :: (a -> b) -> Codiagonal Vector2 a -> Codiagonal Vector2 b #

(<$) :: a -> Codiagonal Vector2 b -> Codiagonal Vector2 a #

Num s => Monoid (Vector2 s) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

mempty :: Vector2 s #

mappend :: Vector2 s -> Vector2 s -> Vector2 s #

mconcat :: [Vector2 s] -> Vector2 s #

Num s => Semigroup (Vector2 s) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

(<>) :: Vector2 s -> Vector2 s -> Vector2 s #

sconcat :: NonEmpty (Vector2 s) -> Vector2 s #

stimes :: Integral b => b -> Vector2 s -> Vector2 s #

Generic a => Generic (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Rep (Vector2 a) :: Type -> Type #

Methods

from :: Vector2 a -> Rep (Vector2 a) x #

to :: Rep (Vector2 a) x -> Vector2 a #

Num a => Num (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

(+) :: Vector2 a -> Vector2 a -> Vector2 a #

(-) :: Vector2 a -> Vector2 a -> Vector2 a #

(*) :: Vector2 a -> Vector2 a -> Vector2 a #

negate :: Vector2 a -> Vector2 a #

abs :: Vector2 a -> Vector2 a #

signum :: Vector2 a -> Vector2 a #

fromInteger :: Integer -> Vector2 a #

Read a => Read (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Show a => Show (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

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

show :: Vector2 a -> String #

showList :: [Vector2 a] -> ShowS #

Binary s => Binary (Vector2 s) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

put :: Vector2 s -> Put #

get :: Get (Vector2 s) #

putList :: [Vector2 s] -> Put #

ConjugateSymmetric a => ConjugateSymmetric (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

conj :: Vector2 a -> Vector2 a Source #

Num a => CoordinateSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Coordinate (Vector2 a) Source #

Scalar (SIMDVec 2 Double) ~ Double => InnerProductSpace (Vector2 Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => InnerProductSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

(%.) :: Vector2 a -> Vector2 a -> Scalar (Vector2 a) Source #

NormedSpace (Vector2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

StandardBasis (Vector2 (Vector2 Int)) Source # 
Instance details

Defined in Math.Matrix.Vector2

StandardBasis (Vector2 Int) Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => StandardBasis (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => VectorSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar (Vector2 a) Source #

Optimal (Vector2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector2 (Complex Float)) Source #

Optimal (Vector2 Int64) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector2 Int64) Source #

Optimal (Vector2 Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector2 Double) Source #

MedianAlgebra s => MedianAlgebra (Vector2 s) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

med :: Vector2 s -> Vector2 s -> Vector2 s -> Vector2 s Source #

PpShow a => PpShow (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

pp :: Vector2 a -> Doc Source #

Universe a => Universe (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Visitor (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data Fold (Vector2 a) :: Type -> Type Source #

Methods

visit :: Fold (Vector2 a) a0 -> Vector2 a -> a0 Source #

Eq a => Eq (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

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

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

Ord a => Ord (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

compare :: Vector2 a -> Vector2 a -> Ordering #

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

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

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

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

max :: Vector2 a -> Vector2 a -> Vector2 a #

min :: Vector2 a -> Vector2 a -> Vector2 a #

(Num a, ConjugateSymmetric a) => Dualizable (Vector2 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector2 a -> Scalar (Vector2 a)) -> Dual (Vector2 a) Source #

bracket :: Dual (Vector2 a) -> Vector2 a -> Scalar (Vector2 a) Source #

(ConjugateSymmetric a, Infinitesimal Stream a, Closed a) => VectorDerivative (Vector2 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

Num a => DecomposableVectorSpace (Vector2 a) ((->) TwoD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector2 a) -> res) -> Vector2 a -> TwoD -> res Source #

project :: Vector2 a -> TwoD -> Scalar (Vector2 a) Source #

Applicative (Vector2 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

pure :: a -> (Vector2 \\\ Vector1) a #

(<*>) :: (Vector2 \\\ Vector1) (a -> b) -> (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b #

liftA2 :: (a -> b -> c) -> (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) c #

(*>) :: (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) b #

(<*) :: (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) a #

Applicative (Vector3 \\\ Vector2) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pure :: a -> (Vector3 \\\ Vector2) a #

(<*>) :: (Vector3 \\\ Vector2) (a -> b) -> (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b #

liftA2 :: (a -> b -> c) -> (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) c #

(*>) :: (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) b #

(<*) :: (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) a #

Functor (Vector2 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

fmap :: (a -> b) -> (Vector2 \\\ Vector1) a -> (Vector2 \\\ Vector1) b #

(<$) :: a -> (Vector2 \\\ Vector1) b -> (Vector2 \\\ Vector1) a #

Functor (Vector3 \\\ Vector2) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

fmap :: (a -> b) -> (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b #

(<$) :: a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) a #

Show a => Show (Codiagonal Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Show a => Show ((Vector3 \\\ Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Universe row, Num a) => LinearTransform ((->) row) Vector2 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector2 a -> ((->) row :*: Vector2) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector2) a -> (row -> a) -> Vector2 a Source #

Transposable ((->) row) Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

transpose_impl :: ((->) row :*: Vector2) a -> (Vector2 :*: (->) row) a Source #

Num a => Indexable (Vector2 :*: Vector2) a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => Monoid ((Vector2 :*: Vector2) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => Semigroup ((Vector2 :*: Vector2) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => Num ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

(Fractional a, ConjugateSymmetric a) => Fractional ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Linear

Show (f a) => Show ((Vector2 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

showsPrec :: Int -> (Vector2 :*: f) a -> ShowS #

show :: (Vector2 :*: f) a -> String #

showList :: [(Vector2 :*: f) a] -> ShowS #

(Num a, ConjugateSymmetric a) => ConjugateSymmetric ((Vector2 :*: Vector2) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector2

(ConjugateSymmetric a, Num a) => StandardBasis ((Dual :*: Vector2) a) Source #

https://en.wikipedia.org/wiki/Dual_space

Instance details

Defined in Math.Matrix.Covector

Num a => VectorSpace ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector1 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector3) a) Source #

2 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector2 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector4) a) Source #

2 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector2 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector2 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector2 :*: (->) col) a) Source #

Methods

vzero :: (Vector2 :*: (->) col) a Source #

vnegate :: (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

(%+) :: (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

(%*) :: Scalar ((Vector2 :*: (->) col) a) -> (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

Num a => VectorSpace ((Vector3 :*: Vector2) a) Source #

3 x 2 matrices

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector2) a) Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector2) a) Source #

Num a => VectorSpace (((->) row :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector2) a) Source #

Methods

vzero :: ((->) row :*: Vector2) a Source #

vnegate :: ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

(%+) :: ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

(%*) :: Scalar (((->) row :*: Vector2) a) -> ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

Optimal ((Vector2 :*: Vector2) Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector2) Int32) Source #

Optimal ((Vector2 :*: Vector2) Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector2) Float) Source #

Optimal ((Vector2 :*: Vector4) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector4) Int16) Source #

Optimal ((Vector4 :*: Vector2) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector4 :*: Vector2) Int16) Source #

(Fractional a, ConjugateSymmetric a) => Group ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

PpShow (f a) => PpShow ((Vector2 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

pp :: (Vector2 :*: f) a -> Doc Source #

data Codiagonal Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

type Vector1 :+: Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

type Vector2 :+: Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

type Vector2 :+: Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector2 :+: Stream Source # 
Instance details

Defined in Math.Matrix.VectorConversions

type Vector2 \\ a Source # 
Instance details

Defined in Math.Matrix.Vector2

type Vector2 \\ a = Vector1 a
data (Vector2 \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector2

data (Vector3 \\\ Vector2) a Source # 
Instance details

Defined in Math.Matrix.Vector3

data Closure str (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

data Closure str (Vector2 a) = Vector2Closure (Vector2 (Closure str a))
type Rep (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Rep (Vector2 a) = D1 ('MetaData "Vector2" "Math.Matrix.Interface" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "Vector2" 'PrefixI 'True) (S1 ('MetaSel ('Just "xcoord2") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "ycoord2") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type Coordinate (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar (Vector2 a) = a
type Optimized (Vector2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized (Vector2 Int64) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized (Vector2 Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

data Fold (Vector2 a) b Source # 
Instance details

Defined in Math.Matrix.Vector2

data Fold (Vector2 a) b = Vector2Fold (a -> a -> b)
type Scalar ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector1 :*: Vector2) a) = a
type Scalar ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector2 :*: Vector1) a) = a
type Scalar ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

type Scalar ((Vector2 :*: Vector2) a) = a
type Scalar ((Vector2 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector2 :*: Vector3) a) = a
type Scalar ((Vector2 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector2 :*: Vector4) a) = a
type Scalar ((Vector2 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector2 :*: (->) col) a) = a
type Scalar ((Vector3 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector2) a) = a
type Scalar ((Vector4 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector2) a) = a
type Scalar (((->) row :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector2) a) = a
type Optimized ((Vector2 :*: Vector2) Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector2 :*: Vector2) Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector2 :*: Vector4) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector4 :*: Vector2) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

data Vector3 s Source #

Three element vector

Constructors

Vector3 

Fields

Instances

Instances details
MonadZip Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

mzip :: Vector3 a -> Vector3 b -> Vector3 (a, b) #

mzipWith :: (a -> b -> c) -> Vector3 a -> Vector3 b -> Vector3 c #

munzip :: Vector3 (a, b) -> (Vector3 a, Vector3 b) #

Foldable Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Vector3 a -> m #

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

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

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

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

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

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

toList :: Vector3 a -> [a] #

null :: Vector3 a -> Bool #

length :: Vector3 a -> Int #

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

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

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

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

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

Traversable Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

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

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

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

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

Applicative Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pure :: a -> Vector3 a #

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

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

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

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

Functor Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

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

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

Monad Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

(>>=) :: Vector3 a -> (a -> Vector3 b) -> Vector3 b #

(>>) :: Vector3 a -> Vector3 b -> Vector3 b #

return :: a -> Vector3 a #

UpdateableMatrixDimension Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

write_row :: Applicative h => h a -> Vector3 ((Vector3 :*: h) a -> (Vector3 :*: h) a) Source #

write_column :: Applicative h => h a -> Vector3 ((h :*: Vector3) a -> (h :*: Vector3) a) Source #

DifferentialOperator Vector3 Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

partial :: DifferentiallyClosed a => (Vector3 a -> a) -> Vector3 a -> Vector3 a Source #

CircularComonad Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

rotate :: Vector3 a -> Vector3 a Source #

Coapplicative Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

coeval :: Vector3 a -> a Source #

colambda :: (Vector3 a -> Vector3 b) -> Vector3 (a -> b) Source #

Comonad Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

extract :: Vector3 a -> a Source #

duplicate :: Vector3 a -> Vector3 (Vector3 a) Source #

extend :: (Vector3 a -> b) -> Vector3 a -> Vector3 b Source #

(=>>) :: Vector3 a -> (Vector3 a -> b) -> Vector3 b Source #

(.>>) :: Vector3 a -> b -> Vector3 b Source #

FiniteComonad Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

PpShowF Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

ppf :: PpShow a => Vector3 a -> Doc Source #

PpShowVerticalF Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

ppf_vertical :: PpShow a => Vector3 a -> Doc Source #

Unfoldable Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

unfoldF :: forall (m :: Type -> Type) s a. Monad m => StateT s m a -> StateT s m (Vector3 a) Source #

AppendableVector Vector1 Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector1 :+: Vector3 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector3 a -> (Vector1 :+: Vector3) a Source #

AppendableVector Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector3 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector3 a -> Vector1 a -> (Vector3 :+: Vector1) a Source #

AppendableVector Vector3 Stream Source # 
Instance details

Defined in Math.Number.Stream

Associated Types

type Vector3 :+: Stream :: Type -> Type Source #

Methods

(||>>) :: Vector3 a -> Stream a -> (Vector3 :+: Stream) a Source #

CodiagonalMatrix Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data Codiagonal Vector3 a Source #

type Vector3 \\ a Source #

Num a => Diagonalizable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Floating a, Ord a, ConjugateSymmetric a) => EigenDecomposable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => Indexable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Fractional a => Invertible Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

ProjectionSpace Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data (Vector3 \\\ Vector1) a Source #

ProjectionSpace Vector3 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data (Vector3 \\\ Vector2) a Source #

SplittableVector Vector1 Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector1 :+: Vector3) a -> (Vector1 a, Vector3 a) Source #

SplittableVector Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector3 :+: Vector1) a -> (Vector3 a, Vector1 a) Source #

Num a => Traceable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

HasIdentityLinear Vector3 LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => LinearTransform Vector1 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector2 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector3

LinearTransform Vector3 Vector3 Float Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => ProjectionDual Vector3 Dual a Source # 
Instance details

Defined in Math.Matrix.Linear

Transposable Vector1 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector2 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector4 a Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector3 a Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Stream Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector3 (f a)) (Dual (f a)) -> (Vector3 :*: Dual) (f a) Source #

linear :: (Vector3 :*: Dual) (f a) -> LinearMap (Vector3 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector3 a) (col -> a) -> (Vector3 :*: (->) col) a Source #

linear :: (Vector3 :*: (->) col) a -> LinearMap (Vector3 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector3 a) -> ((->) row :*: Vector3) a Source #

linear :: ((->) row :*: Vector3) a -> LinearMap (row -> a) (Vector3 a) Source #

(Monad str, Limiting str a) => Limiting str (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data Closure str (Vector3 a) Source #

Methods

limit :: str (Vector3 a) -> Closure str (Vector3 a) Source #

approximations :: Closure str (Vector3 a) -> str (Vector3 a) Source #

Lift a => Lift (Vector3 a :: Type) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => Vector3 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector3 a -> Code m (Vector3 a) #

(Closed a, Num a, ConjugateSymmetric a) => VectorCrossProduct (Vector3 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Closed a, Num a, ConjugateSymmetric a) => VectorLaplacian (Vector3 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, Universe col) => LinearTransform Vector3 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector3 :*: (->) col) a -> Vector3 a Source #

(<<*>) :: (Vector3 :*: (->) col) a -> Vector3 a -> col -> a Source #

Transposable Vector3 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

transpose_impl :: (Vector3 :*: (->) row) a -> ((->) row :*: Vector3) a Source #

Lift ((Vector3 :*: Vector3) Integer) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => (Vector3 :*: Vector3) Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (Vector3 :*: Vector3) Integer -> Code m ((Vector3 :*: Vector3) Integer) #

Data a => Data (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector3 a -> c (Vector3 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector3 a) #

toConstr :: Vector3 a -> Constr #

dataTypeOf :: Vector3 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector3 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector3 a)) #

gmapT :: (forall b. Data b => b -> b) -> Vector3 a -> Vector3 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector3 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector3 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vector3 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector3 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector3 a -> m (Vector3 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector3 a -> m (Vector3 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector3 a -> m (Vector3 a) #

Applicative (Codiagonal Vector3) Source # 
Instance details

Defined in Math.Matrix.Vector3

Functor (Codiagonal Vector3) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

fmap :: (a -> b) -> Codiagonal Vector3 a -> Codiagonal Vector3 b #

(<$) :: a -> Codiagonal Vector3 b -> Codiagonal Vector3 a #

Num s => Monoid (Vector3 s) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

mempty :: Vector3 s #

mappend :: Vector3 s -> Vector3 s -> Vector3 s #

mconcat :: [Vector3 s] -> Vector3 s #

Num s => Semigroup (Vector3 s) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

(<>) :: Vector3 s -> Vector3 s -> Vector3 s #

sconcat :: NonEmpty (Vector3 s) -> Vector3 s #

stimes :: Integral b => b -> Vector3 s -> Vector3 s #

Generic a => Generic (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Rep (Vector3 a) :: Type -> Type #

Methods

from :: Vector3 a -> Rep (Vector3 a) x #

to :: Rep (Vector3 a) x -> Vector3 a #

Num a => Num (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

(+) :: Vector3 a -> Vector3 a -> Vector3 a #

(-) :: Vector3 a -> Vector3 a -> Vector3 a #

(*) :: Vector3 a -> Vector3 a -> Vector3 a #

negate :: Vector3 a -> Vector3 a #

abs :: Vector3 a -> Vector3 a #

signum :: Vector3 a -> Vector3 a #

fromInteger :: Integer -> Vector3 a #

Read a => Read (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Show a => Show (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

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

show :: Vector3 a -> String #

showList :: [Vector3 a] -> ShowS #

Binary s => Binary (Vector3 s) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

put :: Vector3 s -> Put #

get :: Get (Vector3 s) #

putList :: [Vector3 s] -> Put #

ConjugateSymmetric a => ConjugateSymmetric (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

conj :: Vector3 a -> Vector3 a Source #

Num a => CoordinateSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Coordinate (Vector3 a) Source #

InnerProductSpace (Vector3 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

(ConjugateSymmetric a, Num a) => InnerProductSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

(%.) :: Vector3 a -> Vector3 a -> Scalar (Vector3 a) Source #

Num a => LieAlgebra (Vector3 a) Source #

https://en.wikipedia.org/wiki/Lie_algebra

Instance details

Defined in Math.Matrix.Vector3

Methods

(%<>%) :: Vector3 a -> Vector3 a -> Vector3 a Source #

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => StandardBasis (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => VectorSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar (Vector3 a) Source #

Optimal (Vector3 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector3 Float) Source #

Num s => Group (Vector3 s) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

ginvert :: Vector3 s -> Vector3 s Source #

ShowPrecision s => ShowPrecision (Vector3 s) Source # 
Instance details

Defined in Math.Matrix.Vector3

MedianAlgebra s => MedianAlgebra (Vector3 s) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

med :: Vector3 s -> Vector3 s -> Vector3 s -> Vector3 s Source #

PpShow a => PpShow (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pp :: Vector3 a -> Doc Source #

Universe a => Universe (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Visitor (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data Fold (Vector3 a) :: Type -> Type Source #

Methods

visit :: Fold (Vector3 a) a0 -> Vector3 a -> a0 Source #

Eq a => Eq (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

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

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

Ord a => Ord (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

compare :: Vector3 a -> Vector3 a -> Ordering #

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

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

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

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

max :: Vector3 a -> Vector3 a -> Vector3 a #

min :: Vector3 a -> Vector3 a -> Vector3 a #

(ConjugateSymmetric a, Num a) => Dualizable (Vector3 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector3 a -> Scalar (Vector3 a)) -> Dual (Vector3 a) Source #

bracket :: Dual (Vector3 a) -> Vector3 a -> Scalar (Vector3 a) Source #

(Closed a, Num a, ConjugateSymmetric a) => VectorDerivative (Vector3 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

Num a => DecomposableVectorSpace (Vector3 a) ((->) ThreeD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector3 a) -> res) -> Vector3 a -> ThreeD -> res Source #

project :: Vector3 a -> ThreeD -> Scalar (Vector3 a) Source #

Applicative (Vector3 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pure :: a -> (Vector3 \\\ Vector1) a #

(<*>) :: (Vector3 \\\ Vector1) (a -> b) -> (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b #

liftA2 :: (a -> b -> c) -> (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) c #

(*>) :: (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) b #

(<*) :: (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) a #

Applicative (Vector3 \\\ Vector2) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pure :: a -> (Vector3 \\\ Vector2) a #

(<*>) :: (Vector3 \\\ Vector2) (a -> b) -> (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b #

liftA2 :: (a -> b -> c) -> (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) c #

(*>) :: (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) b #

(<*) :: (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) a #

Functor (Vector3 \\\ Vector1) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

fmap :: (a -> b) -> (Vector3 \\\ Vector1) a -> (Vector3 \\\ Vector1) b #

(<$) :: a -> (Vector3 \\\ Vector1) b -> (Vector3 \\\ Vector1) a #

Functor (Vector3 \\\ Vector2) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

fmap :: (a -> b) -> (Vector3 \\\ Vector2) a -> (Vector3 \\\ Vector2) b #

(<$) :: a -> (Vector3 \\\ Vector2) b -> (Vector3 \\\ Vector2) a #

Show a => Show (Codiagonal Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Show a, Monad str, Limiting str a) => Show (Closure str (Vector3 a)) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

showsPrec :: Int -> Closure str (Vector3 a) -> ShowS #

show :: Closure str (Vector3 a) -> String #

showList :: [Closure str (Vector3 a)] -> ShowS #

(Monad str, PpShow a, Limiting str a) => PpShow (Closure str (Vector3 a)) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

pp :: Closure str (Vector3 a) -> Doc Source #

ProjectionSpace (Vector3 \\\ Vector1) Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data ((Vector3 \\\ Vector1) \\\ Vector1) a Source #

Show a => Show ((Vector3 \\\ Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Show a => Show ((Vector3 \\\ Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Universe row, Num a) => LinearTransform ((->) row) Vector3 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector3 a -> ((->) row :*: Vector3) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector3) a -> (row -> a) -> Vector3 a Source #

Transposable ((->) row) Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

transpose_impl :: ((->) row :*: Vector3) a -> (Vector3 :*: (->) row) a Source #

(Num a, ConjugateSymmetric a) => Monoid ((Vector3 :*: Vector3) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector3

(ConjugateSymmetric a, Num a) => Semigroup ((Vector3 :*: Vector3) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => Num ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Fractional a, ConjugateSymmetric a) => Fractional ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Show (f a) => Show ((Vector3 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

showsPrec :: Int -> (Vector3 :*: f) a -> ShowS #

show :: (Vector3 :*: f) a -> String #

showList :: [(Vector3 :*: f) a] -> ShowS #

(ConjugateSymmetric a, Num a) => ConjugateSymmetric ((Vector3 :*: Vector3) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector3

(Floating a, ConjugateSymmetric a) => InnerProductSpace ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LieAlgebra ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

(Floating a, ConjugateSymmetric a) => NormedSpace ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => StandardBasis ((Dual :*: Vector3) a) Source #

https://en.wikipedia.org/wiki/Dual_space

Instance details

Defined in Math.Matrix.Linear

Num a => VectorSpace ((Vector1 :*: Vector3) a) Source #

1 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector1 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector3) a) Source #

2 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector2 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector1) a) Source #

3 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector2) a) Source #

3 x 2 matrices

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector3) a) Source #

3 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector4) a) Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector3 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector3 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector3 :*: (->) col) a) Source #

Methods

vzero :: (Vector3 :*: (->) col) a Source #

vnegate :: (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

(%+) :: (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

(%*) :: Scalar ((Vector3 :*: (->) col) a) -> (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

Num a => VectorSpace ((Vector4 :*: Vector3) a) Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector3) a) Source #

Num a => VectorSpace (((->) row :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector3) a) Source #

Methods

vzero :: ((->) row :*: Vector3) a Source #

vnegate :: ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(%+) :: ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(%*) :: Scalar (((->) row :*: Vector3) a) -> ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(Fractional a, ConjugateSymmetric a) => Group ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

data Codiagonal Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

type Vector1 :+: Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector3 :+: Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector3 :+: Stream Source # 
Instance details

Defined in Math.Number.Stream

type Vector3 \\ a Source # 
Instance details

Defined in Math.Matrix.Vector3

type Vector3 \\ a = Vector2 a
data (Vector3 \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector3

data (Vector3 \\\ Vector2) a Source # 
Instance details

Defined in Math.Matrix.Vector3

data Closure str (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

data Closure str (Vector3 a) = Vector3Closure (Vector3 (Closure str a))
type Rep (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Rep (Vector3 a) = D1 ('MetaData "Vector3" "Math.Matrix.Interface" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "Vector3" 'PrefixI 'True) (S1 ('MetaSel ('Just "xcoord3") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Just "ycoord3") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "zcoord3") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))
type Coordinate (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar (Vector3 a) = a
type Optimized (Vector3 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

data Fold (Vector3 a) b Source # 
Instance details

Defined in Math.Matrix.Vector3

data Fold (Vector3 a) b = Vector3Fold (a -> a -> a -> b)
data ((Vector3 \\\ Vector1) \\\ Vector1) a Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector1 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector1 :*: Vector3) a) = a
type Scalar ((Vector2 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector2 :*: Vector3) a) = a
type Scalar ((Vector3 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector1) a) = a
type Scalar ((Vector3 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector2) a) = a
type Scalar ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

type Scalar ((Vector3 :*: Vector3) a) = a
type Scalar ((Vector3 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector3 :*: Vector4) a) = a
type Scalar ((Vector3 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector3 :*: (->) col) a) = a
type Scalar ((Vector4 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector3) a) = a
type Scalar (((->) row :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector3) a) = a

data Vector4 s Source #

Constructors

Vector4 

Fields

Instances

Instances details
MonadZip Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

mzip :: Vector4 a -> Vector4 b -> Vector4 (a, b) #

mzipWith :: (a -> b -> c) -> Vector4 a -> Vector4 b -> Vector4 c #

munzip :: Vector4 (a, b) -> (Vector4 a, Vector4 b) #

Foldable Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Vector4 a -> m #

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

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

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

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

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

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

toList :: Vector4 a -> [a] #

null :: Vector4 a -> Bool #

length :: Vector4 a -> Int #

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

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

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

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

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

Traversable Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

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

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

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

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

Applicative Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

pure :: a -> Vector4 a #

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

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

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

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

Functor Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

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

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

Monad Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

(>>=) :: Vector4 a -> (a -> Vector4 b) -> Vector4 b #

(>>) :: Vector4 a -> Vector4 b -> Vector4 b #

return :: a -> Vector4 a #

UpdateableMatrixDimension Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

write_row :: Applicative h => h a -> Vector4 ((Vector4 :*: h) a -> (Vector4 :*: h) a) Source #

write_column :: Applicative h => h a -> Vector4 ((h :*: Vector4) a -> (h :*: Vector4) a) Source #

DifferentialOperator Vector4 Source # 
Instance details

Defined in Math.Matrix.LinearOperations

Methods

partial :: DifferentiallyClosed a => (Vector4 a -> a) -> Vector4 a -> Vector4 a Source #

Comonad Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

extract :: Vector4 a -> a Source #

duplicate :: Vector4 a -> Vector4 (Vector4 a) Source #

extend :: (Vector4 a -> b) -> Vector4 a -> Vector4 b Source #

(=>>) :: Vector4 a -> (Vector4 a -> b) -> Vector4 b Source #

(.>>) :: Vector4 a -> b -> Vector4 b Source #

PpShowF Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

ppf :: PpShow a => Vector4 a -> Doc Source #

PpShowVerticalF Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

ppf_vertical :: PpShow a => Vector4 a -> Doc Source #

Unfoldable Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

unfoldF :: forall (m :: Type -> Type) s a. Monad m => StateT s m a -> StateT s m (Vector4 a) Source #

StreamBuilder str => AppendableVector Vector4 str Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector4 :+: str :: Type -> Type Source #

Methods

(||>>) :: Vector4 a -> str a -> (Vector4 :+: str) a Source #

CodiagonalMatrix Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

data Codiagonal Vector4 a Source #

type Vector4 \\ a Source #

Num a => Diagonalizable Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => Indexable Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Fractional a => Invertible Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => Traceable Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

HasIdentityLinear Vector4 LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => LinearTransform Vector1 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector2 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector4

LinearTransform Vector4 Vector4 Float Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => ProjectionDual Vector4 Dual a Source # 
Instance details

Defined in Math.Matrix.LinearOperations

Transposable Vector1 Vector4 a Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector2 Vector4 a Source #

2 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector3 Vector4 a Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector1 a Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector2 a Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector3 a Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector4 a Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Stream Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector4 (f a)) (Dual (f a)) -> (Vector4 :*: Dual) (f a) Source #

linear :: (Vector4 :*: Dual) (f a) -> LinearMap (Vector4 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector4 a) (col -> a) -> (Vector4 :*: (->) col) a Source #

linear :: (Vector4 :*: (->) col) a -> LinearMap (Vector4 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector4 a) -> ((->) row :*: Vector4) a Source #

linear :: ((->) row :*: Vector4) a -> LinearMap (row -> a) (Vector4 a) Source #

(Monad str, Limiting str a) => Limiting str (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

data Closure str (Vector4 a) Source #

Methods

limit :: str (Vector4 a) -> Closure str (Vector4 a) Source #

approximations :: Closure str (Vector4 a) -> str (Vector4 a) Source #

Lift a => Lift (Vector4 a :: Type) Source # 
Instance details

Defined in Math.Matrix.QuasiQuoter

Methods

lift :: Quote m => Vector4 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector4 a -> Code m (Vector4 a) #

(Closed a, ConjugateSymmetric a, LinearTransform Vector4 Vector1 a) => VectorLaplacian (Vector4 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.LinearOperations

(Universe col, Num a) => LinearTransform Vector4 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector4 :*: (->) col) a -> Vector4 a Source #

(<<*>) :: (Vector4 :*: (->) col) a -> Vector4 a -> col -> a Source #

Transposable Vector4 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

transpose_impl :: (Vector4 :*: (->) row) a -> ((->) row :*: Vector4) a Source #

Data a => Data (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector4 a -> c (Vector4 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector4 a) #

toConstr :: Vector4 a -> Constr #

dataTypeOf :: Vector4 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector4 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector4 a)) #

gmapT :: (forall b. Data b => b -> b) -> Vector4 a -> Vector4 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector4 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector4 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vector4 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector4 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector4 a -> m (Vector4 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector4 a -> m (Vector4 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector4 a -> m (Vector4 a) #

Applicative (Codiagonal Vector4) Source # 
Instance details

Defined in Math.Matrix.Vector4

Functor (Codiagonal Vector4) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

fmap :: (a -> b) -> Codiagonal Vector4 a -> Codiagonal Vector4 b #

(<$) :: a -> Codiagonal Vector4 b -> Codiagonal Vector4 a #

Num s => Monoid (Vector4 s) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

mempty :: Vector4 s #

mappend :: Vector4 s -> Vector4 s -> Vector4 s #

mconcat :: [Vector4 s] -> Vector4 s #

Num s => Semigroup (Vector4 s) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

(<>) :: Vector4 s -> Vector4 s -> Vector4 s #

sconcat :: NonEmpty (Vector4 s) -> Vector4 s #

stimes :: Integral b => b -> Vector4 s -> Vector4 s #

Generic a => Generic (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Rep (Vector4 a) :: Type -> Type #

Methods

from :: Vector4 a -> Rep (Vector4 a) x #

to :: Rep (Vector4 a) x -> Vector4 a #

Num a => Num (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

(+) :: Vector4 a -> Vector4 a -> Vector4 a #

(-) :: Vector4 a -> Vector4 a -> Vector4 a #

(*) :: Vector4 a -> Vector4 a -> Vector4 a #

negate :: Vector4 a -> Vector4 a #

abs :: Vector4 a -> Vector4 a #

signum :: Vector4 a -> Vector4 a #

fromInteger :: Integer -> Vector4 a #

Read a => Read (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Show a => Show (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

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

show :: Vector4 a -> String #

showList :: [Vector4 a] -> ShowS #

Binary s => Binary (Vector4 s) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

put :: Vector4 s -> Put #

get :: Get (Vector4 s) #

putList :: [Vector4 s] -> Put #

ConjugateSymmetric a => ConjugateSymmetric (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

conj :: Vector4 a -> Vector4 a Source #

Num a => CoordinateSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Coordinate (Vector4 a) Source #

InnerProductSpace (Vector4 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => InnerProductSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

(%.) :: Vector4 a -> Vector4 a -> Scalar (Vector4 a) Source #

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => StandardBasis (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => VectorSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar (Vector4 a) Source #

Optimal (Vector4 Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector4 Int32) Source #

Optimal (Vector4 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector4 Float) Source #

ShowPrecision s => ShowPrecision (Vector4 s) Source # 
Instance details

Defined in Math.Matrix.Vector4

MedianAlgebra s => MedianAlgebra (Vector4 s) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

med :: Vector4 s -> Vector4 s -> Vector4 s -> Vector4 s Source #

PpShow a => PpShow (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

pp :: Vector4 a -> Doc Source #

Universe a => Universe (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

IdVisitor (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

idFold :: Fold (Vector4 a) (Vector4 a) Source #

Visitor (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

data Fold (Vector4 a) :: Type -> Type Source #

Methods

visit :: Fold (Vector4 a) a0 -> Vector4 a -> a0 Source #

Eq a => Eq (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

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

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

Ord a => Ord (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

compare :: Vector4 a -> Vector4 a -> Ordering #

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

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

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

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

max :: Vector4 a -> Vector4 a -> Vector4 a #

min :: Vector4 a -> Vector4 a -> Vector4 a #

(ConjugateSymmetric a, Num a) => Dualizable (Vector4 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector4 a -> Scalar (Vector4 a)) -> Dual (Vector4 a) Source #

bracket :: Dual (Vector4 a) -> Vector4 a -> Scalar (Vector4 a) Source #

(Num a, Closed a, ConjugateSymmetric a, LinearTransform Vector4 Vector1 a) => VectorDerivative (Vector4 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.LinearOperations

Num a => DecomposableVectorSpace (Vector4 a) ((->) FourD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector4 a) -> res) -> Vector4 a -> FourD -> res Source #

project :: Vector4 a -> FourD -> Scalar (Vector4 a) Source #

Show a => Show (Codiagonal Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Optimal (Vector4 Int16, Vector4 Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized (Vector4 Int16, Vector4 Int16) Source #

(Universe row, Num a) => LinearTransform ((->) row) Vector4 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector4 a -> ((->) row :*: Vector4) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector4) a -> (row -> a) -> Vector4 a Source #

Transposable ((->) row) Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

transpose_impl :: ((->) row :*: Vector4) a -> (Vector4 :*: (->) row) a Source #

(Num a, ConjugateSymmetric a) => Monoid ((Vector4 :*: Vector4) a) Source #

see "Lawvere,Rosebrugh: Sets for mathematics", pg. 167.

Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => Semigroup ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => Num ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Show (f a) => Show ((Vector4 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

showsPrec :: Int -> (Vector4 :*: f) a -> ShowS #

show :: (Vector4 :*: f) a -> String #

showList :: [(Vector4 :*: f) a] -> ShowS #

ConjugateSymmetric a => ConjugateSymmetric ((Vector4 :*: Vector4) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector4

(Floating a, ConjugateSymmetric a) => InnerProductSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LieAlgebra ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

(Floating a, ConjugateSymmetric a) => NormedSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Num a => VectorSpace ((Vector1 :*: Vector4) a) Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector1 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector4) a) Source #

2 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector2 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector4) a) Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector3 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector1) a) Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector2) a) Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector3) a) Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector4 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector4 :*: (->) col) a) Source #

Methods

vzero :: (Vector4 :*: (->) col) a Source #

vnegate :: (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

(%+) :: (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

(%*) :: Scalar ((Vector4 :*: (->) col) a) -> (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

Num a => VectorSpace (((->) row :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector4) a) Source #

Methods

vzero :: ((->) row :*: Vector4) a Source #

vnegate :: ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

(%+) :: ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

(%*) :: Scalar (((->) row :*: Vector4) a) -> ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

Optimal ((Vector2 :*: Vector4) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector2 :*: Vector4) Int16) Source #

Optimal ((Vector4 :*: Vector2) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector4 :*: Vector2) Int16) Source #

Optimal ((Vector4 :*: Vector4) Int8) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Optimized ((Vector4 :*: Vector4) Int8) Source #

(Fractional a, ConjugateSymmetric a) => Group ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

PpShow (f a) => PpShow ((Vector4 :*: f) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

pp :: (Vector4 :*: f) a -> Doc Source #

data Codiagonal Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector4 :+: str Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector4 :+: str = str
type Vector4 \\ a Source # 
Instance details

Defined in Math.Matrix.Vector4

type Vector4 \\ a = Vector3 a
data Closure str (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Rep (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Rep (Vector4 a) = D1 ('MetaData "Vector4" "Math.Matrix.Interface" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "Vector4" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tcoord4") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "xcoord4") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "ycoord4") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "zcoord4") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))
type Coordinate (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar (Vector4 a) = a
type Optimized (Vector4 Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized (Vector4 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

data Fold (Vector4 a) b Source # 
Instance details

Defined in Math.Matrix.Vector4

data Fold (Vector4 a) b = Vector4Fold (a -> a -> a -> a -> b)
type Optimized (Vector4 Int16, Vector4 Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Scalar ((Vector1 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector1 :*: Vector4) a) = a
type Scalar ((Vector2 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector2 :*: Vector4) a) = a
type Scalar ((Vector3 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector3 :*: Vector4) a) = a
type Scalar ((Vector4 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector1) a) = a
type Scalar ((Vector4 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector2) a) = a
type Scalar ((Vector4 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector3) a) = a
type Scalar ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Vector4

type Scalar ((Vector4 :*: Vector4) a) = a
type Scalar ((Vector4 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar ((Vector4 :*: (->) col) a) = a
type Scalar (((->) row :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Simple

type Scalar (((->) row :*: Vector4) a) = a
type Optimized ((Vector2 :*: Vector4) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector4 :*: Vector2) Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

type Optimized ((Vector4 :*: Vector4) Int8) Source # 
Instance details

Defined in Math.Matrix.SIMD

matrix :: (Functor m, Functor n) => (a -> b -> c) -> m a -> n b -> (m :*: n) c Source #

This method of matrix construction is especially nice. This is the functoriality of the tensor product.

inverse_matrix :: (Contravariant m, Contravariant n) => (g a -> c -> b) -> m (n c) -> n b -> (m :*: g) a Source #

left_inverse_matrix :: (Contravariant m, Functor n) => (g a -> c -> b) -> m (n b) -> n c -> (m :*: g) a Source #

right_inverse_matrix :: (Functor m, Contravariant n) => (t -> a -> b) -> m t -> n b -> (m :*: n) a Source #

inverse_fix :: Contravariant p => (a -> a) -> p a Source #

inverse_fix2 :: Contravariant p => (a -> b) -> (b -> a) -> p a Source #

matrix_compose :: (Functor m, Functor n, Category cat) => m (cat b c) -> n (cat a b) -> (m :*: n) (cat a c) Source #

tensor_product :: (Num a, Functor m, Functor n) => m a -> n a -> (m :*: n) a Source #

tensor_product_lin :: (Linearizable arr (:*:) f g a, Num a, Functor f, Functor g) => f a -> g a -> arr (f a) (g a) Source #

bilinear_impl :: (VectorSpace (g c), Scalar (g c) ~ c, Indexable f c, Indexable g c, Integral c, VectorSpace ((f :*: g) c)) => (f c -> f c -> g c) -> f c -> f c -> (f :*: g) c Source #

https://en.wikipedia.org/wiki/Tensor_product

bilinearity : \[f (a + b,c) = f(a, c) + f(b, c)\] \[f (k b, c) = k f(b, c)\] \[f (a, b + c) = f(a, b) + f(a,c)\] \[f (a, k c) = k f(a, c)\] https://en.wikipedia.org/wiki/Bilinear_map

applicativeMatrix :: (Applicative f, Functor m, Functor n) => f (a -> b -> c) -> (m :*: f) a -> (n :*: f) b -> (m :*: n) (f c) Source #

(>*<) :: (Applicative f, Functor m, Functor n) => f (a -> b -> c) -> ((m :*: f) a, (n :*: f) b) -> (m :*: n) (f c) Source #

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

Associated Types

type Scalar v Source #

Methods

vzero :: v Source #

vnegate :: v -> v Source #

(%+) :: v -> v -> v infixl 6 Source #

(%*) :: Scalar v -> v -> v infix 7 Source #

Instances

Instances details
VectorSpace Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

type Scalar Dimension Source #

VectorSpace R Source #

R as an infinite dimensional vector space over the rationals.

Instance details

Defined in Math.Number.R

Associated Types

type Scalar R Source #

Methods

vzero :: R Source #

vnegate :: R -> R Source #

(%+) :: R -> R -> R Source #

(%*) :: Scalar R -> R -> R Source #

VectorSpace R Source # 
Instance details

Defined in Math.Number.Real

Associated Types

type Scalar R Source #

Methods

vzero :: R Source #

vnegate :: R -> R Source #

(%+) :: R -> R -> R Source #

(%*) :: Scalar R -> R -> R Source #

VectorSpace AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar AbsorbedDose Source #

VectorSpace Acceleration Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Acceleration Source #

VectorSpace Angle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Angle Source #

VectorSpace Capacitance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Capacitance Source #

VectorSpace CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar CatalyticActivity Source #

VectorSpace Charge Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Charge Source #

VectorSpace Conductance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Conductance Source #

VectorSpace CubicLength Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar CubicLength Source #

VectorSpace Current Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Current Source #

VectorSpace DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar DegreesAngle Source #

VectorSpace DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar DegreesFahrenheit Source #

VectorSpace DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar DegreesTemperature Source #

VectorSpace Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Dimensionless Source #

VectorSpace Energy Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Energy Source #

VectorSpace EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar EquivalentDose Source #

VectorSpace Flux Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Flux Source #

VectorSpace FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar FluxDensity Source #

VectorSpace Force Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Force Source #

VectorSpace Frequency Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Frequency Source #

VectorSpace Illuminance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Illuminance Source #

VectorSpace Inductance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Inductance Source #

VectorSpace Information Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Information Source #

VectorSpace Intensity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Intensity Source #

VectorSpace Length Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Length Source #

VectorSpace LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar LuminousFlux Source #

VectorSpace Mass Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Mass Source #

VectorSpace Percentage Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Percentage Source #

VectorSpace Power Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Power Source #

VectorSpace Pressure Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Pressure Source #

VectorSpace Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Radioactivity Source #

VectorSpace Resistance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Resistance Source #

VectorSpace SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar SolidAngle Source #

VectorSpace SoundLevel Source #

NOTE: additive operations mapped to multiplicative. Notice this reduces the possible range of SoundLevel values to around -300..300 dB based on possible exponents in Double.

Instance details

Defined in Math.Number.Units

Associated Types

type Scalar SoundLevel Source #

VectorSpace SquareLength Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar SquareLength Source #

VectorSpace Substance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Substance Source #

VectorSpace Temperature Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Temperature Source #

VectorSpace Time Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Time Source #

VectorSpace Torque Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Torque Source #

VectorSpace Velocity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Velocity Source #

VectorSpace Voltage Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Voltage Source #

VectorSpace Integer Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar Integer Source #

VectorSpace Double Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar Double Source #

VectorSpace Float Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar Float Source #

VectorSpace Int Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar Int Source #

RealFloat a => VectorSpace (Complex a) Source #

Note: Scalar (Complex a) = Complex a

Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Complex a) Source #

Num a => VectorSpace (First a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (First a) Source #

Methods

vzero :: First a Source #

vnegate :: First a -> First a Source #

(%+) :: First a -> First a -> First a Source #

(%*) :: Scalar (First a) -> First a -> First a Source #

Num a => VectorSpace (Last a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Last a) Source #

Methods

vzero :: Last a Source #

vnegate :: Last a -> Last a Source #

(%+) :: Last a -> Last a -> Last a Source #

(%*) :: Scalar (Last a) -> Last a -> Last a Source #

Num a => VectorSpace (Endo a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Endo a) Source #

Methods

vzero :: Endo a Source #

vnegate :: Endo a -> Endo a Source #

(%+) :: Endo a -> Endo a -> Endo a Source #

(%*) :: Scalar (Endo a) -> Endo a -> Endo a Source #

Floating a => VectorSpace (Product a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Product a) Source #

Num a => VectorSpace (Sum a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Sum a) Source #

Methods

vzero :: Sum a Source #

vnegate :: Sum a -> Sum a Source #

(%+) :: Sum a -> Sum a -> Sum a Source #

(%*) :: Scalar (Sum a) -> Sum a -> Sum a Source #

Integral a => VectorSpace (Ratio a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Ratio a) Source #

Methods

vzero :: Ratio a Source #

vnegate :: Ratio a -> Ratio a Source #

(%+) :: Ratio a -> Ratio a -> Ratio a Source #

(%*) :: Scalar (Ratio a) -> Ratio a -> Ratio a Source #

Num a => VectorSpace (FreeVectorSpace a) Source # 
Instance details

Defined in Math.Matrix.FreeVectorSpace

Associated Types

type Scalar (FreeVectorSpace a) Source #

VectorSpace k => VectorSpace (Basis k) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Basis k) Source #

Methods

vzero :: Basis k Source #

vnegate :: Basis k -> Basis k Source #

(%+) :: Basis k -> Basis k -> Basis k Source #

(%*) :: Scalar (Basis k) -> Basis k -> Basis k Source #

Num a => VectorSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Scalar (Vector1 a) Source #

Num a => VectorSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar (Vector2 a) Source #

Num a => VectorSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar (Vector3 a) Source #

Num a => VectorSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar (Vector4 a) Source #

(Num a, ConjugateSymmetric a, Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Vector1 a, Diagonalizable f a, LinearTransform f Vector1 a) => VectorSpace (Dual (f a)) Source # 
Instance details

Defined in Math.Matrix.Linear

Associated Types

type Scalar (Dual (f a)) Source #

Methods

vzero :: Dual (f a) Source #

vnegate :: Dual (f a) -> Dual (f a) Source #

(%+) :: Dual (f a) -> Dual (f a) -> Dual (f a) Source #

(%*) :: Scalar (Dual (f a)) -> Dual (f a) -> Dual (f a) Source #

Num a => VectorSpace (Quaternion a) Source # 
Instance details

Defined in Math.Matrix.Quaternion

Associated Types

type Scalar (Quaternion a) Source #

Methods

vzero :: Quaternion a Source #

vnegate :: Quaternion a -> Quaternion a Source #

(%+) :: Quaternion a -> Quaternion a -> Quaternion a Source #

(%*) :: Scalar (Quaternion a) -> Quaternion a -> Quaternion a Source #

Num r => VectorSpace (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

type Scalar (Quantity r) Source #

Num a => VectorSpace (Stream a) Source # 
Instance details

Defined in Math.Number.StreamInterface

Associated Types

type Scalar (Stream a) Source #

Methods

vzero :: Stream a Source #

vnegate :: Stream a -> Stream a Source #

(%+) :: Stream a -> Stream a -> Stream a Source #

(%*) :: Scalar (Stream a) -> Stream a -> Stream a Source #

VectorSpace (DUnit DAbsorbedDose) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DAbsorbedDose) Source #

VectorSpace (DUnit DAcceleration) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DAcceleration) Source #

VectorSpace (DUnit DAngle) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DAngle) Source #

VectorSpace (DUnit DCapacitance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DCapacitance) Source #

VectorSpace (DUnit DCatalyticActivity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DCatalyticActivity) Source #

VectorSpace (DUnit DCharge) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DCharge) Source #

VectorSpace (DUnit DConductance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DConductance) Source #

VectorSpace (DUnit DCubicLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DCubicLength) Source #

VectorSpace (DUnit DCurrent) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DCurrent) Source #

VectorSpace (DUnit DDimensionless) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DDimensionless) Source #

VectorSpace (DUnit DEnergy) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DEnergy) Source #

VectorSpace (DUnit DFlux) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DFlux) Source #

VectorSpace (DUnit DFluxDensity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DFluxDensity) Source #

VectorSpace (DUnit DForce) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DForce) Source #

VectorSpace (DUnit DFrequency) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DFrequency) Source #

VectorSpace (DUnit DIlluminance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DIlluminance) Source #

VectorSpace (DUnit DInductance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DInductance) Source #

VectorSpace (DUnit DLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DLength) Source #

VectorSpace (DUnit DLuminosity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DLuminosity) Source #

VectorSpace (DUnit DMass) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DMass) Source #

VectorSpace (DUnit DPower) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DPower) Source #

VectorSpace (DUnit DPressure) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DPressure) Source #

VectorSpace (DUnit DRadioactivity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DRadioactivity) Source #

VectorSpace (DUnit DResistance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DResistance) Source #

VectorSpace (DUnit DSolidAngle) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DSolidAngle) Source #

VectorSpace (DUnit DSquareLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DSquareLength) Source #

VectorSpace (DUnit DSubstance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DSubstance) Source #

VectorSpace (DUnit DTemperature) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DTemperature) Source #

VectorSpace (DUnit DTime) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DTime) Source #

VectorSpace (DUnit DTorque) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DTorque) Source #

VectorSpace (DUnit DVelocity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DVelocity) Source #

VectorSpace (DUnit DVoltage) Source # 
Instance details

Defined in Math.Number.TypeUnits

Associated Types

type Scalar (DUnit DVoltage) Source #

Num a => VectorSpace (I a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (I a) Source #

Methods

vzero :: I a Source #

vnegate :: I a -> I a Source #

(%+) :: I a -> I a -> I a Source #

(%*) :: Scalar (I a) -> I a -> I a Source #

Num a => VectorSpace (Interval a) Source # 
Instance details

Defined in Math.Tools.Median

Associated Types

type Scalar (Interval a) Source #

Num a => VectorSpace (Queue a) Source #

This version of queue is not a comonad, since empty queue is possible.

Instance details

Defined in Math.Tools.Queue

Associated Types

type Scalar (Queue a) Source #

Methods

vzero :: Queue a Source #

vnegate :: Queue a -> Queue a Source #

(%+) :: Queue a -> Queue a -> Queue a Source #

(%*) :: Scalar (Queue a) -> Queue a -> Queue a Source #

VectorSpace a => VectorSpace (Maybe a) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Maybe a) Source #

Methods

vzero :: Maybe a Source #

vnegate :: Maybe a -> Maybe a Source #

(%+) :: Maybe a -> Maybe a -> Maybe a Source #

(%*) :: Scalar (Maybe a) -> Maybe a -> Maybe a Source #

Num a => VectorSpace [a] Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar [a] Source #

Methods

vzero :: [a] Source #

vnegate :: [a] -> [a] Source #

(%+) :: [a] -> [a] -> [a] Source #

(%*) :: Scalar [a] -> [a] -> [a] Source #

(Num a, Num i, Ix i, Enum i) => VectorSpace (Array i a) Source # 
Instance details

Defined in Math.Matrix.Bitmap

Associated Types

type Scalar (Array i a) Source #

Methods

vzero :: Array i a Source #

vnegate :: Array i a -> Array i a Source #

(%+) :: Array i a -> Array i a -> Array i a Source #

(%*) :: Scalar (Array i a) -> Array i a -> Array i a Source #

Bilinear f g h a => VectorSpace (BilinearMap (f a, g a) (h a)) Source # 
Instance details

Defined in Math.Matrix.Bilinear

Associated Types

type Scalar (BilinearMap (f a, g a) (h a)) Source #

Methods

vzero :: BilinearMap (f a, g a) (h a) Source #

vnegate :: BilinearMap (f a, g a) (h a) -> BilinearMap (f a, g a) (h a) Source #

(%+) :: BilinearMap (f a, g a) (h a) -> BilinearMap (f a, g a) (h a) -> BilinearMap (f a, g a) (h a) Source #

(%*) :: Scalar (BilinearMap (f a, g a) (h a)) -> BilinearMap (f a, g a) (h a) -> BilinearMap (f a, g a) (h a) Source #

(Applicative f, Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) g g a, Diagonalizable g a, Applicative g, VectorSpace (f a), VectorSpace (g a), Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f g a, Num a) => VectorSpace (LinearMap (f a) (g a)) Source # 
Instance details

Defined in Math.Matrix.Linear

Associated Types

type Scalar (LinearMap (f a) (g a)) Source #

Methods

vzero :: LinearMap (f a) (g a) Source #

vnegate :: LinearMap (f a) (g a) -> LinearMap (f a) (g a) Source #

(%+) :: LinearMap (f a) (g a) -> LinearMap (f a) (g a) -> LinearMap (f a) (g a) Source #

(%*) :: Scalar (LinearMap (f a) (g a)) -> LinearMap (f a) (g a) -> LinearMap (f a) (g a) Source #

VectorSpace (SIMDVec 1 (Complex Double)) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 1 (Complex Double)) Source #

VectorSpace (SIMDVec 2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 2 (Complex Float)) Source #

VectorSpace (SIMDVec 2 Int64) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 2 Int64) Source #

VectorSpace (SIMDVec 2 Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 2 Double) Source #

VectorSpace (SIMDVec 4 Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 4 Int32) Source #

VectorSpace (SIMDVec 4 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 4 Float) Source #

VectorSpace (SIMDVec 8 Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 8 Int16) Source #

VectorSpace (SIMDVec 16 Int8) Source # 
Instance details

Defined in Math.Matrix.SIMD

Associated Types

type Scalar (SIMDVec 16 Int8) Source #

Num r => VectorSpace (GroupRing r g) Source # 
Instance details

Defined in Math.Number.Group

Associated Types

type Scalar (GroupRing r g) Source #

Methods

vzero :: GroupRing r g Source #

vnegate :: GroupRing r g -> GroupRing r g Source #

(%+) :: GroupRing r g -> GroupRing r g -> GroupRing r g Source #

(%*) :: Scalar (GroupRing r g) -> GroupRing r g -> GroupRing r g Source #

VectorSpace (VectorSpaceExpr v a) Source # 
Instance details

Defined in Math.Number.NumericExpression

Associated Types

type Scalar (VectorSpaceExpr v a) Source #

VectorSpace (Closure Stream R) Source # 
Instance details

Defined in Math.Number.Real

Associated Types

type Scalar (Closure Stream R) Source #

(LiteralUnit a, LiteralUnit b, Scalar a ~ Scalar b) => VectorSpace (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar (a :* b) Source #

Methods

vzero :: a :* b Source #

vnegate :: (a :* b) -> a :* b Source #

(%+) :: (a :* b) -> (a :* b) -> a :* b Source #

(%*) :: Scalar (a :* b) -> (a :* b) -> a :* b Source #

(LiteralUnit a, LiteralUnit b, Scalar a ~ Scalar b) => VectorSpace (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar (a :/ b) Source #

Methods

vzero :: a :/ b Source #

vnegate :: (a :/ b) -> a :/ b Source #

(%+) :: (a :/ b) -> (a :/ b) -> a :/ b Source #

(%*) :: Scalar (a :/ b) -> (a :/ b) -> a :/ b Source #

(VectorSpace a, VectorSpace b, Scalar a ~ Scalar b) => VectorSpace (a, b) Source #

a pair of vector spaces is a vector space if they are over the same set of scalars.

Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (a, b) Source #

Methods

vzero :: (a, b) Source #

vnegate :: (a, b) -> (a, b) Source #

(%+) :: (a, b) -> (a, b) -> (a, b) Source #

(%*) :: Scalar (a, b) -> (a, b) -> (a, b) Source #

Num v => VectorSpace (x -> v) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (x -> v) Source #

Methods

vzero :: x -> v Source #

vnegate :: (x -> v) -> x -> v Source #

(%+) :: (x -> v) -> (x -> v) -> x -> v Source #

(%*) :: Scalar (x -> v) -> (x -> v) -> x -> v Source #

(Linear v w, Linear w u) => VectorSpace (v, w, u) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (v, w, u) Source #

Methods

vzero :: (v, w, u) Source #

vnegate :: (v, w, u) -> (v, w, u) Source #

(%+) :: (v, w, u) -> (v, w, u) -> (v, w, u) Source #

(%*) :: Scalar (v, w, u) -> (v, w, u) -> (v, w, u) Source #

Num a => VectorSpace ((Vector1 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Scalar ((Vector1 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector1 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector3) a) Source #

1 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector1 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector1 :*: Vector4) a) Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector1 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector1 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector1 :*: (->) col) a) Source #

Methods

vzero :: (Vector1 :*: (->) col) a Source #

vnegate :: (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

(%+) :: (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

(%*) :: Scalar ((Vector1 :*: (->) col) a) -> (Vector1 :*: (->) col) a -> (Vector1 :*: (->) col) a Source #

Num a => VectorSpace ((Vector2 :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Scalar ((Vector2 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector3) a) Source #

2 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector2 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector2 :*: Vector4) a) Source #

2 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector2 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector2 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector2 :*: (->) col) a) Source #

Methods

vzero :: (Vector2 :*: (->) col) a Source #

vnegate :: (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

(%+) :: (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

(%*) :: Scalar ((Vector2 :*: (->) col) a) -> (Vector2 :*: (->) col) a -> (Vector2 :*: (->) col) a Source #

Num a => VectorSpace ((Vector3 :*: Vector1) a) Source #

3 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector2) a) Source #

3 x 2 matrices

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector3) a) Source #

3 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Scalar ((Vector3 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector3 :*: Vector4) a) Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector3 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector3 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector3 :*: (->) col) a) Source #

Methods

vzero :: (Vector3 :*: (->) col) a Source #

vnegate :: (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

(%+) :: (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

(%*) :: Scalar ((Vector3 :*: (->) col) a) -> (Vector3 :*: (->) col) a -> (Vector3 :*: (->) col) a Source #

Num a => VectorSpace ((Vector4 :*: Vector1) a) Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector1) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector2) a) Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector2) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector3) a) Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector3) a) Source #

Num a => VectorSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Scalar ((Vector4 :*: Vector4) a) Source #

Num a => VectorSpace ((Vector4 :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar ((Vector4 :*: (->) col) a) Source #

Methods

vzero :: (Vector4 :*: (->) col) a Source #

vnegate :: (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

(%+) :: (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

(%*) :: Scalar ((Vector4 :*: (->) col) a) -> (Vector4 :*: (->) col) a -> (Vector4 :*: (->) col) a Source #

Num a => VectorSpace (((->) row :*: Vector1) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector1) a) Source #

Methods

vzero :: ((->) row :*: Vector1) a Source #

vnegate :: ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

(%+) :: ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

(%*) :: Scalar (((->) row :*: Vector1) a) -> ((->) row :*: Vector1) a -> ((->) row :*: Vector1) a Source #

Num a => VectorSpace (((->) row :*: Vector2) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector2) a) Source #

Methods

vzero :: ((->) row :*: Vector2) a Source #

vnegate :: ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

(%+) :: ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

(%*) :: Scalar (((->) row :*: Vector2) a) -> ((->) row :*: Vector2) a -> ((->) row :*: Vector2) a Source #

Num a => VectorSpace (((->) row :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector3) a) Source #

Methods

vzero :: ((->) row :*: Vector3) a Source #

vnegate :: ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(%+) :: ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

(%*) :: Scalar (((->) row :*: Vector3) a) -> ((->) row :*: Vector3) a -> ((->) row :*: Vector3) a Source #

Num a => VectorSpace (((->) row :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: Vector4) a) Source #

Methods

vzero :: ((->) row :*: Vector4) a Source #

vnegate :: ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

(%+) :: ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

(%*) :: Scalar (((->) row :*: Vector4) a) -> ((->) row :*: Vector4) a -> ((->) row :*: Vector4) a Source #

Num a => VectorSpace (((->) row :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Associated Types

type Scalar (((->) row :*: (->) col) a) Source #

Methods

vzero :: ((->) row :*: (->) col) a Source #

vnegate :: ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a Source #

(%+) :: ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a Source #

(%*) :: Scalar (((->) row :*: (->) col) a) -> ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a Source #

class VectorSpace v => DecomposableVectorSpace v cofree | v -> cofree where Source #

cofree is right adjoint to Scalar

Minimal complete definition

decompose

Methods

decompose :: (Scalar v -> res) -> v -> cofree res Source #

project :: v -> cofree (Scalar v) Source #

Instances

Instances details
Num a => DecomposableVectorSpace (Vector1 a) ((->) OneD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector1 a) -> res) -> Vector1 a -> OneD -> res Source #

project :: Vector1 a -> OneD -> Scalar (Vector1 a) Source #

Num a => DecomposableVectorSpace (Vector2 a) ((->) TwoD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector2 a) -> res) -> Vector2 a -> TwoD -> res Source #

project :: Vector2 a -> TwoD -> Scalar (Vector2 a) Source #

Num a => DecomposableVectorSpace (Vector3 a) ((->) ThreeD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector3 a) -> res) -> Vector3 a -> ThreeD -> res Source #

project :: Vector3 a -> ThreeD -> Scalar (Vector3 a) Source #

Num a => DecomposableVectorSpace (Vector4 a) ((->) FourD) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Vector4 a) -> res) -> Vector4 a -> FourD -> res Source #

project :: Vector4 a -> FourD -> Scalar (Vector4 a) Source #

Num a => DecomposableVectorSpace (Stream a) ((->) Integer) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

decompose :: (Scalar (Stream a) -> res) -> Stream a -> Integer -> res Source #

project :: Stream a -> Integer -> Scalar (Stream a) Source #

type SupportsMatrixMultiplication f g h a = (VectorSpace (f a), VectorSpace (h a), InnerProductSpace (g a), Scalar (f a) ~ a, Scalar (h a) ~ a, Scalar (g a) ~ a, Num a, ConjugateSymmetric a, Functor f, Transposable g h a) Source #

type LinearIso f g a = (LinearTransform f g a, LinearTransform g f a) Source #

class VectorSpace v => BilinearVectorSpace v where Source #

Methods

biLin :: v -> v -> Scalar v Source #

class VectorSpace m => InnerProductSpace m where Source #

Methods

(%.) :: m -> m -> Scalar m infix 7 Source #

Instances

Instances details
InnerProductSpace Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

InnerProductSpace R Source # 
Instance details

Defined in Math.Number.Real

Methods

(%.) :: R -> R -> Scalar R Source #

InnerProductSpace Integer Source # 
Instance details

Defined in Math.Matrix.Interface

InnerProductSpace Double Source # 
Instance details

Defined in Math.Matrix.Interface

InnerProductSpace Float Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: Float -> Float -> Scalar Float Source #

InnerProductSpace Int Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: Int -> Int -> Scalar Int Source #

RealFloat a => InnerProductSpace (Complex a) Source #

https://en.wikipedia.org/wiki/Inner_product_space

Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: Complex a -> Complex a -> Scalar (Complex a) Source #

Num a => InnerProductSpace (First a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: First a -> First a -> Scalar (First a) Source #

Floating a => InnerProductSpace (Product a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: Product a -> Product a -> Scalar (Product a) Source #

(ConjugateSymmetric a, Num a) => InnerProductSpace (Sum a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: Sum a -> Sum a -> Scalar (Sum a) Source #

Integral a => InnerProductSpace (Ratio a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: Ratio a -> Ratio a -> Scalar (Ratio a) Source #

(Num a, ConjugateSymmetric a) => InnerProductSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

(%.) :: Vector1 a -> Vector1 a -> Scalar (Vector1 a) Source #

Scalar (SIMDVec 2 Double) ~ Double => InnerProductSpace (Vector2 Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => InnerProductSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

(%.) :: Vector2 a -> Vector2 a -> Scalar (Vector2 a) Source #

InnerProductSpace (Vector3 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

(ConjugateSymmetric a, Num a) => InnerProductSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

(%.) :: Vector3 a -> Vector3 a -> Scalar (Vector3 a) Source #

InnerProductSpace (Vector4 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => InnerProductSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

(%.) :: Vector4 a -> Vector4 a -> Scalar (Vector4 a) Source #

(StandardBasis (f v), Num v, VectorSpace (f v), DualNum f v) => InnerProductSpace (Dual (f v)) Source # 
Instance details

Defined in Math.Matrix.Covector

Methods

(%.) :: Dual (f v) -> Dual (f v) -> Scalar (Dual (f v)) Source #

Fractional a => InnerProductSpace (Quaternion a) Source # 
Instance details

Defined in Math.Matrix.Quaternion

Methods

(%.) :: Quaternion a -> Quaternion a -> Scalar (Quaternion a) Source #

(Show r, InnerProductSpace r, Scalar (Quantity r) ~ Scalar r) => InnerProductSpace (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

(%.) :: Quantity r -> Quantity r -> Scalar (Quantity r) Source #

(ConjugateSymmetric a, Num a, Closed a) => InnerProductSpace (Stream a) Source # 
Instance details

Defined in Math.Number.Stream

Methods

(%.) :: Stream a -> Stream a -> Scalar (Stream a) Source #

Num a => InnerProductSpace (Interval a) Source # 
Instance details

Defined in Math.Tools.Median

Methods

(%.) :: Interval a -> Interval a -> Scalar (Interval a) Source #

InnerProductSpace (SIMDVec 1 (Complex Double)) Source # 
Instance details

Defined in Math.Matrix.SIMD

InnerProductSpace (SIMDVec 2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

InnerProductSpace (SIMDVec 2 Int64) Source # 
Instance details

Defined in Math.Matrix.SIMD

Scalar (SIMDVec 2 Double) ~ Double => InnerProductSpace (SIMDVec 2 Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

InnerProductSpace (SIMDVec 4 Int32) Source # 
Instance details

Defined in Math.Matrix.SIMD

InnerProductSpace (SIMDVec 4 Float) Source # 
Instance details

Defined in Math.Matrix.SIMD

InnerProductSpace (SIMDVec 8 Int16) Source # 
Instance details

Defined in Math.Matrix.SIMD

InnerProductSpace (SIMDVec 16 Int8) Source # 
Instance details

Defined in Math.Matrix.SIMD

Methods

(%.) :: SIMDVec 16 Int8 -> SIMDVec 16 Int8 -> Scalar (SIMDVec 16 Int8) Source #

InnerProductSpace (VectorSpaceExpr v a) Source # 
Instance details

Defined in Math.Number.NumericExpression

(LinearInnerProductSpace v w, Num (Scalar w)) => InnerProductSpace (v, w) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: (v, w) -> (v, w) -> Scalar (v, w) Source #

(Universe a, Num b) => InnerProductSpace (a -> b) Source #

https://en.wikipedia.org/wiki/Dot_product

Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: (a -> b) -> (a -> b) -> Scalar (a -> b) Source #

(LinearInnerProductSpace v w, LinearInnerProductSpace w u, Num (Scalar w)) => InnerProductSpace (v, w, u) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%.) :: (v, w, u) -> (v, w, u) -> Scalar (v, w, u) Source #

(Floating a, ConjugateSymmetric a) => InnerProductSpace ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Floating a, ConjugateSymmetric a) => InnerProductSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

(Integral col, Integral row, Universe row, Universe col, Num a, ConjugateSymmetric a) => InnerProductSpace (((->) row :*: (->) col) a) Source #

https://en.wikipedia.org/wiki/Frobenius_inner_product

Instance details

Defined in Math.Matrix.Simple

Methods

(%.) :: ((->) row :*: (->) col) a -> ((->) row :*: (->) col) a -> Scalar (((->) row :*: (->) col) a) Source #

outer :: (InnerProductSpace m, Scalar m ~ Scalar v, VectorSpace v) => m -> v -> m -> v Source #

class VectorSpace m => LieAlgebra m where Source #

Methods

(%<>%) :: m -> m -> m Source #

Instances

Instances details
Num a => LieAlgebra (Endo a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%<>%) :: Endo a -> Endo a -> Endo a Source #

Floating a => LieAlgebra (Product a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%<>%) :: Product a -> Product a -> Product a Source #

Num a => LieAlgebra (Vector3 a) Source #

https://en.wikipedia.org/wiki/Lie_algebra

Instance details

Defined in Math.Matrix.Vector3

Methods

(%<>%) :: Vector3 a -> Vector3 a -> Vector3 a Source #

(v ~ Scalar (f v), VectorSpace (f v), DualNum f v) => LieAlgebra (Dual (f v)) Source # 
Instance details

Defined in Math.Matrix.Covector

Methods

(%<>%) :: Dual (f v) -> Dual (f v) -> Dual (f v) Source #

Num a => LieAlgebra (Quaternion a) Source # 
Instance details

Defined in Math.Matrix.Quaternion

Methods

(%<>%) :: Quaternion a -> Quaternion a -> Quaternion a Source #

(LieAlgebra a, LieAlgebra b, Scalar a ~ Scalar b) => LieAlgebra (a, b) Source #

https://en.wikipedia.org/wiki/Lie_algebra

Instance details

Defined in Math.Matrix.Interface

Methods

(%<>%) :: (a, b) -> (a, b) -> (a, b) Source #

(VectorSpace a, Num a) => LieAlgebra (a -> a) Source #

https://en.wikipedia.org/wiki/Commutator

Instance details

Defined in Math.Matrix.Interface

Methods

(%<>%) :: (a -> a) -> (a -> a) -> a -> a Source #

(Integral row, Universe row, SupportsMatrixMultiplication ((->) row) ((->) row) ((->) row) a) => LieAlgebra ((row :&: row) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(%<>%) :: (row :&: row) a -> (row :&: row) a -> (row :&: row) a Source #

(LieAlgebra v, LieAlgebra w, LieAlgebra u, Scalar v ~ Scalar w, Scalar w ~ Scalar u) => LieAlgebra (v, w, u) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

(%<>%) :: (v, w, u) -> (v, w, u) -> (v, w, u) Source #

(Num a, ConjugateSymmetric a) => LieAlgebra ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

(Num a, ConjugateSymmetric a) => LieAlgebra ((Vector4 :*: Vector4) a) Source # 
Instance details

Defined in Math.Matrix.Matrix

class VectorSpace s => MetricSpace s where Source #

Methods

distance :: s -> s -> Scalar s Source #

Instances

Instances details
MetricSpace R Source # 
Instance details

Defined in Math.Number.Real

Methods

distance :: R -> R -> Scalar R Source #

MetricSpace Integer Source # 
Instance details

Defined in Math.Number.Real

MetricSpace Int Source # 
Instance details

Defined in Math.Number.Real

Methods

distance :: Int -> Int -> Scalar Int Source #

RealFloat a => MetricSpace (Complex a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

distance :: Complex a -> Complex a -> Scalar (Complex a) Source #

MetricSpace (Ratio Integer) Source # 
Instance details

Defined in Math.Number.Real

MetricSpace (Stream R) Source # 
Instance details

Defined in Math.Number.Real

MetricSpace (Closure Stream R) Source # 
Instance details

Defined in Math.Number.Real

class VectorSpace m => NormedSpace m where Source #

norm_squared is an optimization that often avoids computing square root

Minimal complete definition

norm | norm_squared

Methods

norm :: m -> Scalar m Source #

default norm :: Floating (Scalar m) => m -> Scalar m Source #

norm_squared :: m -> Scalar m Source #

Instances

Instances details
NormedSpace R Source # 
Instance details

Defined in Math.Number.Real

NormedSpace AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Acceleration Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Angle Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Capacitance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Charge Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Conductance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Current Source # 
Instance details

Defined in Math.Number.Units

NormedSpace DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

NormedSpace DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

NormedSpace DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Dimensionless Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Energy Source # 
Instance details

Defined in Math.Number.Units

NormedSpace EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Flux Source # 
Instance details

Defined in Math.Number.Units

NormedSpace FluxDensity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Force Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Frequency Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Illuminance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Inductance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Information Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Intensity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Length Source # 
Instance details

Defined in Math.Number.Units

NormedSpace LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Mass Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Percentage Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Power Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Pressure Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Radioactivity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Resistance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace SolidAngle Source # 
Instance details

Defined in Math.Number.Units

NormedSpace SquareLength Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Substance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Temperature Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Time Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Torque Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Velocity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Voltage Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Integer Source # 
Instance details

Defined in Math.Matrix.Interface

NormedSpace Double Source # 
Instance details

Defined in Math.Matrix.Interface

NormedSpace Float Source # 
Instance details

Defined in Math.Matrix.Interface

NormedSpace Int Source # 
Instance details

Defined in Math.Matrix.Interface

NormedSpace (Complex Double) Source # 
Instance details

Defined in Math.Matrix.SIMD

RealFloat a => NormedSpace (Complex a) Source # 
Instance details

Defined in Math.Matrix.Interface

Floating a => NormedSpace (First a) Source # 
Instance details

Defined in Math.Matrix.Interface

(Floating a, ConjugateSymmetric a) => NormedSpace (Sum a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

norm :: Sum a -> Scalar (Sum a) Source #

norm_squared :: Sum a -> Scalar (Sum a) Source #

Integral a => NormedSpace (Ratio a) Source # 
Instance details

Defined in Math.Matrix.Interface

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

NormedSpace (Vector2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Floating a, ConjugateSymmetric a) => NormedSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

(ConjugateSymmetric a, Floating a) => NormedSpace (Quaternion a) Source # 
Instance details

Defined in Math.Matrix.Quaternion

Methods

norm :: Quaternion a -> Scalar (Quaternion a) Source #

norm_squared :: Quaternion a -> Scalar (Quaternion a) Source #

(Num r, NormedSpace r) => NormedSpace (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Closed a, ConjugateSymmetric a, Floating a) => NormedSpace (Stream a) Source # 
Instance details

Defined in Math.Number.Stream

Num a => NormedSpace (Interval a) Source # 
Instance details

Defined in Math.Tools.Median

(Num (Scalar a), NormedSpace a) => NormedSpace (Maybe a) Source # 
Instance details

Defined in Math.Matrix.Interface

NormedSpace (SIMDVec 1 (Complex Double)) Source # 
Instance details

Defined in Math.Matrix.SIMD

NormedSpace (SIMDVec 2 (Complex Float)) Source # 
Instance details

Defined in Math.Matrix.SIMD

(Floating b, Universe a) => NormedSpace (a -> b) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

norm :: (a -> b) -> Scalar (a -> b) Source #

norm_squared :: (a -> b) -> Scalar (a -> b) Source #

(VectorSpace a, Integral col, Integral row, Universe row, ConjugateSymmetric a, Universe col, Floating a, Integral row, Scalar (col -> a) ~ a) => NormedSpace ((row :&: col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

norm :: (row :&: col) a -> Scalar ((row :&: col) a) Source #

norm_squared :: (row :&: col) a -> Scalar ((row :&: col) a) Source #

(Floating a, ConjugateSymmetric a) => NormedSpace ((Vector3 :*: Vector3) a) Source # 
Instance details

Defined in Math.Matrix.Vector3

(Floating a, ConjugateSymmetric a) => NormedSpace ((Vector4 :*: Vector4) a) Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

(Integral row, Integral col, Floating a, Universe row, Universe col, ConjugateSymmetric a) => NormedSpace (((->) row :*: (->) col) a) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

norm :: ((->) row :*: (->) col) a -> Scalar (((->) row :*: (->) col) a) Source #

norm_squared :: ((->) row :*: (->) col) a -> Scalar (((->) row :*: (->) col) a) Source #

matrix_norm :: (Functor f, NormedSpace (g a), NormedSpace (f (Scalar (g a)))) => (f :*: g) a -> Scalar (f (Scalar (g a))) Source #

This computes norm of each row, then computes the norm of the resulting column vector.

class CompleteSpace m Source #

Instances

Instances details
CompleteSpace R Source # 
Instance details

Defined in Math.Number.R

class ConjugateSymmetric m where Source #

Methods

conj :: m -> m Source #

Instances

Instances details
ConjugateSymmetric R Source # 
Instance details

Defined in Math.Number.R

Methods

conj :: R -> R Source #

ConjugateSymmetric R Source # 
Instance details

Defined in Math.Number.Real

Methods

conj :: R -> R Source #

ConjugateSymmetric Integer Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: Integer -> Integer Source #

ConjugateSymmetric Double Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: Double -> Double Source #

ConjugateSymmetric Float Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: Float -> Float Source #

ConjugateSymmetric Int Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: Int -> Int Source #

RealFloat a => ConjugateSymmetric (Complex a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: Complex a -> Complex a Source #

Integral a => ConjugateSymmetric (Ratio a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: Ratio a -> Ratio a Source #

ConjugateSymmetric a => ConjugateSymmetric (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

conj :: Vector1 a -> Vector1 a Source #

ConjugateSymmetric a => ConjugateSymmetric (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

conj :: Vector2 a -> Vector2 a Source #

ConjugateSymmetric a => ConjugateSymmetric (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

conj :: Vector3 a -> Vector3 a Source #

ConjugateSymmetric a => ConjugateSymmetric (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

conj :: Vector4 a -> Vector4 a Source #

Num a => ConjugateSymmetric (Quaternion a) Source # 
Instance details

Defined in Math.Matrix.Quaternion

Methods

conj :: Quaternion a -> Quaternion a Source #

(Show r, ConjugateSymmetric r) => ConjugateSymmetric (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

conj :: Quantity r -> Quantity r Source #

ConjugateSymmetric a => ConjugateSymmetric (Stream a) Source # 
Instance details

Defined in Math.Number.Stream

Methods

conj :: Stream a -> Stream a Source #

(Closed a, Num a, ConjugateSymmetric a) => ConjugateSymmetric (Stream a :-> Stream a) Source # 
Instance details

Defined in Math.Number.Stream

Methods

conj :: (Stream a :-> Stream a) -> Stream a :-> Stream a Source #

(Eq a, Show a) => ConjugateSymmetric (NumExpr v a) Source # 
Instance details

Defined in Math.Number.NumericExpression

Methods

conj :: NumExpr v a -> NumExpr v a Source #

ConjugateSymmetric (Closure Stream R) Source # 
Instance details

Defined in Math.Number.R

(ConjugateSymmetric a, ConjugateSymmetric b) => ConjugateSymmetric (a, b) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: (a, b) -> (a, b) Source #

ConjugateSymmetric a => ConjugateSymmetric (a -> a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: (a -> a) -> a -> a Source #

(ConjugateSymmetric a, ConjugateSymmetric b, ConjugateSymmetric c) => ConjugateSymmetric (a, b, c) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: (a, b, c) -> (a, b, c) Source #

(ConjugateSymmetric a, ConjugateSymmetric b, ConjugateSymmetric c, ConjugateSymmetric d) => ConjugateSymmetric (a, b, c, d) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

conj :: (a, b, c, d) -> (a, b, c, d) Source #

(Num a, ConjugateSymmetric a) => ConjugateSymmetric ((Vector2 :*: Vector2) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector2

(ConjugateSymmetric a, Num a) => ConjugateSymmetric ((Vector3 :*: Vector3) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector3

ConjugateSymmetric a => ConjugateSymmetric ((Vector4 :*: Vector4) a) Source #

https://en.wikipedia.org/wiki/Conjugate_transpose

Instance details

Defined in Math.Matrix.Vector4

ConjugateSymmetric a => ConjugateSymmetric ((Stream :*: Stream) a) Source # 
Instance details

Defined in Math.Number.Stream

Methods

conj :: (Stream :*: Stream) a -> (Stream :*: Stream) a Source #

class (Scalar (m a) ~ Scalar (n a), Functor m, Functor n) => LinearTransform m n a where Source #

Methods

(<*>>) Source #

Arguments

:: n a 
-> (m :*: n) a 
-> m a

vector times matrix

(<<*>) Source #

Arguments

:: (m :*: n) a 
-> m a 
-> n a

matrix times vector

Instances

Instances details
Num a => LinearTransform Vector1 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

(ConjugateSymmetric a, Num a) => LinearTransform Vector1 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => LinearTransform Vector1 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector1 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(ConjugateSymmetric a, Num a) => LinearTransform Vector2 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Scalar (SIMDVec 2 Double) ~ Double => LinearTransform Vector2 Vector2 Double Source # 
Instance details

Defined in Math.Matrix.SIMD

(ConjugateSymmetric a, Num a) => LinearTransform Vector2 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Num a, ConjugateSymmetric a) => LinearTransform Vector2 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector2 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector3

LinearTransform Vector3 Vector3 Float Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

(Num a, ConjugateSymmetric a) => LinearTransform Vector3 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector4

LinearTransform Vector4 Vector4 Float Source # 
Instance details

Defined in Math.Matrix.SIMD

(Num a, ConjugateSymmetric a) => LinearTransform Vector4 Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Closed a, ConjugateSymmetric a, Num a) => LinearTransform Stream Stream a Source # 
Instance details

Defined in Math.Number.Stream

Methods

(<*>>) :: Stream a -> (Stream :*: Stream) a -> Stream a Source #

(<<*>) :: (Stream :*: Stream) a -> Stream a -> Stream a Source #

(Num a, Universe col) => LinearTransform Vector1 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector1 :*: (->) col) a -> Vector1 a Source #

(<<*>) :: (Vector1 :*: (->) col) a -> Vector1 a -> col -> a Source #

(Num a, Universe col) => LinearTransform Vector2 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector2 :*: (->) col) a -> Vector2 a Source #

(<<*>) :: (Vector2 :*: (->) col) a -> Vector2 a -> col -> a Source #

(Num a, Universe col) => LinearTransform Vector3 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector3 :*: (->) col) a -> Vector3 a Source #

(<<*>) :: (Vector3 :*: (->) col) a -> Vector3 a -> col -> a Source #

(Universe col, Num a) => LinearTransform Vector4 ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> (Vector4 :*: (->) col) a -> Vector4 a Source #

(<<*>) :: (Vector4 :*: (->) col) a -> Vector4 a -> col -> a Source #

(Universe row, Num a) => LinearTransform ((->) row) Vector1 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector1 a -> ((->) row :*: Vector1) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector1) a -> (row -> a) -> Vector1 a Source #

(Universe row, Num a) => LinearTransform ((->) row) Vector2 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector2 a -> ((->) row :*: Vector2) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector2) a -> (row -> a) -> Vector2 a Source #

(Universe row, Num a) => LinearTransform ((->) row) Vector3 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector3 a -> ((->) row :*: Vector3) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector3) a -> (row -> a) -> Vector3 a Source #

(Universe row, Num a) => LinearTransform ((->) row) Vector4 a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: Vector4 a -> ((->) row :*: Vector4) a -> row -> a Source #

(<<*>) :: ((->) row :*: Vector4) a -> (row -> a) -> Vector4 a Source #

(Num a, Universe row, Universe col) => LinearTransform ((->) row) ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

(<*>>) :: (col -> a) -> ((->) row :*: (->) col) a -> row -> a Source #

(<<*>) :: ((->) row :*: (->) col) a -> (row -> a) -> col -> a Source #

data Lin b c where Source #

Constructors

Lin :: (f :*: g) a -> Lin (f a) (g a) 

class (Functor m, Functor n, Scalar (m a) ~ Scalar (n a)) => Transposable m n a where Source #

Methods

transpose_impl :: (m :*: n) a -> (n :*: m) a Source #

Instances

Instances details
Transposable Complex Complex a Source #

notice matrix of two complex numbers has special properties as matrix.

Instance details

Defined in Math.Matrix.Interface

(LinearTransform f Complex a, Diagonalizable Complex a, Applicative f, Num a) => Transposable Complex f a Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: (Complex :*: f) a -> (f :*: Complex) a Source #

Transposable Vector1 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Transposable Vector1 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector1 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector1 Vector4 a Source #

1 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector2 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector2 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Vector2 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector2 Vector4 a Source #

2 x 4 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector3 Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Vector3 Vector4 a Source #

3 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector1 a Source #

4 x 1 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector2 a Source #

4 x 2 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector3 a Source #

4 x 3 matrices:

Instance details

Defined in Math.Matrix.Vector4

Transposable Vector4 Vector4 a Source #

4 x 4 matrices

Instance details

Defined in Math.Matrix.Vector4

Transposable Stream Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Transposable Stream Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Transposable Stream Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Transposable Stream Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => Transposable Stream Stream a Source # 
Instance details

Defined in Math.Number.StreamInterface

Transposable IO IO a Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: (IO :*: IO) a -> (IO :*: IO) a Source #

(Indexable f a, Diagonalizable f a, Functor f, Scalar (f a) ~ Complex a, Num a) => Transposable f Complex a Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: (f :*: Complex) a -> (Complex :*: f) a Source #

Transposable Vector1 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

transpose_impl :: (Vector1 :*: (->) row) a -> ((->) row :*: Vector1) a Source #

Transposable Vector2 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

transpose_impl :: (Vector2 :*: (->) row) a -> ((->) row :*: Vector2) a Source #

Transposable Vector3 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

transpose_impl :: (Vector3 :*: (->) row) a -> ((->) row :*: Vector3) a Source #

Transposable Vector4 ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

transpose_impl :: (Vector4 :*: (->) row) a -> ((->) row :*: Vector4) a Source #

(Ix i, Ix j) => Transposable (Array i) (Array j) a Source # 
Instance details

Defined in Math.Matrix.Bitmap

Methods

transpose_impl :: (Array i :*: Array j) a -> (Array j :*: Array i) a Source #

Scalar a ~ Scalar b => Transposable ((,) a) ((,) b) c Source #

Oddly, scalars must match.

Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: ((,) a :*: (,) b) c -> ((,) b :*: (,) a) c Source #

Transposable ((->) row) Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Methods

transpose_impl :: ((->) row :*: Vector1) a -> (Vector1 :*: (->) row) a Source #

Transposable ((->) row) Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

transpose_impl :: ((->) row :*: Vector2) a -> (Vector2 :*: (->) row) a Source #

Transposable ((->) row) Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

transpose_impl :: ((->) row :*: Vector3) a -> (Vector3 :*: (->) row) a Source #

Transposable ((->) row) Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

transpose_impl :: ((->) row :*: Vector4) a -> (Vector4 :*: (->) row) a Source #

Transposable ((->) row) ((->) col) a Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: ((->) row :*: (->) col) a -> ((->) col :*: (->) row) a Source #

(Transposable f h (g (k a)), Transposable g h (k a), Transposable g k a, Transposable f k (g a), Scalar ((f :*: g) a) ~ Scalar ((h :*: k) a)) => Transposable (f :*: g) (h :*: k) a Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

transpose_impl :: ((f :*: g) :*: (h :*: k)) a -> ((h :*: k) :*: (f :*: g)) a Source #

transpose :: (Transposable g f a, Linearizable arr (:*:) f g a, Linearizable arr (:*:) g f a) => arr (g a) (f a) -> arr (f a) (g a) Source #

indexable_transpose :: (Functor n, Indexable m a) => (n :*: m) a -> (m :*: n) a Source #

update_column :: Applicative h => (a -> f b -> g c) -> h a -> (h :*: f) b -> (h :*: g) c Source #

update_row :: (a -> f (g b) -> f' (g' b')) -> a -> (f :*: g) b -> (f' :*: g') b' Source #

class UpdateableMatrixDimension f where Source #

Example use:

write_column (Vector3 3 4 5) `ycoord3` identity3 == [[1,3,0],[0,4,0],[0,5,1]]

Methods

write_row :: Applicative h => h a -> f ((f :*: h) a -> (f :*: h) a) Source #

write_column :: Applicative h => h a -> f ((h :*: f) a -> (h :*: f) a) Source #

Instances

Instances details
UpdateableMatrixDimension Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

write_row :: Applicative h => h a -> Vector2 ((Vector2 :*: h) a -> (Vector2 :*: h) a) Source #

write_column :: Applicative h => h a -> Vector2 ((h :*: Vector2) a -> (h :*: Vector2) a) Source #

UpdateableMatrixDimension Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

write_row :: Applicative h => h a -> Vector3 ((Vector3 :*: h) a -> (Vector3 :*: h) a) Source #

write_column :: Applicative h => h a -> Vector3 ((h :*: Vector3) a -> (h :*: Vector3) a) Source #

UpdateableMatrixDimension Vector4 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

write_row :: Applicative h => h a -> Vector4 ((Vector4 :*: h) a -> (Vector4 :*: h) a) Source #

write_column :: Applicative h => h a -> Vector4 ((h :*: Vector4) a -> (h :*: Vector4) a) Source #

Eq ind => UpdateableMatrixDimension ((->) ind) Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

write_row :: Applicative h => h a -> ind -> (((->) ind :*: h) a -> ((->) ind :*: h) a) Source #

write_column :: Applicative h => h a -> ind -> ((h :*: (->) ind) a -> (h :*: (->) ind) a) Source #

solve_matrix :: (Traceable m b, Fractional b, UpdateableMatrixDimension m) => (m :*: m) b -> m b -> m b Source #

Cramer's rule https://en.wikipedia.org/wiki/Cramer%27s_rule.

Solves \({\mathbf x}\) from matrix equation \(A{\mathbf x} = {\mathbf b}\), where \(A\) is first parameter and \({\mathbf b}\) is second parameter. Returns vector \({\mathbf x}\). Satisfies requirements:

a <<*> solve_matrix a b == b

\[{\mathbf x}_i = {{\det(A[A_{ki} := {\mathbf b}_k])} \over {\det(A)}}\]

(<!-!>) :: (m a -> a) -> (a -> m a) -> Index m a Source #

runIndex :: Index m a -> m a -> a Source #

appIndex :: Applicative f => f (Index m a) -> f (m a) -> f a Source #

type Index m a = m a :==: I a Source #

class (Applicative m, Num a) => Indexable m a where Source #

Minimal complete definition

diagonal_projections, indexable_indices

Instances

Instances details
Num a => Indexable Complex a Source # 
Instance details

Defined in Math.Matrix.Interface

Num a => Indexable Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Num a => Indexable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => Indexable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => Indexable Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => Indexable Stream a Source # 
Instance details

Defined in Math.Number.Stream

Num a => Indexable I a Source # 
Instance details

Defined in Math.Matrix.Indexable

(Num a, Monoid a) => Indexable List a Source # 
Instance details

Defined in Math.Matrix.Interface

(Num a, Integral row) => Indexable ((->) row) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

diagonal_projections :: row -> Index ((->) row) a Source #

basis_vector :: Index ((->) row) a -> row -> a Source #

index_project :: Index ((->) row) a -> (row -> a) -> a Source #

indexable_indices :: row -> a Source #

Num a => Indexable (Vector2 :*: Vector2) a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Integral a, Indexable f a, Indexable g a) => Indexable (f :*: g) a Source # 
Instance details

Defined in Math.Matrix.Indexable

Methods

diagonal_projections :: (f :*: g) (Index (f :*: g) a) Source #

basis_vector :: Index (f :*: g) a -> (f :*: g) a Source #

index_project :: Index (f :*: g) a -> (f :*: g) a -> a Source #

indexable_indices :: (f :*: g) a Source #

class (Num a, Indexable m a, Transposable m m a) => Diagonalizable m a where Source #

Minimal complete definition

identity, diagonal_impl, diagonal_matrix_impl

Methods

identity_impl :: m Integer -> (m :*: m) a Source #

argument to identity_impl is dimension of the matrix

identity :: (m :*: m) a Source #

diagonal_impl :: (m :*: m) a -> m a Source #

diagonal_matrix_impl :: m a -> (m :*: m) a Source #

Instances

Instances details
Num a => Diagonalizable Complex a Source #

diagonalizable instance for complex numbers. diagonal ((a+bi)+i(c+di)) = (a-d) + i(b+c)

Instance details

Defined in Math.Matrix.Interface

Num a => Diagonalizable Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Num a => Diagonalizable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => Diagonalizable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => Diagonalizable Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Num a => Diagonalizable Stream a Source #

square matrix implementation for streams.

Instance details

Defined in Math.Number.Stream

(Num a, Eq dim, Integral dim) => Diagonalizable ((->) dim) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

identity_impl :: (dim -> Integer) -> ((->) dim :*: (->) dim) a Source #

identity :: ((->) dim :*: (->) dim) a Source #

diagonal_impl :: ((->) dim :*: (->) dim) a -> dim -> a Source #

diagonal_matrix_impl :: (dim -> a) -> ((->) dim :*: (->) dim) a Source #

basis :: Diagonalizable m a => m (m a) Source #

coefficients :: (Foldable m, Applicative m, VectorSpace v) => m (Scalar v) -> m v -> v Source #

bilinear_map :: (VectorSpace a, Foldable m, Foldable n, Diagonalizable m b, Diagonalizable n c) => (m b -> n c -> a) -> m (Scalar a) -> n (Scalar a) -> a Source #

linear_map' :: (b ~ Scalar (n b), Foldable m, Diagonalizable m a, VectorSpace (n b)) => (m a -> n b) -> m b -> n b Source #

linear_identity :: (Linearizable arr (:*:) m m a, LinearTransform m m a, Diagonalizable m a) => arr (m a) (m a) Source #

diagonal :: (Linearizable arr (:*:) m m a, Diagonalizable m a) => arr (m a) (m a) -> m a Source #

class (Functor m, Functor n) => ProjectionSpace (m :: * -> *) (n :: * -> *) where Source #

Associated Types

data (m \\\ n) a Source #

Methods

project_first :: m a -> n a Source #

project_second :: m a -> (m \\\ n) a Source #

join_vector :: n a -> (m \\\ n) a -> m a Source #

Instances

Instances details
ProjectionSpace Vector1 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

data (Vector1 \\\ Vector1) a Source #

ProjectionSpace Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data (Vector2 \\\ Vector1) a Source #

ProjectionSpace Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data (Vector3 \\\ Vector1) a Source #

ProjectionSpace Vector3 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data (Vector3 \\\ Vector2) a Source #

ProjectionSpace (Vector3 \\\ Vector1) Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data ((Vector3 \\\ Vector1) \\\ Vector1) a Source #

class CodiagonalMatrix m a where Source #

CodiagonalMatrix represents a matrix that can be split along the diagonal. The Codiagonal type represents a matrix without its diagonal. The ProjectionVector type represents a vector down from first element of diagonal when the diagonal is removed. This vector often has less elements than the original vector. Similarly for vector right from the first element of diagonal.

Associated Types

data Codiagonal m a Source #

type m \\ a Source #

Methods

codiagonal_impl :: (m :*: m) a -> Codiagonal m a Source #

(|\|) :: m a -> Codiagonal m a -> (m :*: m) a Source #

down_project :: Codiagonal m a -> m \\ a Source #

right_project :: Codiagonal m a -> m \\ a Source #

Instances

Instances details
CodiagonalMatrix Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

data Codiagonal Vector2 a Source #

type Vector2 \\ a Source #

CodiagonalMatrix Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

data Codiagonal Vector3 a Source #

type Vector3 \\ a Source #

CodiagonalMatrix Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

data Codiagonal Vector4 a Source #

type Vector4 \\ a Source #

Num a => CodiagonalMatrix Stream a Source # 
Instance details

Defined in Math.Number.StreamInterface

Associated Types

data Codiagonal Stream a Source #

type Stream \\ a Source #

class Category arr => Linearizable arr prod f g a | arr -> prod where Source #

NOTICE: Linearizable instances for matrices that have similar dimensions are special.

Methods

fromLinear :: arr (f a) (g a) -> prod f g a Source #

linear :: prod f g a -> arr (f a) (g a) Source #

Instances

Instances details
(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector1 (a :: Type) Source #

NOTICE: Linearizable instances for matrices that have similar dimensions are special.

Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Scalar a ~ a, Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a, Diagonalizable Stream a, InnerProductSpace (Stream a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Stream Stream (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector1 (f a)) (Dual (f a)) -> (Vector1 :*: Dual) (f a) Source #

linear :: (Vector1 :*: Dual) (f a) -> LinearMap (Vector1 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector2 (f a)) (Dual (f a)) -> (Vector2 :*: Dual) (f a) Source #

linear :: (Vector2 :*: Dual) (f a) -> LinearMap (Vector2 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector3 (f a)) (Dual (f a)) -> (Vector3 :*: Dual) (f a) Source #

linear :: (Vector3 :*: Dual) (f a) -> LinearMap (Vector3 (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector4 (f a)) (Dual (f a)) -> (Vector4 :*: Dual) (f a) Source #

linear :: (Vector4 :*: Dual) (f a) -> LinearMap (Vector4 (f a)) (Dual (f a)) Source #

(Scalar (f a) ~ f a, Num a, ConjugateSymmetric a, Diagonalizable Dual (f a)) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Dual Dual (f a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Dual (f a)) (Dual (f a)) -> (Dual :*: Dual) (f a) Source #

linear :: (Dual :*: Dual) (f a) -> LinearMap (Dual (f a)) (Dual (f a)) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector1 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector1 a) (col -> a) -> (Vector1 :*: (->) col) a Source #

linear :: (Vector1 :*: (->) col) a -> LinearMap (Vector1 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector2 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector2 a) (col -> a) -> (Vector2 :*: (->) col) a Source #

linear :: (Vector2 :*: (->) col) a -> LinearMap (Vector2 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector3 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector3 a) (col -> a) -> (Vector3 :*: (->) col) a Source #

linear :: (Vector3 :*: (->) col) a -> LinearMap (Vector3 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Vector4 ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (Vector4 a) (col -> a) -> (Vector4 :*: (->) col) a Source #

linear :: (Vector4 :*: (->) col) a -> LinearMap (Vector4 a) (col -> a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector1 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector1 a) -> ((->) row :*: Vector1) a Source #

linear :: ((->) row :*: Vector1) a -> LinearMap (row -> a) (Vector1 a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector2 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector2 a) -> ((->) row :*: Vector2) a Source #

linear :: ((->) row :*: Vector2) a -> LinearMap (row -> a) (Vector2 a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector3 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector3 a) -> ((->) row :*: Vector3) a Source #

linear :: ((->) row :*: Vector3) a -> LinearMap (row -> a) (Vector3 a) Source #

(Num a, ConjugateSymmetric a, Universe row) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) Vector4 (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (Vector4 a) -> ((->) row :*: Vector4) a Source #

linear :: ((->) row :*: Vector4) a -> LinearMap (row -> a) (Vector4 a) Source #

(Diagonalizable ((->) row) a, Num a, ConjugateSymmetric a, Universe row, Universe col) => Linearizable LinearMap ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) ((->) row :: Type -> Type) ((->) col :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

fromLinear :: LinearMap (row -> a) (col -> a) -> ((->) row :*: (->) col) a Source #

linear :: ((->) row :*: (->) col) a -> LinearMap (row -> a) (col -> a) Source #

class Diagonalizable m a => Traceable m a where Source #

Minimal complete definition

trace_impl, determinant_impl

Methods

trace_impl :: (m :*: m) a -> a Source #

determinant_impl :: (m :*: m) a -> a Source #

vector_dimension :: m a -> a Source #

Instances

Instances details
Num a => Traceable Vector1 a Source # 
Instance details

Defined in Math.Matrix.Vector1

Num a => Traceable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => Traceable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => Traceable Vector4 a Source # 
Instance details

Defined in Math.Matrix.Vector4

(Eq dim, Num dim, Integral dim, Universe dim, CoFactorDimension dim, ConjugateSymmetric a, Num a) => Traceable ((->) dim) a Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

trace_impl :: ((->) dim :*: (->) dim) a -> a Source #

determinant_impl :: ((->) dim :*: (->) dim) a -> a Source #

vector_dimension :: (dim -> a) -> a Source #

class (Category arr, Traceable m a) => LinearTraceable arr m a where Source #

Minimal complete definition

Nothing

Methods

determinant :: arr (m a) (m a) -> a Source #

default determinant :: Linearizable arr (:*:) m m a => arr (m a) (m a) -> a Source #

trace :: arr (m a) (m a) -> a Source #

default trace :: Linearizable arr (:*:) m m a => arr (m a) (m a) -> a Source #

Instances

Instances details
(ConjugateSymmetric a, Num a) => LinearTraceable LinearMap Vector2 a Source # 
Instance details

Defined in Math.Matrix.Linear

class LinearTraceable arr m a => LinearInvertible arr m a where Source #

Minimal complete definition

Nothing

Methods

cofactor :: arr (m a) (m a) -> arr (m a) (m a) Source #

default cofactor :: (Invertible m a, Linearizable arr (:*:) m m a) => arr (m a) (m a) -> arr (m a) (m a) Source #

adjucate :: arr (m a) (m a) -> arr (m a) (m a) Source #

default adjucate :: (Invertible m a, Linearizable arr (:*:) m m a) => arr (m a) (m a) -> arr (m a) (m a) Source #

inverse :: arr (m a) (m a) -> arr (m a) (m a) Source #

default inverse :: (Invertible m a, Linearizable arr (:*:) m m a) => arr (m a) (m a) -> arr (m a) (m a) Source #

dual_basis_impl :: Invertible m a => (m :*: m) a -> (m :*: m) a Source #

this computes \[f(A) = (A^{-1})^{\top}\] it's used to compute dual basis for a set of basis vectors.

dual_basis :: (Invertible m a, Linearizable arr (:*:) m m a) => arr (m a) (m a) -> arr (m a) (m a) Source #

class Functor m => EigenDecomposable m a where Source #

Methods

eigenvalues :: (m :*: m) a -> m a Source #

Instances

Instances details
Floating a => EigenDecomposable Vector2 a Source # 
Instance details

Defined in Math.Matrix.Vector2

(Floating a, Ord a, ConjugateSymmetric a) => EigenDecomposable Vector3 a Source # 
Instance details

Defined in Math.Matrix.Vector3

class EigenDecomposable m a => EigenVectorable m a where Source #

Methods

eigenvectors :: (m :*: m) a -> (m :*: m) a Source #

class (Applicative m, Applicative n) => AppendableVector m n where Source #

Associated Types

type m :+: n :: * -> * Source #

Methods

(||>>) :: m a -> n a -> (m :+: n) a Source #

Instances

Instances details
AppendableVector Vector1 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Vector1 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector1 a -> (Vector1 :+: Vector1) a Source #

AppendableVector Vector1 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Vector1 :+: Vector2 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector2 a -> (Vector1 :+: Vector2) a Source #

AppendableVector Vector1 Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector1 :+: Vector3 :: Type -> Type Source #

Methods

(||>>) :: Vector1 a -> Vector3 a -> (Vector1 :+: Vector3) a Source #

AppendableVector Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Vector2 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Vector1 a -> (Vector2 :+: Vector1) a Source #

AppendableVector Vector2 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector2 :+: Vector2 :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Vector2 a -> (Vector2 :+: Vector2) a Source #

AppendableVector Vector2 Stream Source # 
Instance details

Defined in Math.Matrix.VectorConversions

Associated Types

type Vector2 :+: Stream :: Type -> Type Source #

Methods

(||>>) :: Vector2 a -> Stream a -> (Vector2 :+: Stream) a Source #

AppendableVector Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector3 :+: Vector1 :: Type -> Type Source #

Methods

(||>>) :: Vector3 a -> Vector1 a -> (Vector3 :+: Vector1) a Source #

AppendableVector Vector3 Stream Source # 
Instance details

Defined in Math.Number.Stream

Associated Types

type Vector3 :+: Stream :: Type -> Type Source #

Methods

(||>>) :: Vector3 a -> Stream a -> (Vector3 :+: Stream) a Source #

StreamBuilder str => AppendableVector Vector4 str Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Vector4 :+: str :: Type -> Type Source #

Methods

(||>>) :: Vector4 a -> str a -> (Vector4 :+: str) a Source #

AppendableVector List List Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type List :+: List :: Type -> Type Source #

Methods

(||>>) :: [a] -> [a] -> (List :+: List) a Source #

class AppendableVector m n => SplittableVector m n where Source #

Methods

vsplit :: (m :+: n) a -> (m a, n a) Source #

Instances

Instances details
SplittableVector Vector1 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

vsplit :: (Vector1 :+: Vector1) a -> (Vector1 a, Vector1 a) Source #

SplittableVector Vector1 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

vsplit :: (Vector1 :+: Vector2) a -> (Vector1 a, Vector2 a) Source #

SplittableVector Vector1 Vector3 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector1 :+: Vector3) a -> (Vector1 a, Vector3 a) Source #

SplittableVector Vector2 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector3

Methods

vsplit :: (Vector2 :+: Vector1) a -> (Vector2 a, Vector1 a) Source #

SplittableVector Vector2 Vector2 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector2 :+: Vector2) a -> (Vector2 a, Vector2 a) Source #

SplittableVector Vector3 Vector1 Source # 
Instance details

Defined in Math.Matrix.Vector4

Methods

vsplit :: (Vector3 :+: Vector1) a -> (Vector3 a, Vector1 a) Source #

class Conditional a where Source #

Methods

fromBoolean :: Bool -> a Source #

Instances

Instances details
Conditional Integer Source # 
Instance details

Defined in Math.Matrix.Interface

Conditional Float Source # 
Instance details

Defined in Math.Matrix.Interface

Conditional Int Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

fromBoolean :: Bool -> Int Source #

class StandardBasis m where Source #

Methods

unit_vectors :: [m] Source #

Instances

Instances details
StandardBasis Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Num a => StandardBasis (Complex a) Source # 
Instance details

Defined in Math.Matrix.Interface

Num a => StandardBasis (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

StandardBasis (Vector2 (Vector2 Int)) Source # 
Instance details

Defined in Math.Matrix.Vector2

StandardBasis (Vector2 Int) Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => StandardBasis (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Num a => StandardBasis (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Num a => StandardBasis (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

(ConjugateSymmetric a, Num a) => StandardBasis ((Dual :*: Vector2) a) Source #

https://en.wikipedia.org/wiki/Dual_space

Instance details

Defined in Math.Matrix.Covector

(Num a, ConjugateSymmetric a) => StandardBasis ((Dual :*: Vector3) a) Source #

https://en.wikipedia.org/wiki/Dual_space

Instance details

Defined in Math.Matrix.Linear

(Functor f, Functor g, Num a, StandardBasis (g a), StandardBasis (f a)) => StandardBasis ((f :*: g) a) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

unit_vectors :: [(f :*: g) a] Source #

class VectorSpace v => CoordinateSpace v where Source #

Associated Types

type Coordinate v Source #

Instances

Instances details
Num a => CoordinateSpace (Vector1 a) Source # 
Instance details

Defined in Math.Matrix.Vector1

Associated Types

type Coordinate (Vector1 a) Source #

Num a => CoordinateSpace (Vector2 a) Source # 
Instance details

Defined in Math.Matrix.Vector2

Associated Types

type Coordinate (Vector2 a) Source #

Num a => CoordinateSpace (Vector3 a) Source # 
Instance details

Defined in Math.Matrix.Vector3

Associated Types

type Coordinate (Vector3 a) Source #

Num a => CoordinateSpace (Vector4 a) Source # 
Instance details

Defined in Math.Matrix.Vector4

Associated Types

type Coordinate (Vector4 a) Source #

class (Num (Scalar v), VectorSpace v) => NumSpace v Source #

vector space with scalars in Num class

class (Fractional (Scalar v), NumSpace v) => FractionalSpace v Source #

vector space with fractional scalars

class HasIdentityLinear v arr where Source #

Methods

mat_identity :: (Num a, ConjugateSymmetric a) => arr (v a) (v a) Source #

class VectorSpace v => Dualizable v d where Source #

Methods

covector :: (v -> Scalar v) -> d v Source #

bracket :: d v -> v -> Scalar v Source #

Instances

Instances details
(ConjugateSymmetric a, Num a) => Dualizable (Vector1 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector1 a -> Scalar (Vector1 a)) -> Dual (Vector1 a) Source #

bracket :: Dual (Vector1 a) -> Vector1 a -> Scalar (Vector1 a) Source #

(Num a, ConjugateSymmetric a) => Dualizable (Vector2 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector2 a -> Scalar (Vector2 a)) -> Dual (Vector2 a) Source #

bracket :: Dual (Vector2 a) -> Vector2 a -> Scalar (Vector2 a) Source #

(ConjugateSymmetric a, Num a) => Dualizable (Vector3 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector3 a -> Scalar (Vector3 a)) -> Dual (Vector3 a) Source #

bracket :: Dual (Vector3 a) -> Vector3 a -> Scalar (Vector3 a) Source #

(ConjugateSymmetric a, Num a) => Dualizable (Vector4 a) Dual Source # 
Instance details

Defined in Math.Matrix.Linear

Methods

covector :: (Vector4 a -> Scalar (Vector4 a)) -> Dual (Vector4 a) Source #

bracket :: Dual (Vector4 a) -> Vector4 a -> Scalar (Vector4 a) Source #

(Integral a, Universe a, Num b, ConjugateSymmetric b) => Dualizable (a -> b) Dual Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

covector :: ((a -> b) -> Scalar (a -> b)) -> Dual (a -> b) Source #

bracket :: Dual (a -> b) -> (a -> b) -> Scalar (a -> b) Source #

class VectorSpace v => VectorDerivative v d arr | d -> arr, v arr -> d where Source #

Minimal complete definition

divergence, grad, directional_derivative

Methods

divergence :: arr v v -> d v Source #

grad :: d v -> arr v v Source #

directional_derivative :: v -> d v -> d v Source #

laplace :: d v -> d v Source #

Instances

Instances details
(ConjugateSymmetric a, Num a, Closed a) => VectorDerivative (Vector1 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(ConjugateSymmetric a, Infinitesimal Stream a, Closed a) => VectorDerivative (Vector2 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Closed a, Num a, ConjugateSymmetric a) => VectorDerivative (Vector3 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, Closed a, ConjugateSymmetric a, LinearTransform Vector4 Vector1 a) => VectorDerivative (Vector4 a) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.LinearOperations

(b ~ Scalar a, Scalar (a -> b) ~ b, Integral a, VectorSpace b, ConjugateSymmetric b, Closed b, Infinitesimal Stream b, Eq a, Universe a) => VectorDerivative (a -> b) Dual LinearMap Source # 
Instance details

Defined in Math.Matrix.Simple

Methods

divergence :: LinearMap (a -> b) (a -> b) -> Dual (a -> b) Source #

grad :: Dual (a -> b) -> LinearMap (a -> b) (a -> b) Source #

directional_derivative :: (a -> b) -> Dual (a -> b) -> Dual (a -> b) Source #

laplace :: Dual (a -> b) -> Dual (a -> b) Source #

normalized_directional_derivative :: (VectorDerivative v d arr, NormedSpace v, Fractional (Scalar v)) => v -> d v -> d v Source #

version of directional derivative that normalizes the direction: https://mathworld.wolfram.com/DirectionalDerivative.html

class VectorCrossProduct v arr where Source #

Methods

curl :: arr v v -> arr v v Source #

Instances

Instances details
(ConjugateSymmetric a, Infinitesimal Stream a, VectorSpace a, Closed a) => VectorCrossProduct (Vector2 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

(Closed a, Num a, ConjugateSymmetric a) => VectorCrossProduct (Vector3 a :: Type) LinearMap Source # 
Instance details

Defined in Math.Matrix.Linear

class Functor f => ProjectionDual f d a where Source #

Methods

projection_dual :: f (d (f a)) Source #

Instances

Instances details
(ConjugateSymmetric a, Num a) => ProjectionDual Vector1 Dual a Source # 
Instance details

Defined in Math.Matrix.Linear

(ConjugateSymmetric a, Num a) => ProjectionDual Vector2 Dual a Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => ProjectionDual Vector3 Dual a Source # 
Instance details

Defined in Math.Matrix.Linear

(Num a, ConjugateSymmetric a) => ProjectionDual Vector4 Dual a Source # 
Instance details

Defined in Math.Matrix.LinearOperations

matrixM :: (Traversable f, Traversable g, Monad m) => (a -> b -> m c) -> f a -> g b -> m ((f :*: g) c) Source #

matrixMatrix :: (Functor m, Functor n, Functor m', Functor n') => (a -> b -> c) -> (m :*: m') a -> (n :*: n') b -> ((m :*: n) :*: (m' :*: n')) c Source #

newtype Basis m Source #

Constructors

Basis [m] 

Instances

Instances details
Show v => Show (Basis v) Source # 
Instance details

Defined in Math.Matrix.Interface

Methods

showsPrec :: Int -> Basis v -> ShowS #

show :: Basis v -> String #

showList :: [Basis v] -> ShowS #

VectorSpace k => VectorSpace (Basis k) Source # 
Instance details

Defined in Math.Matrix.Interface

Associated Types

type Scalar (Basis k) Source #

Methods

vzero :: Basis k Source #

vnegate :: Basis k -> Basis k Source #

(%+) :: Basis k -> Basis k -> Basis k Source #

(%*) :: Scalar (Basis k) -> Basis k -> Basis k Source #

type Scalar (Basis k) Source # 
Instance details

Defined in Math.Matrix.Interface

type Scalar (Basis k) = Scalar k

(%-) :: VectorSpace v => v -> v -> v infixl 6 Source #

(%/) :: (Fractional (Scalar v), VectorSpace v) => v -> Scalar v -> v Source #

vsum :: (Foldable t, VectorSpace a) => t a -> a Source #

divide :: (Fractional (Scalar v), VectorSpace v) => v -> Scalar v -> v Source #

vaverage :: (Num v, Fractional (Scalar v), VectorSpace v) => [v] -> v Source #

(%*%) :: SupportsMatrixMultiplication f g h a => (f :*: g) a -> (g :*: h) a -> (f :*: h) (Scalar (g a)) Source #

generalized implementation of matrix multiplication see http://en.wikipedia.org/wiki/Matrix_multiplication

(%**%) :: (SupportsMatrixMultiplication f g h a, Linearizable arr (:*:) f h a, Linearizable arr (:*:) f g a, Linearizable arr (:*:) g h a) => arr (f a) (g a) -> arr (g a) (h a) -> arr (f a) (h a) Source #

type MatrixNorm arr h m a = (LinearTraceable arr m (Scalar (h a)), InnerProductSpace (h a), ConjugateSymmetric a, Transposable h m a) Source #

In this version, we must assume VectorSpaceOver (h a) a constraint, but the result type is nicer.

(%^%) :: (SupportsMatrixMultiplication f f f a, Diagonalizable f (f a), Diagonalizable f a) => (f :*: f) a -> Integer -> (f :*: f) a Source #

(|><|) :: (Functor m, Functor n, InnerProductSpace a) => m a -> n a -> (m :*: n) (Scalar a) Source #

(%.%) :: (Num (Scalar m), CoordinateSpace m) => m -> m -> Scalar m infixl 7 Source #

functionMatrix :: Diagonalizable f b => (f b -> g b) -> (f :*: g) b Source #

This is the linearity condition:

convex_combination :: (VectorSpace v, Fractional (Scalar v), Foldable t, Applicative t) => t (Scalar v) -> t v -> v Source #

https://en.wikipedia.org/wiki/Convex_combination This computes \[f([a_0,a_1,...,a_n], [{\mathbf b}_0,{\mathbf b}_1,...,{\mathbf b}_n]) = {{\sum_{j=0}^n{a_j{\mathbf b}_j}} \over \sum_{i=0}^n{a_i}}\]

vec2_cast :: (a :~: b) -> (a :~: b) -> a :~: b Source #

hilbertSpace :: (Num m, NormedSpace m) => m -> m -> Scalar m Source #

left_unitor :: (I :*: f) a -> f a Source #

right_unitor :: Functor f => (f :*: I) a -> f a Source #

associator :: Functor f => ((f :*: g) :*: h) a -> (f :*: (g :*: h)) a Source #

unassociator :: Functor f => (f :*: (g :*: h)) a -> ((f :*: g) :*: h) a Source #

(<!>) :: (Functor f, Functor g) => (g :*: f) a -> (g c -> b, f a -> c) -> b Source #

reduceI :: (I :*: I) a -> I a Source #

sum_coordinates :: (Foldable t, Num a) => t a -> a Source #

join_matrix :: (Monad g, Monad f, forall b. Transposable g f b) => (f :*: g) ((f :*: g) a) -> (f :*: g) a Source #

Orphan instances

PpShowVerticalF Complex Source # 
Instance details

Methods

ppf_vertical :: PpShow a => Complex a -> Doc Source #

Num a => Num (Endo a) Source # 
Instance details

Methods

(+) :: Endo a -> Endo a -> Endo a #

(-) :: Endo a -> Endo a -> Endo a #

(*) :: Endo a -> Endo a -> Endo a #

negate :: Endo a -> Endo a #

abs :: Endo a -> Endo a #

signum :: Endo a -> Endo a #

fromInteger :: Integer -> Endo a #