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

Math.Matrix.Vector2

Synopsis

Documentation

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

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

writeColumn :: 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

ppfVertical :: 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 #

(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) => 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

(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

transposeImpl :: (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

Methods

unitVectors :: [Vector2 a] Source #

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

Methods

allElements :: [Vector2 a] Source #

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

transposeImpl :: ((->) 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.Vector2" "cifl-math-library-2.0.0.0-K3Wcv1zXOBxvFThQyThI4" '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

setx2 :: s -> Vector2 s -> Vector2 s Source #

sety2 :: s -> Vector2 s -> Vector2 s Source #

updateRow2 :: g a -> Vector2 ((Vector2 :*: g) a -> (Vector2 :*: g) a) Source #

updateColumn2 :: Applicative f => f a -> Vector2 ((f :*: Vector2) a -> (f :*: Vector2) a) Source #

i2 :: Num a => Vector2 a Source #

j2 :: Num a => Vector2 a Source #

vec2 :: (a, a) -> Vector2 a Source #

splitMatrix :: (Functor f, SplittableVector f f, SplittableVector m m) => ((f :+: f) :*: (m :+: m)) a -> (Vector2 :*: Vector2) ((f :*: m) a) Source #

composeIndex :: (m (n a) :==: I (n a)) -> (n a :==: I a) -> (m :*: n) a :==: (I :*: I) a Source #

rightMultiply2Gen :: (VectorSpace (f a), ConjugateSymmetric a, Scalar (f a) ~ a) => (Vector2 :*: f) a -> Vector2 a -> f a Source #

trace2 :: Num a => Matrix2 a -> a Source #

Orphan instances

AppendableVector Vector1 Vector1 Source # 
Instance details

Associated Types

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

Methods

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

SplittableVector Vector1 Vector1 Source # 
Instance details

Methods

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