comfort-blas-0.0.2: Numerical Basic Linear Algebra using BLAS
Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.BLAS.Vector.Slice

Synopsis

Documentation

data T sh slice a Source #

Instances

Instances details
(C sh, Storable a, Show slice, Show sh, Show a) => Show (T sh slice a) Source # 
Instance details

Defined in Numeric.BLAS.Vector.Slice

Methods

showsPrec :: Int -> T sh slice a -> ShowS #

show :: T sh slice a -> String #

showList :: [T sh slice a] -> ShowS #

shape :: T sh slice a -> slice Source #

type family RealOf x Source #

Instances

Instances details
type RealOf Double Source # 
Instance details

Defined in Numeric.BLAS.Scalar

type RealOf Float Source # 
Instance details

Defined in Numeric.BLAS.Scalar

type RealOf (Complex a) Source # 
Instance details

Defined in Numeric.BLAS.Scalar

type RealOf (Complex a) = a

slice :: (T shA -> T shB) -> T sh shA a -> T sh shB a Source #

fromStorableVector :: Vector a -> T ShapeInt ShapeInt a Source #

Non-copying conversion from StorableVector.

fromVector :: C sh => Vector sh a -> T sh sh a Source #

toVector :: (C slice, Floating a) => T sh slice a -> Vector slice a Source #

extract :: (C slice, C sh, Floating a) => (T sh -> T slice) -> Vector sh a -> Vector slice a Source #

QC.forAll genShape $ \shape@(_::+(_rows,columns)::+_) -> QC.forAll (QC.elements (Shape.indices columns)) $ \c -> QC.forAll (genVector shape number_) $ \xs -> VectorSlice.extract (Slice.column c . Slice.left . Slice.right) xs == Matrix.takeColumn c (Vector.takeLeft (Vector.takeRight (xs :: Vector Number_)))
forAll_ (TestSlice.genShapeSelect 4 100) $ \(TestSlice.ShapeSelect sh select) -> QC.forAll (genVector sh number_) $ \xs -> case TestSlice.instantiate sh select of TestSlice.Extraction slice cut -> VectorSlice.extract slice xs == cut xs

access :: (C shA, Indexed sh, Storable a) => T shA sh a -> Index sh -> a Source #

replicate :: (C sh, Storable a) => sh -> a -> T () sh a Source #

QC.forAll genShape $ \shape a -> VectorSlice.toVector (VectorSlice.replicate shape a) == Vector.constant shape (a :: Number_)

append :: (C sliceA, C sliceB, Floating a) => T shA sliceA a -> T shB sliceB a -> Vector (sliceA ::+ sliceB) a Source #

>>> List.map realPart $ Vector.toList $ VectorSlice.append (VectorSlice.fromVector $ Vector.autoFromList [3,1,4,1]) (VectorSlice.replicate (Shape.ZeroBased (3::Int)) (0::Number_))
[3.0,1.0,4.0,1.0,0.0,0.0,0.0]

data Chunk a Source #

chunk :: Storable a => T sh ShapeInt a -> Chunk a Source #

concat :: Floating a => [Chunk a] -> Vector ShapeInt a Source #

>>> List.map realPart $ Vector.toList $ let matrix = Vector.fromList (Shape.ZeroBased (4::Int), Shape.ZeroBased (3::Int)) $ map (\x -> fromInteger x :: Number_) [0 ..] in VectorSlice.concat $ map (\k -> VectorSlice.chunk (VectorSlice.slice (Slice.column k) $ VectorSlice.fromVector matrix)) [0,1,2]
[0.0,3.0,6.0,9.0,1.0,4.0,7.0,10.0,2.0,5.0,8.0,11.0]

dot :: (C sh, Eq sh, Floating a) => T shA sh a -> T shB sh a -> a Source #

inner :: (C sh, Eq sh, Floating a) => T shA sh a -> T shB sh a -> a Source #

forSliced2 number_ $ \xs ys -> VectorSlice.inner xs ys == Vector.dot (VectorSlice.conjugate xs) (VectorSlice.toVector ys)
forSliced number_ $ \xs -> VectorSlice.inner xs xs == Scalar.fromReal (VectorSlice.norm2Squared xs)

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

forSliced number_ $ \xs -> VectorSlice.sum xs == List.sum (listFromSlice xs)

absSum :: (C sh, Floating a) => T shA 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.

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

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

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

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

forSliced number_ $ \xs -> VectorSlice.normInf xs == List.maximum (0 : List.map absolute (listFromSlice xs))

normInf1 :: (C sh, Floating a) => T shA 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.

forSliced number_ $ \xs -> VectorSlice.normInf1 xs == List.maximum (0 : List.map Scalar.norm1 (listFromSlice xs))

argAbsMaximum :: (InvIndexed sh, Floating a) => T shA 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!

