lapack-0.2.3.1: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Vector

Synopsis

Documentation

type family RealOf x Source #

Instances
type RealOf Double Source # 
Instance details

Defined in Numeric.LAPACK.Scalar

type RealOf Float Source # 
Instance details

Defined in Numeric.LAPACK.Scalar

type RealOf (Complex a) Source # 
Instance details

Defined in Numeric.LAPACK.Scalar

type RealOf (Complex a) = a

toList :: (C sh, Storable a) => Vector sh a -> [a] Source #

fromList :: (C sh, Storable a) => sh -> [a] -> Vector sh a Source #

append :: (C shx, C shy, Storable a) => Vector shx a -> Vector shy a -> Vector (shx :+: shy) a Source #

takeLeft :: (C sh0, C sh1, Storable a) => Vector (sh0 :+: sh1) a -> Vector sh0 a Source #

takeRight :: (C sh0, C sh1, Storable a) => Vector (sh0 :+: sh1) a -> Vector sh1 a Source #

swap :: (Indexed sh, Storable a) => Index sh -> Index sh -> Vector sh a -> Vector sh a Source #

singleton :: Storable a => a -> Vector () a Source #

singleton = constant ()

However, singleton does not need Floating constraint.

constant :: (C sh, Floating a) => sh -> a -> Vector sh a Source #

unit :: (Indexed sh, Floating a) => sh -> Index sh -> Vector sh a Source #

dot :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> a Source #

dot x y = Matrix.toScalar (singleRow x <#> singleColumn y)

inner :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> a Source #

inner x y = dot (conjugate x) y

sum :: (C sh, Floating a) => Vector sh a -> a Source #

absSum :: (C sh, Floating a) => Vector sh a -> RealOf a Source #

Sum of the absolute values of real numbers or components of complex numbers. For real numbers it is equivalent to norm1.

norm1 :: (C sh, Floating a) => Vector sh a -> RealOf a Source #

norm2 :: (C sh, Floating a) => Vector sh a -> RealOf a Source #

Euclidean norm of a vector or Frobenius norm of a matrix.

normInf :: (C sh, Floating a) => Vector sh a -> RealOf a Source #

normInf1 :: (C sh, Floating a) => Vector sh a -> RealOf a Source #

Computes (almost) the infinity norm of the vector. For complex numbers every element is replaced by the sum of the absolute component values first.

argAbsMaximum :: (InvIndexed sh, Floating a) => Vector sh a -> (Index sh, a) Source #

Returns the index and value of the element with the maximal absolute value. Caution: It actually returns the value of the element, not its absolute value!

argAbs1Maximum :: (InvIndexed sh, Floating a) => Vector sh a -> (Index sh, a) Source #

Returns the index and value of the element with the maximal absolute value. The function does not strictly compare the absolute value of a complex number but the sum of the absolute complex components. Caution: It actually returns the value of the element, not its absolute value!

product :: (C sh, Floating a) => Vector sh a -> a Source #

scale :: (C sh, Floating a) => a -> Vector sh a -> Vector sh a Source #

scaleReal :: (C sh, Floating a) => RealOf a -> Vector sh a -> Vector sh a Source #

add :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> Vector sh a Source #

sub :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> Vector sh a Source #

mac :: (C sh, Eq sh, Floating a) => a -> Vector sh a -> Vector sh a -> Vector sh a Source #

mul :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> Vector sh a Source #

conjugate :: (C sh, Floating a) => Vector sh a -> Vector sh a Source #

fromReal :: (C sh, Floating a) => Vector sh (RealOf a) -> Vector sh a Source #

toComplex :: (C sh, Floating a) => Vector sh a -> Vector sh (ComplexOf a) Source #

realPart :: (C sh, Floating a) => Vector sh a -> Vector sh (RealOf a) Source #

complexFromReal :: (C sh, Real a) => Vector sh a -> Vector sh (Complex a) Source #

complexToRealPart :: (C sh, Real a) => Vector sh (Complex a) -> Vector sh a Source #

complexToImaginaryPart :: (C sh, Real a) => Vector sh (Complex a) -> Vector sh a Source #

zipComplex :: (C sh, Eq sh, Real a) => Vector sh a -> Vector sh a -> Vector sh (Complex a) Source #

unzipComplex :: (C sh, Real a) => Vector sh (Complex a) -> (Vector sh a, Vector sh a) Source #

random :: (C sh, Floating a) => RandomDistribution -> sh -> Word64 -> Vector sh a Source #

data RandomDistribution Source #

Instances
Enum RandomDistribution Source # 
Instance details

Defined in Numeric.LAPACK.Vector

Eq RandomDistribution Source # 
Instance details

Defined in Numeric.LAPACK.Vector

Ord RandomDistribution Source # 
Instance details

Defined in Numeric.LAPACK.Vector

Show RandomDistribution Source # 
Instance details

Defined in Numeric.LAPACK.Vector