lapack-0.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) => Array shx a -> Array shy a -> Array (shx :+: shy) a #

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

Precedence and associativity (right) of (List.++). This also matches '(Shape.:+:)'.

take :: (Integral n, Storable a) => n -> Array (ZeroBased n) a -> Array (ZeroBased n) a #

drop :: (Integral n, Storable a) => n -> Array (ZeroBased n) a -> Array (ZeroBased n) a #

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

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

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

singleton :: Storable a => a -> Array () a #

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

constant () = singleton

However, singleton does not need Floating constraint.

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

one :: (C sh, Floating a) => sh -> 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

(-*|) :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> a infixl 7 Source #

dot x y = Matrix.toScalar (singleRow x <#> singleColumn 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.

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

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 #

(.*|) :: (C sh, Floating a) => a -> Vector sh a -> Vector sh a infixl 7 Source #

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

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

(|+|) :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> Vector sh a infixl 6 Source #

(|-|) :: (C sh, Eq sh, Floating a) => Vector sh a -> Vector sh a -> Vector sh a infixl 6 Source #

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

raise :: (C sh, Floating a) => a -> Array sh a -> Array 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 #

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

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

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

For restrictions see limits.

argMinimum :: (InvIndexed sh, Index sh ~ ix, Real a) => Vector sh a -> (ix, a) Source #

For restrictions see limits.

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

For restrictions see limits.

argMaximum :: (InvIndexed sh, Index sh ~ ix, Real a) => Vector sh a -> (ix, a) Source #

For restrictions see limits.

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

It should hold limits x = Array.limits x. The function is based on fast BLAS functions. It should be faster than Array.minimum and Array.maximum although it is certainly not as fast as possible. It is less precise if minimum and maximum differ considerably in magnitude and there are several minimum or maximum candidates of similar value. E.g. you cannot rely on the property that raise (- minimum x) x has only non-negative elements.

argLimits :: (InvIndexed sh, Index sh ~ ix, Real a) => Vector sh a -> ((ix, a), (ix, a)) Source #

foldl :: (C sh, Storable a) => (b -> a -> b) -> b -> Array sh a -> b #

foldl1 :: (C sh, Storable a) => (a -> a -> a) -> Array sh a -> a #

foldMap :: (C sh, Storable a, Ord a, Semigroup m) => (a -> m) -> Array sh a -> m #

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 #

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