lapack-0.5.1.1: Numerical Linear Algebra using LAPACK
Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.LAPACK.Shape

Synopsis

Documentation

class C shape => Permutable shape Source #

Class of shapes where indices still make sense if we permute elements. We use this for all matrix factorisations involving permutations or more generally orthogonal transformations, e.g. eigenvalue and singular value, LU and QR decompositions. E.g. say, we have a square matrix with dimension 'Shape.Enumeration Ordering'. Its vector of eigenvalues has the same dimension, but it does not make sense to access the eigenvalues with indices like LT or EQ. Thus Enumeration is no instance of Permutable (and you should not add an orphan instance).

If you want to factor a matrix with a non-permutable shape, you should convert it temporarily to a permutable one, like ZeroBased (i.e. ShapeInt) or IntIndexed.

The Permutable class has no method, so you could add any shape to it. However, you should use good taste when adding an instance. There is no strict criterion which shape type to add.

We tried to use ShapeInt for eigenvalue vectors and LiberalSquares as transformation matrices of eigenvalue decompositions. However, this way, the type checker cannot infer that the product of the factorisation is a strict square.

We also tried to use IntIndexed for eigenvalue vectors with according LiberalSquares transformations. This has also the problem of inferring squares. Additionally, more such transformations lead to nested IntIndexed wrappers and for ShapeInt even the first wrapper is unnecessary.

Instances

Instances details
Permutable Zero Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Permutable () Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Integral n => Permutable (Cyclic n) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Permutable sh => Permutable (Deferred sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Integral n => Permutable (OneBased n) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Ix n => Permutable (Range n) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Integral n => Permutable (Shifted n) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Integral n => Permutable (ZeroBased n) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

C sh => Permutable (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Permutable sh => Permutable (Tagged s sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

newtype IntIndexed sh Source #

This shape type wraps any other array shape type. However, its Indexed instance just uses zero-based Int indices. Thus it can turn any shape type into a Indexed one. The main usage is to make an arbitrary shape Permutable.

Constructors

IntIndexed 

Fields

Instances

Instances details
Show sh => Show (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Methods

showsPrec :: Int -> IntIndexed sh -> ShowS #

show :: IntIndexed sh -> String #

showList :: [IntIndexed sh] -> ShowS #

C sh => C (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Methods

size :: IntIndexed sh -> Int #

C sh => Indexed (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Associated Types

type Index (IntIndexed sh) #

C sh => InvIndexed (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

NFData sh => NFData (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Methods

rnf :: IntIndexed sh -> () #

Eq sh => Eq (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

Methods

(==) :: IntIndexed sh -> IntIndexed sh -> Bool #

(/=) :: IntIndexed sh -> IntIndexed sh -> Bool #

C sh => FormatArray (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Plain.Format

Methods

formatArray :: (Floating a, Output out) => Config -> Array (IntIndexed sh) a -> out Source #

C sh => Permutable (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

type Index (IntIndexed sh) Source # 
Instance details

Defined in Numeric.LAPACK.Shape

type Index (IntIndexed sh) = Int

shapeInt :: C sh => sh -> ZeroBased Int Source #