forSliced number_ $ \xs -> isNonEmpty xs ==> let (xi,xm) = VectorSlice.argAbsMaximum xs in VectorSlice.access xs xi == xm
forSliced number_ $ \xs -> isNonEmpty xs ==> let (_xi,xm) = VectorSlice.argAbsMaximum xs in List.all (\x -> absolute x <= absolute xm) $ listFromSlice xs
forSliced number_ $ \xs -> forSliced number_ $ \ys -> isNonEmpty xs && isNonEmpty ys ==> let (_xi,xm) = VectorSlice.argAbsMaximum xs; (_yi,ym) = VectorSlice.argAbsMaximum ys; (zi,zm) = Vector.argAbsMaximum (VectorSlice.toVector xs +++ VectorSlice.toVector ys) in case zi of Left _ -> xm==zm && absolute xm >= absolute ym; Right _ -> ym==zm && absolute xm < absolute ym

argAbs1Maximum :: (InvIndexed sh, Floating a) => T shA 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!

forSliced real_ $ \xs -> isNonEmpty xs ==> VectorSlice.argAbsMaximum xs == VectorSlice.argAbs1Maximum xs

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

QC.forAll genShape $ \sh@(_::+(_rows,columns)::+_) -> QC.forAll (QC.elements (Shape.indices columns)) $ \c -> QC.forAll (genVector sh $ genNumber 3) $ \xt -> let xs = takeColumn c xt in approx 1e-2 (VectorSlice.product xs) (List.product (listFromSlice (xs :: Sliced Number_)))

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

forSliced number_ $ \xs -> VectorSlice.negate xs == VectorSlice.scale minusOne xs
forSliced number_ $ \xs -> VectorSlice.scale 2 xs == VectorSlice.add xs xs

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

Complex implementation requires double number of multiplications compared to scaleReal.

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

forSliced2 number_ $ \xs ys -> VectorSlice.add xs ys == VectorSlice.add ys xs
forSliced2 number_ $ \xs ys -> VectorSlice.toVector xs == VectorSlice.sub xs ys |+| VectorSlice.toVector ys

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

forSliced2 number_ $ \xs ys -> VectorSlice.add xs ys == VectorSlice.add ys xs
forSliced2 number_ $ \xs ys -> VectorSlice.toVector xs == VectorSlice.sub xs ys |+| VectorSlice.toVector ys

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

forSliced number_ $ \xs -> VectorSlice.toVector xs == Vector.negate (VectorSlice.negate xs)

raise :: (C sh, Floating a) => a -> T shA sh a -> Vector sh a Source #

QC.forAll (genNumber maxElem) $ \d -> forSliced number_ $ \xs -> VectorSlice.toVector xs == Vector.raise (-d) (VectorSlice.raise d xs)

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

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

forSliced2 number_ $ \xs ys -> VectorSlice.mul xs ys == VectorSlice.mul ys xs

mulConj :: (C sh, Eq sh, Floating a) => T shA sh a -> T shB sh a -> Vector sh a Source #

forSliced2 number_ $ \xs ys -> VectorSlice.mulConj xs ys == Vector.mul (VectorSlice.conjugate xs) (VectorSlice.toVector ys)

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

For restrictions see limits.

forSliced real_ $ \xs -> isNonEmpty xs ==> VectorSlice.minimum xs == List.minimum (listFromSlice xs)
forSliced real_ $ \xs -> isNonEmpty xs ==> VectorSlice.maximum xs == List.maximum (listFromSlice xs)

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

For restrictions see limits.

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

For restrictions see limits.

forSliced real_ $ \xs -> isNonEmpty xs ==> VectorSlice.minimum xs == List.minimum (listFromSlice xs)
forSliced real_ $ \xs -> isNonEmpty xs ==> VectorSlice.maximum xs == List.maximum (listFromSlice xs)

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

For restrictions see limits.

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

forSliced real_ $ \xs -> isNonEmpty xs ==> VectorSlice.limits xs == Array.limits (VectorSlice.toVector xs)

In contrast to limits this implementation 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. Boths limits share the precision of the limit with the larger absolute value. This implies for example that you cannot rely on the property that raise (- minimum x) x has only non-negative elements.

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

For restrictions see limits.

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

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

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

realFromComplexVector :: C sh => Vector sh (Complex a) -> T (sh, ComplexShape) (sh, ComplexShape) a Source #

realPart :: (C sh, Real a) => T shA sh (Complex a) -> T (shA, ComplexShape) sh a Source #

imaginaryPart :: (C sh, Real a) => T shA sh (Complex a) -> T (shA, ComplexShape) sh a Source #

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

unzipComplex :: (C sh, Real a) => T shA sh (Complex a) -> (T (shA, ComplexShape) sh a, T (shA, ComplexShape) sh a) Source #

forSliced complex_ $ \xs -> approxReal 1e-2 (VectorSlice.norm2 xs) $ let (xrs,xis) = VectorSlice.unzipComplex xs in sqrt $ VectorSlice.norm2Squared xrs + VectorSlice.norm2Squared xis