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

Numeric.LAPACK.Matrix

Synopsis

Documentation

data family Matrix typ extraLower extraUpper lower upper meas vert horiz height width a Source #

Instances

Instances details
(MultiplySame typ, StaticIdentity typ, MultiplySameExtra typ xl, MultiplySameExtra typ xu, StaticIdentityExtra typ xl, StaticIdentityStrip typ lower, StaticIdentityExtra typ xu, StaticIdentityStrip typ upper, PowerStrip lower, PowerStrip upper, meas ~ Shape, vert ~ Small, horiz ~ Small, Static height, Eq height, height ~ width, Floating a) => Monoid (Matrix typ xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

mempty :: Matrix typ xl xu lower upper meas vert horiz height width a #

mappend :: Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a #

mconcat :: [Matrix typ xl xu lower upper meas vert horiz height width a] -> Matrix typ xl xu lower upper meas vert horiz height width a #

(MultiplySame typ, MultiplySameExtra typ xl, MultiplySameExtra typ xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C height, Eq height, height ~ width, Floating a) => Semigroup (Matrix typ xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

(<>) :: Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a #

sconcat :: NonEmpty (Matrix typ xl xu lower upper meas vert horiz height width a) -> Matrix typ xl xu lower upper meas vert horiz height width a #

stimes :: Integral b => b -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a #

(Measure meas, C vert, C horiz, C height, C width, Storable a, Show height, Show width, Show a) => Show (Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Methods

showsPrec :: Int -> Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a] -> ShowS #

(Show (Matrix typ0 (Append0 xl) (Append0 xu) lower upper meas vert horiz (AppendSelectShape xl height sh0) (AppendSelectShape xu width sh0) a), Show (Matrix typ1 (Append1 xl) (Append1 xu) lower upper meas vert horiz (AppendSelectShape xl height sh1) (AppendSelectShape xu width sh1) a), C height, C width, Show height, Show width, Show a) => Show (Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

showsPrec :: Int -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a] -> ShowS #

(Show (Quadratic typ0 (Diagonal0 xl) (Diagonal0 xu) lower upper (ShapeHead height) a), Show (Quadratic typ1 (Diagonal1 xl) (Diagonal1 xu) lower upper (ShapeTail height) a), C height, C width, Show height, Show width, Show a) => Show (Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

showsPrec :: Int -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a] -> ShowS #

(Show (Quadratic typ00 (Square00 xl) (Square00 xu) Filled Filled (ShapeHead height) a), Show (Quadratic typ11 (Square11 xl) (Square11 xu) Filled Filled (ShapeTail height) a), Show (Matrix (SquareType xu) (Square01 xu) (Square10 xu) Filled Filled measOff vertOff horizOff (ShapeHead height) (ShapeTail width) a), Show (Matrix (SquareType xl) (Square10 xl) (Square01 xl) Filled Filled measOff horizOff vertOff (ShapeTail height) (ShapeHead width) a), C height, C width, Show height, Show width, Show a) => Show (Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

showsPrec :: Int -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a] -> ShowS #

(Show (Quadratic typ0 (Symmetric0 xl) (Symmetric0 xu) lower upper (ShapeHead height) a), Show (Quadratic typ1 (Symmetric1 xl) (Symmetric1 xu) lower upper (ShapeTail height) a), Show (Matrix typOff xlOff xuOff Filled Filled Size Big Big (ShapeHead height) (ShapeTail height) a), C height, C width, Show height, Show width, Show a) => Show (Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

showsPrec :: Int -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a] -> ShowS #

(Show (Quadratic typ0 (Triangular0 xl) (Triangular0 xu) lower upper (ShapeHead height) a), Show (Quadratic typ1 (Triangular1 xl) (Triangular1 xu) lower upper (ShapeTail height) a), Show (Matrix typOff (TriangularOff xl) (TriangularOff xu) Filled Filled Size Big Big (TriangularFstShape xl xu height) (TriangularSndShape xl xu height) a), C height, C width, Show height, Show width, Show a) => Show (Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

showsPrec :: Int -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a] -> ShowS #

(C height, Show height) => Show (Matrix Permutation xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

showsPrec :: Int -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix Permutation xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix Permutation xl xu lower upper meas vert horiz height width a] -> ShowS #

(C height, Show height, Show a) => Show (Matrix Scale xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

showsPrec :: Int -> Matrix Scale xl xu lower upper meas vert horiz height width a -> ShowS #

show :: Matrix Scale xl xu lower upper meas vert horiz height width a -> String #

showList :: [Matrix Scale xl xu lower upper meas vert horiz height width a] -> ShowS #

(NFData typ, Measure meas, C vert, C horiz, NFData height, NFData width, NFData a) => NFData (Matrix typ xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

rnf :: Matrix typ xl xu lower upper meas vert horiz height width a -> () #

(C height, Eq height) => Eq (Matrix Permutation xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

(==) :: Matrix Permutation xl xu lower upper meas vert horiz height width a -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> Bool #

(/=) :: Matrix Permutation xl xu lower upper meas vert horiz height width a -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> Bool #

(Format typ, FormatExtra typ xl, FormatExtra typ xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Display (Matrix typ xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

display :: Matrix typ xl xu lower upper meas vert horiz height width a -> Graphic #

displayIO :: Matrix typ xl xu lower upper meas vert horiz height width a -> IO Graphic #

(Format typ, FormatExtra typ xl, FormatExtra typ xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Format (Matrix typ xl xu lower upper meas vert horiz height width a) Source # 
Instance details

Defined in Numeric.LAPACK.Format

Methods

format :: Output out => Config -> Matrix typ xl xu lower upper meas vert horiz height width a -> out Source #

data Matrix Identity xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

data Matrix Identity xl xu lower upper meas vert horiz height width a where
data Matrix Permutation xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

data Matrix Permutation xl xu lower upper meas vert horiz height width a where
data Matrix Scale xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

data Matrix Scale xl xu lower upper meas vert horiz height width a where
data Matrix (Inverse typ) extraLower extraUpper lowerf upperf meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

data Matrix (Inverse typ) extraLower extraUpper lowerf upperf meas vert horiz height width a where
  • Inverse :: forall typ xl xu upperf lowerf meas width height a. QuadraticMeas typ xl xu upperf lowerf meas width height a -> Matrix (Inverse typ) (xl, lowerf) (xu, upperf) lowerf upperf meas Small Small height width a
data Matrix (Product fuse) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

data Matrix (Product fuse) xl xu lower upper meas vert horiz height width a where
  • Product :: forall lowerA lowerB lower upperA upperB upper typA xlA xuA meas vert horiz height fuse a typB xlB xuB width. (MultipliedBands lowerA lowerB ~ lower, MultipliedBands lowerB lowerA ~ lower, MultipliedBands upperA upperB ~ upper, MultipliedBands upperB upperA ~ upper) => Matrix typA xlA xuA lowerA upperA meas vert horiz height fuse a -> Matrix typB xlB xuB lowerB upperB meas vert horiz fuse width a -> Matrix (Product fuse) (typA, xlA, xuA, lowerA, upperA) (typB, xuB, xlB, upperB, lowerB) lower upper meas vert horiz height width a
data Matrix (FillStrips typ) extraLower extraUpper lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

data Matrix (FillStrips typ) extraLower extraUpper lower upper meas vert horiz height width a where
data Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

data Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a where
  • Array :: forall pack prop lower upper meas vert horiz height width a. OmniArray pack prop lower upper meas vert horiz height width a -> Matrix (Array pack prop) () () lower upper meas vert horiz height width a
data Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

data Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a where
data Matrix (MapExtent typ meas) extraLower extraUpper lower upper meas1 vert1 horiz1 height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

data Matrix (MapExtent typ meas) extraLower extraUpper lower upper meas1 vert1 horiz1 height width a where
  • MapExtent :: forall vert0 horiz0 meas meas1 vert1 horiz1 height width typ xl xu lower upper a. (C vert0, C horiz0) => Map meas vert0 horiz0 meas1 vert1 horiz1 height width -> Matrix typ xl xu lower upper meas vert0 horiz0 height width a -> Matrix (MapExtent typ meas) (xl, vert0) (xu, horiz0) lower upper meas1 vert1 horiz1 height width a
data Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

data Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a where
data Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

data Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a where
data Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

data Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a where
data Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

data Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a where

type Full meas vert horiz height width = UnpackedMatrix Arbitrary Filled Filled meas vert horiz height width Source #

type General height width = Full Size Big Big height width Source #

type Tall height width = Full Size Big Small height width Source #

type Wide height width = Full Size Small Big height width Source #

type Square sh = SquareMeas Shape sh sh Source #

type LiberalSquare height width = SquareMeas Size height width Source #

type Quadratic typ extraLower extraUpper lower upper sh = QuadraticMeas typ extraLower extraUpper lower upper Shape sh sh Source #

type Triangular lo diag up sh = TriangularP Packed lo diag up sh Source #

type Symmetric sh = SymmetricP Packed sh Source #

type Hermitian sh = HermitianP Packed sh Source #

type HermitianPosDef sh = HermitianPosDefP Packed sh Source #

type HermitianPosSemidef sh = HermitianPosSemidefP Packed sh Source #

type FlexHermitian neg zero pos sh = FlexHermitianP Packed neg zero pos sh Source #

The definiteness tags mean:

  • neg == False: There is no x with x^T * A * x < 0.
  • zero == False: There is no x with x^T * A * x = 0.
  • pos == False: There is no x with x^T * A * x > 0.

If a tag is True then this imposes no further restriction on the matrix.

type FlexDiagonal diag size = SymmQuadratic diag U0 size Source #

type RectangularDiagonal meas vert horiz height width = Banded U0 U0 meas vert horiz height width Source #

type Banded sub super meas vert horiz height width = FlexBanded Arbitrary sub super meas vert horiz height width Source #

type BandedHermitian offDiag sh = Hermitian offDiag sh Source #

type Permutation sh = FlexPermutation Filled Filled sh Source #

class Format typ where Source #

Methods

format :: (FormatExtra typ xl, FormatExtra typ xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix typ xl xu lower upper meas vert horiz height width a -> out Source #

Instances

Instances details
Format Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type FormatExtra Permutation extra Source #

Methods

format :: (FormatExtra Permutation xl, FormatExtra Permutation xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> out Source #

Format Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type FormatExtra Scale extra Source #

Methods

format :: (FormatExtra Scale xl, FormatExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix Scale xl xu lower upper meas vert horiz height width a -> out Source #

Format typ => Format (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type FormatExtra (FillStrips typ) extra Source #

Methods

format :: (FormatExtra (FillStrips typ) xl, FormatExtra (FillStrips typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> out Source #

Format (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Associated Types

type FormatExtra (Array pack property) extra Source #

Methods

format :: (FormatExtra (Array pack property) xl, FormatExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> out Source #

(Layout typ0, Layout typ1) => Format (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type FormatExtra (Diagonal typ0 typ1) extra Source #

Methods

format :: (FormatExtra (Diagonal typ0 typ1) xl, FormatExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> out Source #

(Format typ, Measure meas) => Format (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type FormatExtra (MapExtent typ meas) extra Source #

Methods

format :: (FormatExtra (MapExtent typ meas) xl, FormatExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> out Source #

(Layout typ0, Layout typOff, Layout typ1) => Format (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type FormatExtra (Triangular typ0 typOff typ1) extra Source #

Methods

format :: (FormatExtra (Triangular typ0 typOff typ1) xl, FormatExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> out Source #

(Layout typ0, Layout typ1) => Format (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type FormatExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

format :: (FormatExtra (Append typ0 typ1 sh0 sh1) xl, FormatExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> out Source #

(Layout typ00, Layout typ11) => Format (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type FormatExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

format :: (FormatExtra (Square typ00 measOff vertOff horizOff typ11) xl, FormatExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> out Source #

(BoxExtra typOff xlOff, BoxExtra typOff xuOff, Layout typ0, Layout typ1, Layout typOff, LayoutExtra typOff xlOff, LayoutExtra typOff xuOff) => Format (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type FormatExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

format :: (FormatExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, FormatExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> out Source #

type family FormatExtra typ extra :: Constraint Source #

Instances

Instances details
type FormatExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type FormatExtra Permutation extra = ()
type FormatExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type FormatExtra Scale extra = ()
type FormatExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type FormatExtra (FillStrips typ) extra
type FormatExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

type FormatExtra (Array pack property) extra = ()
type FormatExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type FormatExtra (Diagonal typ0 typ1) extra
type FormatExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type FormatExtra (MapExtent typ meas) extra
type FormatExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type FormatExtra (Triangular typ0 typOff typ1) extra
type FormatExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type FormatExtra (Append typ0 typ1 sh0 sh1) extra
type FormatExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type FormatExtra (Square typ00 measOff vertOff horizOff typ11) extra
type FormatExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type FormatExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

formatWithLayout :: (Layout typ, LayoutExtra typ xl, LayoutExtra typ xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix typ xl xu lower upper meas vert horiz height width a -> out Source #

Default implementation of format. Some matrices need more than one array for display, e.g. Householder and LowerUpper. Layout class is still needed for Block matrices.

class Box typ => Layout typ where Source #

Layout matrix elements for use in formatting a block matrix. Optimally its implementation is reused in format via formatWithLayout, but sometimes that is not possible.

Methods

layout :: (LayoutExtra typ xl, LayoutExtra typ xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

Instances

Instances details
Layout Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type LayoutExtra Permutation extra Source #

Methods

layout :: (LayoutExtra Permutation xl, LayoutExtra Permutation xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

Layout Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type LayoutExtra Scale extra Source #

Methods

layout :: (LayoutExtra Scale xl, LayoutExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

Layout typ => Layout (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type LayoutExtra (FillStrips typ) extra Source #

Methods

layout :: (LayoutExtra (FillStrips typ) xl, LayoutExtra (FillStrips typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

Layout (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Associated Types

type LayoutExtra (Array pack property) extra Source #

Methods

layout :: (LayoutExtra (Array pack property) xl, LayoutExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Array0 (height, width) (Separator, Maybe (Style, a)) Source #

(Layout typ0, Layout typ1) => Layout (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type LayoutExtra (Diagonal typ0 typ1) extra Source #

Methods

layout :: (LayoutExtra (Diagonal typ0 typ1) xl, LayoutExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

(Layout typ, Measure meas) => Layout (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type LayoutExtra (MapExtent typ meas) extra Source #

Methods

layout :: (LayoutExtra (MapExtent typ meas) xl, LayoutExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz, C height, C width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

(Layout typ0, Layout typOff, Layout typ1) => Layout (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type LayoutExtra (Triangular typ0 typOff typ1) extra Source #

Methods

layout :: (LayoutExtra (Triangular typ0 typOff typ1) xl, LayoutExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

(Layout typ0, Layout typ1) => Layout (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type LayoutExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

layout :: (LayoutExtra (Append typ0 typ1 sh0 sh1) xl, LayoutExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

(Layout typ00, Layout typ11) => Layout (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type LayoutExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

layout :: (LayoutExtra (Square typ00 measOff vertOff horizOff typ11) xl, LayoutExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

(BoxExtra typOff xlOff, BoxExtra typOff xuOff, Layout typ0, Layout typ1, Layout typOff, LayoutExtra typOff xlOff, LayoutExtra typOff xuOff) => Layout (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type LayoutExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

layout :: (LayoutExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, LayoutExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source #

type family LayoutExtra typ extra :: Constraint Source #

Instances

Instances details
type LayoutExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type LayoutExtra Permutation extra = ()
type LayoutExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type LayoutExtra Scale extra = ()
type LayoutExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type LayoutExtra (FillStrips typ) extra
type LayoutExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

type LayoutExtra (Array pack property) extra = ()
type LayoutExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Diagonal typ0 typ1) extra
type LayoutExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type LayoutExtra (MapExtent typ meas) extra
type LayoutExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Triangular typ0 typOff typ1) extra
type LayoutExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Append typ0 typ1 sh0 sh1) extra
type LayoutExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Square typ00 measOff vertOff horizOff typ11) extra
type LayoutExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

class Box typ => Transpose typ Source #

Minimal complete definition

transpose

Instances

Instances details
Transpose Identity Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type TransposeExtra Identity extra Source #

Methods

transpose :: (TransposeExtra Identity xl, TransposeExtra Identity xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Identity xl xu lower upper meas vert horiz height width a -> Matrix Identity xu xl upper lower meas horiz vert width height a Source #

Transpose Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type TransposeExtra Permutation extra Source #

Methods

transpose :: (TransposeExtra Permutation xl, TransposeExtra Permutation xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Matrix Permutation xu xl upper lower meas horiz vert width height a Source #

Transpose Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type TransposeExtra Scale extra Source #

Methods

transpose :: (TransposeExtra Scale xl, TransposeExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xu xl upper lower meas horiz vert width height a Source #

Transpose typ => Transpose (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type TransposeExtra (Inverse typ) extra Source #

Methods

transpose :: (TransposeExtra (Inverse typ) xl, TransposeExtra (Inverse typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Matrix (Inverse typ) xu xl upper lower meas horiz vert width height a Source #

(C fuse, Eq fuse) => Transpose (Product fuse) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type TransposeExtra (Product fuse) extra Source #

Methods

transpose :: (TransposeExtra (Product fuse) xl, TransposeExtra (Product fuse) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> Matrix (Product fuse) xu xl upper lower meas horiz vert width height a Source #

Transpose typ => Transpose (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type TransposeExtra (FillStrips typ) extra Source #

Methods

transpose :: (TransposeExtra (FillStrips typ) xl, TransposeExtra (FillStrips typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Matrix (FillStrips typ) xu xl upper lower meas horiz vert width height a Source #

Transpose (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Associated Types

type TransposeExtra (Array pack property) extra Source #

Methods

transpose :: (TransposeExtra (Array pack property) xl, TransposeExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xu xl upper lower meas horiz vert width height a Source #

(Transpose typ0, Transpose typ1) => Transpose (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type TransposeExtra (Diagonal typ0 typ1) extra Source #

Methods

transpose :: (TransposeExtra (Diagonal typ0 typ1) xl, TransposeExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xu xl upper lower meas horiz vert width height a Source #

(Transpose typ, Measure meas) => Transpose (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type TransposeExtra (MapExtent typ meas) extra Source #

Methods

transpose :: (TransposeExtra (MapExtent typ meas) xl, TransposeExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz, C height, C width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Matrix (MapExtent typ meas) xu xl upper lower meas0 horiz vert width height a Source #

(Transpose typ0, Transpose typOff, Transpose typ1) => Transpose (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type TransposeExtra (Triangular typ0 typOff typ1) extra Source #

Methods

transpose :: (TransposeExtra (Triangular typ0 typOff typ1) xl, TransposeExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xu xl upper lower meas horiz vert width height a Source #

(Transpose typ0, Transpose typ1) => Transpose (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type TransposeExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

transpose :: (TransposeExtra (Append typ0 typ1 sh0 sh1) xl, TransposeExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xu xl upper lower meas horiz vert width height a Source #

(Transpose typ00, Transpose typ11) => Transpose (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type TransposeExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

transpose :: (TransposeExtra (Square typ00 measOff vertOff horizOff typ11) xl, TransposeExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xu xl upper lower meas horiz vert width height a Source #

(Transpose typ0, Transpose typ1, Transpose typOff, BoxExtra typOff xlOff, BoxExtra typOff xuOff, TransposeExtra typOff xlOff, TransposeExtra typOff xuOff) => Transpose (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type TransposeExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

transpose :: (TransposeExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, TransposeExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xu xl upper lower meas horiz vert width height a Source #

type family TransposeExtra typ extra :: Constraint Source #

Instances

Instances details
type TransposeExtra Identity extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type TransposeExtra Identity extra = ()
type TransposeExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type TransposeExtra Permutation extra = ()
type TransposeExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type TransposeExtra Scale extra = ()
type TransposeExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type TransposeExtra (Inverse typ) extra
type TransposeExtra (Product fuse) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type TransposeExtra (Product fuse) extra
type TransposeExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type TransposeExtra (FillStrips typ) extra
type TransposeExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

type TransposeExtra (Array pack property) extra = extra ~ ()
type TransposeExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type TransposeExtra (Diagonal typ0 typ1) extra
type TransposeExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type TransposeExtra (MapExtent typ meas) extra
type TransposeExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type TransposeExtra (Triangular typ0 typOff typ1) extra
type TransposeExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type TransposeExtra (Append typ0 typ1 sh0 sh1) extra
type TransposeExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type TransposeExtra (Square typ00 measOff vertOff horizOff typ11) extra
type TransposeExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type TransposeExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

transpose :: (Transpose typ, TransposeExtra typ xl, TransposeExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xu xl upper lower meas horiz vert width height a Source #

adjoint :: (Transpose typ, Complex typ) => (TransposeExtra typ xl, TransposeExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xu xl upper lower meas horiz vert width height a Source #

height :: (Box typ, BoxExtra typ xl, BoxExtra typ xu) => (Measure meas, C vert, C horiz) => Matrix typ xl xu lower upper meas vert horiz height width a -> height Source #

width :: (Box typ, BoxExtra typ xl, BoxExtra typ xu) => (Measure meas, C vert, C horiz) => Matrix typ xl xu lower upper meas vert horiz height width a -> width Source #

extent :: (Box typ, BoxExtra typ xl, BoxExtra typ xu) => (Measure meas, C vert, C horiz) => Matrix typ xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

class Box typ Source #

Minimal complete definition

extent

Instances

Instances details
Box Identity Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type BoxExtra Identity extra Source #

Methods

extent :: (BoxExtra Identity xl, BoxExtra Identity xu, Measure meas, C vert, C horiz) => Matrix Identity xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra Identity xl, BoxExtra Identity xu, Measure meas, C vert, C horiz) => Matrix Identity xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra Identity xl, BoxExtra Identity xu, Measure meas, C vert, C horiz) => Matrix Identity xl xu lower upper meas vert horiz height width a -> width Source #

Box Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type BoxExtra Permutation extra Source #

Methods

extent :: (BoxExtra Permutation xl, BoxExtra Permutation xu, Measure meas, C vert, C horiz) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra Permutation xl, BoxExtra Permutation xu, Measure meas, C vert, C horiz) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra Permutation xl, BoxExtra Permutation xu, Measure meas, C vert, C horiz) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> width Source #

Box Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type BoxExtra Scale extra Source #

Methods

extent :: (BoxExtra Scale xl, BoxExtra Scale xu, Measure meas, C vert, C horiz) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra Scale xl, BoxExtra Scale xu, Measure meas, C vert, C horiz) => Matrix Scale xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra Scale xl, BoxExtra Scale xu, Measure meas, C vert, C horiz) => Matrix Scale xl xu lower upper meas vert horiz height width a -> width Source #

Box typ => Box (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type BoxExtra (Inverse typ) extra Source #

Methods

extent :: (BoxExtra (Inverse typ) xl, BoxExtra (Inverse typ) xu, Measure meas, C vert, C horiz) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Inverse typ) xl, BoxExtra (Inverse typ) xu, Measure meas, C vert, C horiz) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Inverse typ) xl, BoxExtra (Inverse typ) xu, Measure meas, C vert, C horiz) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> width Source #

Eq fuse => Box (Product fuse) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type BoxExtra (Product fuse) extra Source #

Methods

extent :: (BoxExtra (Product fuse) xl, BoxExtra (Product fuse) xu, Measure meas, C vert, C horiz) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Product fuse) xl, BoxExtra (Product fuse) xu, Measure meas, C vert, C horiz) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Product fuse) xl, BoxExtra (Product fuse) xu, Measure meas, C vert, C horiz) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> width Source #

Box typ => Box (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type BoxExtra (FillStrips typ) extra Source #

Methods

extent :: (BoxExtra (FillStrips typ) xl, BoxExtra (FillStrips typ) xu, Measure meas, C vert, C horiz) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (FillStrips typ) xl, BoxExtra (FillStrips typ) xu, Measure meas, C vert, C horiz) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (FillStrips typ) xl, BoxExtra (FillStrips typ) xu, Measure meas, C vert, C horiz) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> width Source #

Box (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Associated Types

type BoxExtra (Array pack property) extra Source #

Methods

extent :: (BoxExtra (Array pack property) xl, BoxExtra (Array pack property) xu, Measure meas, C vert, C horiz) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Array pack property) xl, BoxExtra (Array pack property) xu, Measure meas, C vert, C horiz) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Array pack property) xl, BoxExtra (Array pack property) xu, Measure meas, C vert, C horiz) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> width Source #

(Box typ0, Box typ1) => Box (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type BoxExtra (Diagonal typ0 typ1) extra Source #

Methods

extent :: (BoxExtra (Diagonal typ0 typ1) xl, BoxExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Diagonal typ0 typ1) xl, BoxExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Diagonal typ0 typ1) xl, BoxExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> width Source #

(Box typ, Measure meas) => Box (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type BoxExtra (MapExtent typ meas) extra Source #

Methods

extent :: (BoxExtra (MapExtent typ meas) xl, BoxExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Extent meas0 vert horiz height width Source #

height :: (BoxExtra (MapExtent typ meas) xl, BoxExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> height Source #

width :: (BoxExtra (MapExtent typ meas) xl, BoxExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> width Source #

(Box typ0, Box typOff, Box typ1) => Box (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type BoxExtra (Triangular typ0 typOff typ1) extra Source #

Methods

extent :: (BoxExtra (Triangular typ0 typOff typ1) xl, BoxExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Triangular typ0 typOff typ1) xl, BoxExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Triangular typ0 typOff typ1) xl, BoxExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> width Source #

(Box typ0, Box typ1) => Box (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type BoxExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

extent :: (BoxExtra (Append typ0 typ1 sh0 sh1) xl, BoxExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Append typ0 typ1 sh0 sh1) xl, BoxExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Append typ0 typ1 sh0 sh1) xl, BoxExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> width Source #

(Box typ00, Box typ11) => Box (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type BoxExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

extent :: (BoxExtra (Square typ00 measOff vertOff horizOff typ11) xl, BoxExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Square typ00 measOff vertOff horizOff typ11) xl, BoxExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Square typ00 measOff vertOff horizOff typ11) xl, BoxExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> width Source #

(Box typ0, Box typ1, Box typOff, BoxExtra typOff xlOff, BoxExtra typOff xuOff) => Box (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

extent :: (BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source #

height :: (BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> height Source #

width :: (BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> width Source #

type family BoxExtra typ extra :: Constraint Source #

Instances

Instances details
type BoxExtra Identity extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type BoxExtra Identity extra = ()
type BoxExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type BoxExtra Permutation extra = ()
type BoxExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type BoxExtra Scale extra = ()
type BoxExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type BoxExtra (Inverse typ) extra
type BoxExtra (Product fuse) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type BoxExtra (Product fuse) extra
type BoxExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type BoxExtra (FillStrips typ) extra
type BoxExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

type BoxExtra (Array pack property) extra = extra ~ ()
type BoxExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Diagonal typ0 typ1) extra
type BoxExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type BoxExtra (MapExtent typ meas) extra
type BoxExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Triangular typ0 typOff typ1) extra
type BoxExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Append typ0 typ1 sh0 sh1) extra
type BoxExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Square typ00 measOff vertOff horizOff typ11) extra
type BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

indices :: (Box typ, BoxExtra typ xl, BoxExtra typ xu, Measure meas, C vert, C horiz) => (Indexed height, Indexed width) => Matrix typ xl xu lower upper meas vert horiz height width a -> [(Index height, Index width)] Source #

reshape :: (Measure measA, C vertA, C horizA) => (Measure measB, C vertB, C horizB) => (C heightA, C widthA) => (C heightB, C widthB) => Omni packB propB lowerB upperB measB vertB horizB heightB widthB -> ArrayMatrix packA propA lowerA upperA measA vertA horizA heightA widthA a -> ArrayMatrix packB propB lowerB upperB measB vertB horizB heightB widthB a Source #

mapShape :: (Measure measA, C vertA, C horizA) => (Measure measB, C vertB, C horizB) => (C heightA, C widthA) => (C heightB, C widthB) => (Omni packA propA lowerA upperA measA vertA horizA heightA widthA -> Omni packB propB lowerB upperB measB vertB horizB heightB widthB) -> ArrayMatrix packA propA lowerA upperA measA vertA horizA heightA widthA a -> ArrayMatrix packB propB lowerB upperB measB vertB horizB heightB widthB a Source #

caseTallWide :: (Measure meas, C vert, C horiz, C height, C width) => Full meas vert horiz height width a -> Either (Tall height width a) (Wide height width a) Source #

Square matrices will be classified as Tall.

fromScalar :: Storable a => a -> General () () a Source #

toScalar :: Storable a => General () () a -> a Source #

fromList :: (C height, C width, Storable a) => height -> width -> [a] -> General height width a Source #

class Unpack typ Source #

Minimal complete definition

unpack

Instances

Instances details
Unpack Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type UnpackExtra Permutation extra Source #

Methods

unpack :: (UnpackExtra Permutation xl, UnpackExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

Unpack Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type UnpackExtra Scale extra Source #

Methods

unpack :: (UnpackExtra Scale xl, UnpackExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

Unpack typ => Unpack (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type UnpackExtra (FillStrips typ) extra Source #

Methods

unpack :: (UnpackExtra (FillStrips typ) xl, UnpackExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

Property prop => Unpack (Array pack prop) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type UnpackExtra (Array pack prop) extra Source #

Methods

unpack :: (UnpackExtra (Array pack prop) xl, UnpackExtra (Array pack prop) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Array pack prop) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

(Unpack typ0, Unpack typ1) => Unpack (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type UnpackExtra (Diagonal typ0 typ1) extra Source #

Methods

unpack :: (UnpackExtra (Diagonal typ0 typ1) xl, UnpackExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

(Unpack typ, Measure meas) => Unpack (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type UnpackExtra (MapExtent typ meas) extra Source #

Methods

unpack :: (UnpackExtra (MapExtent typ meas) xl, UnpackExtra (MapExtent typ meas) xu, Strip lower, Strip upper, Measure meas0, C vert, C horiz, C height, C width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas0 vert horiz height width a Source #

(Unpack typ0, Unpack typOff, Unpack typ1) => Unpack (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type UnpackExtra (Triangular typ0 typOff typ1) extra Source #

Methods

unpack :: (UnpackExtra (Triangular typ0 typOff typ1) xl, UnpackExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

(Unpack typ0, Unpack typ1) => Unpack (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type UnpackExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

unpack :: (UnpackExtra (Append typ0 typ1 sh0 sh1) xl, UnpackExtra (Append typ0 typ1 sh0 sh1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

(Unpack typ00, Unpack typ11) => Unpack (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type UnpackExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

unpack :: (UnpackExtra (Square typ00 measOff vertOff horizOff typ11) xl, UnpackExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

(Unpack typ0, Unpack typOff, Unpack typ1, UnpackExtra typOff xlOff, UnpackExtra typOff xuOff) => Unpack (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type UnpackExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

unpack :: (UnpackExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, UnpackExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

type family UnpackExtra typ extra :: Constraint Source #

Instances

Instances details
type UnpackExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type UnpackExtra Permutation extra = extra ~ ()
type UnpackExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type UnpackExtra Scale extra = extra ~ ()
type UnpackExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type UnpackExtra (FillStrips typ) extra
type UnpackExtra (Array pack prop) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type UnpackExtra (Array pack prop) extra = extra ~ ()
type UnpackExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type UnpackExtra (Diagonal typ0 typ1) extra
type UnpackExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type UnpackExtra (MapExtent typ meas) extra
type UnpackExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type UnpackExtra (Triangular typ0 typOff typ1) extra
type UnpackExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type UnpackExtra (Append typ0 typ1 sh0 sh1) extra
type UnpackExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type UnpackExtra (Square typ00 measOff vertOff horizOff typ11) extra
type UnpackExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type UnpackExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

toFull :: (Unpack typ, UnpackExtra typ xl, UnpackExtra typ xu) => (Strip lower, Strip upper) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Full meas vert horiz height width a Source #

unpack :: (Unpack typ, UnpackExtra typ xl, UnpackExtra typ xu) => (Strip lower, Strip upper) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source #

mapExtent :: (MapExtent typ, MapExtentExtra typ xl, MapExtentStrip typ lower) => (MapExtentExtra typ xu, MapExtentStrip typ upper) => (Measure measA, C vertA, C horizA) => (Measure measB, C vertB, C horizB) => Map measA vertA horizA measB vertB horizB height width -> Matrix typ xl xu lower upper measA vertA horizA height width a -> Matrix typ xl xu lower upper measB vertB horizB height width a Source #

fromFull :: (Measure meas, C vert, C horiz) => Full meas vert horiz height width a -> General height width a Source #

asGeneral :: Id (General height width a) Source #

asTall :: Id (Tall height width a) Source #

asWide :: Id (Wide height width a) Source #

tallFromGeneral :: (C height, C width, Storable a) => General height width a -> Tall height width a Source #

wideFromGeneral :: (C height, C width, Storable a) => General height width a -> Wide height width a Source #

generalizeTall :: (Measure meas, C vert, C horiz) => Full meas vert Small height width a -> Full Size vert horiz height width a Source #

generalizeWide :: (Measure meas, C vert, C horiz) => Full meas Small horiz height width a -> Full Size vert horiz height width a Source #

class SquareShape typ => MapSquareSize typ Source #

Minimal complete definition

mapSquareSize

Instances

Instances details
MapSquareSize Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

mapSquareSize :: (C shA, C shB) => (shA -> shB) -> Quadratic Permutation xl xu lower upper shA a -> Quadratic Permutation xl xu lower upper shB a Source #

MapSquareSize Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

mapSquareSize :: (C shA, C shB) => (shA -> shB) -> Quadratic Scale xl xu lower upper shA a -> Quadratic Scale xl xu lower upper shB a Source #

MapSquareSize (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

mapSquareSize :: (C shA, C shB) => (shA -> shB) -> Quadratic (Array pack property) xl xu lower upper shA a -> Quadratic (Array pack property) xl xu lower upper shB a Source #

class Box typ => MapSize typ Source #

Minimal complete definition

mapHeight, mapWidth

Instances

Instances details
MapSize (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

mapHeight :: (C vert, C horiz, C heightA, C heightB, C width) => (heightA -> heightB) -> Matrix (Array pack property) extraLower extraUpper lower upper Size vert horiz heightA width a -> Matrix (Array pack property) extraLower extraUpper lower upper Size vert horiz heightB width a Source #

mapWidth :: (C vert, C horiz, C height, C widthA, C widthB) => (widthA -> widthB) -> Matrix (Array pack property) extraLower extraUpper lower upper Size vert horiz height widthA a -> Matrix (Array pack property) extraLower extraUpper lower upper Size vert horiz height widthB a Source #

mapHeight :: (MapSize typ, C vert, C horiz, C heightA, C heightB, C width) => (heightA -> heightB) -> Matrix typ extraLower extraUpper lower upper Size vert horiz heightA width a -> Matrix typ extraLower extraUpper lower upper Size vert horiz heightB width a Source #

The number of rows and columns must be maintained by the shape mapping function.

mapWidth :: (MapSize typ, C vert, C horiz, C height, C widthA, C widthB) => (widthA -> widthB) -> Matrix typ extraLower extraUpper lower upper Size vert horiz height widthA a -> Matrix typ extraLower extraUpper lower upper Size vert horiz height widthB a Source #

mapSquareSize :: (MapSquareSize typ, C shA, C shB) => (shA -> shB) -> Quadratic typ xl xu lower upper shA a -> Quadratic typ xl xu lower upper shB a Source #

The number of rows and columns must be maintained by the shape mapping function.

Not available for Block matrices.

identity :: (Quadratic pack property lower upper, C sh, Floating a) => Order -> sh -> Quadratic pack property lower upper sh a Source #

diagonal :: (Diagonal property, Quadratic pack property lower upper, C sh, Floating a) => Order -> Vector sh a -> Quadratic pack property lower upper sh a Source #

fromRowsNonEmpty :: (C width, Eq width, Storable a) => T [] (Vector width a) -> General ShapeInt width a Source #

fromRowArray :: (C height, C width, Eq width, Storable a) => width -> Array height (Vector width a) -> General height width a Source #

fromRows :: (C width, Eq width, Storable a) => width -> [Vector width a] -> General ShapeInt width a Source #

fromRowsNonEmptyContainer :: (f ~ T g, C g, C width, Eq width, Storable a) => f (Vector width a) -> General (Shape f) width a Source #

fromRowContainer :: (C f, C width, Eq width, Storable a) => width -> f (Vector width a) -> General (Shape f) width a Source #

fromColumnsNonEmpty :: (C height, Eq height, Storable a) => T [] (Vector height a) -> General height ShapeInt a Source #

fromColumnArray :: (C height, Eq height, C width, Storable a) => height -> Array width (Vector height a) -> General height width a Source #

fromColumns :: (C height, Eq height, Storable a) => height -> [Vector height a] -> General height ShapeInt a Source #

fromColumnsNonEmptyContainer :: (f ~ T g, C g, C height, Eq height, Storable a) => f (Vector height a) -> General height (Shape f) a Source #

fromColumnContainer :: (C f, C height, Eq height, Storable a) => height -> f (Vector height a) -> General height (Shape f) a Source #

singleRow :: Order -> Vector width a -> General () width a Source #

singleColumn :: Order -> Vector height a -> General height () a Source #

flattenRow :: General () width a -> Vector width a Source #

flattenColumn :: General height () a -> Vector height a Source #

liftRow :: Order -> (Vector height0 a -> Vector height1 b) -> General () height0 a -> General () height1 b Source #

liftColumn :: Order -> (Vector height0 a -> Vector height1 b) -> General height0 () a -> General height1 () b Source #

unliftRow :: Order -> (General () height0 a -> General () height1 b) -> Vector height0 a -> Vector height1 b Source #

unliftColumn :: Order -> (General height0 () a -> General height1 () b) -> Vector height0 a -> Vector height1 b Source #

toRows :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> [Vector width a] Source #

toColumns :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> [Vector height a] Source #

toRowArray :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> Array height (Vector width a) Source #

toColumnArray :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> Array width (Vector height a) Source #

toRowContainer :: (Measure meas, C vert, C horiz, C f, C width, Floating a) => Full meas vert horiz (Shape f) width a -> f (Vector width a) Source #

toColumnContainer :: (Measure meas, C vert, C horiz, C height, C f, Floating a) => Full meas vert horiz height (Shape f) a -> f (Vector height a) Source #

takeRow :: (Measure meas, C vert, C horiz, Indexed height, C width, Index height ~ ix, Floating a) => Full meas vert horiz height width a -> ix -> Vector width a Source #

takeColumn :: (Measure meas, C vert, C horiz, C height, Indexed width, Index width ~ ix, Floating a) => Full meas vert horiz height width a -> ix -> Vector height a Source #

takeRows :: (C vert, C width, Floating a) => Int -> Full Size vert Big ShapeInt width a -> Full Size vert Big ShapeInt width a Source #

takeColumns :: (C horiz, C height, Floating a) => Int -> Full Size Big horiz height ShapeInt a -> Full Size Big horiz height ShapeInt a Source #

takeEqually :: (Measure meas, C vert, C horiz, Floating a) => Int -> Full meas vert horiz ShapeInt ShapeInt a -> Full meas vert horiz ShapeInt ShapeInt a Source #

Take a left-top aligned square or as much as possible of it. The advantange of this function is that it maintains the matrix size relation, e.g. Square remains Square, Tall remains Tall.

dropRows :: (C vert, C width, Floating a) => Int -> Full Size vert Big ShapeInt width a -> Full Size vert Big ShapeInt width a Source #

dropColumns :: (C horiz, C height, Floating a) => Int -> Full Size Big horiz height ShapeInt a -> Full Size Big horiz height ShapeInt a Source #

dropEqually :: (Measure meas, C vert, C horiz, Floating a) => Int -> Full meas vert horiz ShapeInt ShapeInt a -> Full meas vert horiz ShapeInt ShapeInt a Source #

Drop the same number of top-most rows and left-most columns. The advantange of this function is that it maintains the matrix size relation, e.g. Square remains Square, Tall remains Tall.

takeTop :: (C vert, C height0, C height1, C width, Floating a) => Full Size vert Big (height0 ::+ height1) width a -> Full Size vert Big height0 width a Source #

takeBottom :: (C vert, C height0, C height1, C width, Floating a) => Full Size vert Big (height0 ::+ height1) width a -> Full Size vert Big height1 width a Source #

takeLeft :: (C vert, C height, C width0, C width1, Floating a) => Full Size Big vert height (width0 ::+ width1) a -> Full Size Big vert height width0 a Source #

takeRight :: (C vert, C height, C width0, C width1, Floating a) => Full Size Big vert height (width0 ::+ width1) a -> Full Size Big vert height width1 a Source #

takeRowArray :: (Indexed height, C width, C sh, Floating a) => Array sh (Index height) -> General height width a -> General sh width a Source #

The function is optimized for blocks of consecutive rows. For scattered rows in column major order the function has quite ugly memory access patterns.

takeColumnArray :: (C height, Indexed width, C sh, Floating a) => Array sh (Index width) -> General height width a -> General height sh a Source #

swapRows :: (Measure meas, C vert, C horiz, Indexed height, C width, Floating a) => Index height -> Index height -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

swapColumns :: (Measure meas, C vert, C horiz, C height, Indexed width, Floating a) => Index width -> Index width -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

reverseRows :: (Measure meas, C vert, C horiz, Permutable height, C width, Floating a) => Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

reverseColumns :: (Measure meas, C vert, C horiz, C height, Permutable width, Floating a) => Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

fromRowMajor :: (C height, C width, Floating a) => Array (height, width) a -> General height width a Source #

toRowMajor :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> Array (height, width) a Source #

forceOrder :: (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Order -> ArrayMatrix pack property lower upper meas vert horiz height width a -> ArrayMatrix pack property lower upper meas vert horiz height width a Source #

adaptOrder :: (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => ArrayMatrix pack property lower upper meas vert horiz height width a -> ArrayMatrix pack property lower upper meas vert horiz height width a -> ArrayMatrix pack property lower upper meas vert horiz height width a Source #

adaptOrder x y contains the data of y with the layout of x.

leftBias :: OrderBias Source #

Use the element order of the first operand.

rightBias :: OrderBias Source #

Use the element order of the second operand.

contiguousBias :: OrderBias Source #

Choose element order such that, if possible, one part can be copied as one block. For above this means that RowMajor is chosen whenever at least one operand is RowMajor and ColumnMajor is chosen when both operands are ColumnMajor.

(|||) :: (C vertA, C vertB, C vertC, Append vertA vertB ~ vertC, C height, Eq height, C widthA, C widthB, Floating a) => Full Size vertA Big height widthA a -> Full Size vertB Big height widthB a -> Full Size vertC Big height (widthA ::+ widthB) a infixr 3 Source #

beside :: (C vertA, C vertB, C vertC, C height, Eq height, C widthA, C widthB, Floating a) => OrderBias -> AppendMode vertA vertB vertC height widthA widthB -> Full Size vertA Big height widthA a -> Full Size vertB Big height widthB a -> Full Size vertC Big height (widthA ::+ widthB) a Source #

(===) :: (C horizA, C horizB, C horizC, Append horizA horizB ~ horizC, C width, Eq width, C heightA, C heightB, Floating a) => Full Size Big horizA heightA width a -> Full Size Big horizB heightB width a -> Full Size Big horizC (heightA ::+ heightB) width a infixr 2 Source #

above :: (C horizA, C horizB, C horizC, C width, Eq width, C heightA, C heightB, Floating a) => OrderBias -> AppendMode horizA horizB horizC width heightA heightB -> Full Size Big horizA heightA width a -> Full Size Big horizB heightB width a -> Full Size Big horizC (heightA ::+ heightB) width a Source #

stack :: (Measure meas, C vert, C horiz, C heightA, Eq heightA, C heightB, Eq heightB, C widthA, Eq widthA, C widthB, Eq widthB, Floating a) => Full meas vert horiz heightA widthA a -> General heightA widthB a -> General heightB widthA a -> Full meas vert horiz heightB widthB a -> Full meas vert horiz (heightA ::+ heightB) (widthA ::+ widthB) a Source #

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

tensorProduct :: (C height, Eq height, C width, Eq width, Floating a) => Order -> Vector height a -> Vector width a -> General height width a Source #

tensorProduct order x y = singleColumn order x #*# singleRow order y

outer :: (C height, Eq height, C width, Eq width, Floating a) => Order -> Vector height a -> Vector width a -> General height width a Source #

outer order x y = tensorProduct order x (Vector.conjugate y)

kronecker :: (Measure meas, C vert, C horiz, C heightA, C widthA, C heightB, C widthB, Floating a) => Full meas vert horiz heightA widthA a -> Full meas vert horiz heightB widthB a -> Full meas vert horiz (heightA, heightB) (widthA, widthB) a Source #

sumRank1 :: (C height, Eq height, C width, Eq width, Floating a) => (height, width) -> [(a, (Vector height a, Vector width a))] -> General height width a Source #

map :: (Measure meas, C vert, C horiz, C height, C width, Storable a, Storable b) => (a -> b) -> Full meas vert horiz height width a -> Full meas vert horiz height width b Source #

class Complex typ Source #

Minimal complete definition

conjugate, fromReal, toComplex

Instances

Instances details
Complex Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

conjugate :: (Matrix Permutation xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Matrix Permutation xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Matrix Permutation xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

Complex Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

conjugate :: (Matrix Scale xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Matrix Scale xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Matrix Scale xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

Complex typ => Complex (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Methods

conjugate :: (Matrix (Inverse typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Matrix (Inverse typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Matrix (Inverse typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

Complex typ => Complex (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Methods

conjugate :: (Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

Complex (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Methods

conjugate :: (Matrix (Array pack property) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Matrix (Array pack property) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Matrix (Array pack property) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

(Complex typ, Measure meas) => Complex (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Methods

conjugate :: (Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width ~ matrix, Measure meas0, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width ~ matrix, Measure meas0, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width ~ matrix, Measure meas0, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

conjugate :: (Complex typ, Matrix typ xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source #

fromReal :: (Complex typ, Matrix typ xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source #

toComplex :: (Complex typ, Matrix typ xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source #

class Box typ => SquareShape typ Source #

Minimal complete definition

takeDiagonal, identityFrom

Instances

Instances details
SquareShape Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type SquareShapeExtra Permutation extra Source #

Methods

takeDiagonal :: (SquareShapeExtra Permutation xl, SquareShapeExtra Permutation xu, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra Permutation xl, SquareShapeExtra Permutation xu, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Quadratic Permutation xl xu lower upper sh a Source #

SquareShape Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type SquareShapeExtra Scale extra Source #

Methods

takeDiagonal :: (SquareShapeExtra Scale xl, SquareShapeExtra Scale xu, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra Scale xl, SquareShapeExtra Scale xu, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Quadratic Scale xl xu lower upper sh a Source #

SquareShape (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type SquareShapeExtra (Array pack property) extra Source #

Methods

takeDiagonal :: (SquareShapeExtra (Array pack property) xl, SquareShapeExtra (Array pack property) xu, C sh, Floating a) => Quadratic (Array pack property) xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra (Array pack property) xl, SquareShapeExtra (Array pack property) xu, C sh, Floating a) => Quadratic (Array pack property) xl xu lower upper sh a -> Quadratic (Array pack property) xl xu lower upper sh a Source #

(SquareShape typ0, SquareShape typ1) => SquareShape (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SquareShapeExtra (Diagonal typ0 typ1) extra Source #

Methods

takeDiagonal :: (SquareShapeExtra (Diagonal typ0 typ1) xl, SquareShapeExtra (Diagonal typ0 typ1) xu, C sh, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra (Diagonal typ0 typ1) xl, SquareShapeExtra (Diagonal typ0 typ1) xu, C sh, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a Source #

(SquareShape typ0, SquareShape typ1, Box typOff, Homogeneous typOff) => SquareShape (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SquareShapeExtra (Triangular typ0 typOff typ1) extra Source #

Methods

takeDiagonal :: (SquareShapeExtra (Triangular typ0 typOff typ1) xl, SquareShapeExtra (Triangular typ0 typOff typ1) xu, C sh, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra (Triangular typ0 typOff typ1) xl, SquareShapeExtra (Triangular typ0 typOff typ1) xu, C sh, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a Source #

(SquareShape typ00, SquareShape typ11) => SquareShape (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

takeDiagonal :: (SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) xl, SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) xu, C sh, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) xl, SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) xu, C sh, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a Source #

(SquareShape typ0, SquareShape typ1, Box typOff, Homogeneous typOff, BoxExtra typOff xlOff, BoxExtra typOff xuOff, HomogeneousExtra typOff xlOff, HomogeneousExtra typOff xuOff) => SquareShape (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

takeDiagonal :: (SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, C sh, Floating a) => Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper sh a -> Vector sh a Source #

identityFrom :: (SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, C sh, Floating a) => Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper sh a -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper sh a Source #

type family SquareShapeExtra typ extra :: Constraint Source #

Instances

Instances details
type SquareShapeExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type SquareShapeExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type SquareShapeExtra Scale extra = ()
type SquareShapeExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type SquareShapeExtra (Array pack property) extra = ()
type SquareShapeExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SquareShapeExtra (Diagonal typ0 typ1) extra
type SquareShapeExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SquareShapeExtra (Triangular typ0 typOff typ1) extra
type SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SquareShapeExtra (Square typ00 measOff vertOff horizOff typ11) extra
type SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SquareShapeExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

toSquare :: (Unpack typ, UnpackExtra typ xl, UnpackExtra typ xu) => (Strip lower, Strip upper) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Square sh a Source #

identityFromShape :: (C sh, Floating a) => Quadratic pack property lower upper sh -> Quadratic pack property lower upper sh a Source #

identityFrom :: (SquareShape typ, SquareShapeExtra typ xl, SquareShapeExtra typ xu) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Quadratic typ xl xu lower upper sh a Source #

takeDiagonal :: (SquareShape typ, SquareShapeExtra typ xl, SquareShapeExtra typ xu) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Vector sh a Source #

trace :: (SquareShape typ, SquareShapeExtra typ xl, SquareShapeExtra typ xu) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> a Source #

type family RealOf x #

Instances

Instances details
type RealOf Double 
Instance details

Defined in Numeric.BLAS.Scalar

type RealOf Float 
Instance details

Defined in Numeric.BLAS.Scalar

type RealOf (Complex a) 
Instance details

Defined in Numeric.BLAS.Scalar

type RealOf (Complex a) = a

rowSums :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> Vector height a Source #

columnSums :: (Measure meas, C vert, C horiz, C height, C width, Floating a) => Full meas vert horiz height width a -> Vector width a Source #

rowArgAbsMaximums :: (Measure meas, C vert, C horiz, C height, InvIndexed width, Index width ~ ix, Storable ix, Floating a) => Full meas vert horiz height width a -> (Vector height ix, Vector height a) Source #

columnArgAbsMaximums :: (Measure meas, C vert, C horiz, InvIndexed height, C width, Index height ~ ix, Storable ix, Floating a) => Full meas vert horiz height width a -> (Vector width ix, Vector width a) Source #

scaleRows :: (Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Vector height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

scaleColumns :: (Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Vector width a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

scaleRowsReal :: (Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Vector height (RealOf a) -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

scaleColumnsReal :: (Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Vector width (RealOf a) -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

(\*#) :: (Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Vector height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a infixr 7 Source #

(#*\) :: (Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Vector width a -> Full meas vert horiz height width a infixl 7 Source #

(\\#) :: (Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Vector height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a infixr 7 Source #

(#/\) :: (Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Vector width a -> Full meas vert horiz height width a infixl 7 Source #

multiply :: (Measure meas, C vert, C horiz, C height, C fuse, Eq fuse, C width, Floating a) => Full meas vert horiz height fuse a -> Full meas vert horiz fuse width a -> Full meas vert horiz height width a Source #

multiplyVector :: (Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Vector width a -> Vector height a Source #

class Box typ => ToQuadratic typ where Source #

Methods

heightToQuadratic :: Measure meas => QuadraticMeas typ xl xu lower upper meas height width a -> Quadratic typ xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas typ xl xu lower upper meas height width a -> Quadratic typ xl xu lower upper width a Source #

Instances

Instances details
ToQuadratic Identity Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas Identity xl xu lower upper meas height width a -> Quadratic Identity xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas Identity xl xu lower upper meas height width a -> Quadratic Identity xl xu lower upper width a Source #

ToQuadratic Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas Permutation xl xu lower upper meas height width a -> Quadratic Permutation xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas Permutation xl xu lower upper meas height width a -> Quadratic Permutation xl xu lower upper width a Source #

ToQuadratic Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas Scale xl xu lower upper meas height width a -> Quadratic Scale xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas Scale xl xu lower upper meas height width a -> Quadratic Scale xl xu lower upper width a Source #

ToQuadratic typ => ToQuadratic (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> Quadratic (Inverse typ) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> Quadratic (Inverse typ) xl xu lower upper width a Source #

ToQuadratic typ => ToQuadratic (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (FillStrips typ) xl xu lower upper meas height width a -> Quadratic (FillStrips typ) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (FillStrips typ) xl xu lower upper meas height width a -> Quadratic (FillStrips typ) xl xu lower upper width a Source #

ToQuadratic (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (Array pack property) xl xu lower upper meas height width a -> Quadratic (Array pack property) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (Array pack property) xl xu lower upper meas height width a -> Quadratic (Array pack property) xl xu lower upper width a Source #

(Box typ0, Box typ1) => ToQuadratic (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (Diagonal typ0 typ1) xl xu lower upper meas height width a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (Diagonal typ0 typ1) xl xu lower upper meas height width a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper width a Source #

(Box typ0, Box typOff, Box typ1) => ToQuadratic (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (Triangular typ0 typOff typ1) xl xu lower upper meas height width a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (Triangular typ0 typOff typ1) xl xu lower upper meas height width a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper width a Source #

(Box typ00, Box typ11) => ToQuadratic (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas height width a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas height width a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper width a Source #

(Box typ0, Box typOff, Box typ1, BoxExtra typOff xlOff, BoxExtra typOff xuOff) => ToQuadratic (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Methods

heightToQuadratic :: Measure meas => QuadraticMeas (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas height width a -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper height a Source #

widthToQuadratic :: Measure meas => QuadraticMeas (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas height width a -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper width a Source #

class Homogeneous typ Source #

Minimal complete definition

zeroFrom, negate, scaleReal

Instances

Instances details
Homogeneous Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type HomogeneousExtra Scale extra Source #

Methods

zeroFrom :: (HomogeneousExtra Scale xl, HomogeneousExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra Scale xl, HomogeneousExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra Scale xl, HomogeneousExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source #

Homogeneous property => Homogeneous (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type HomogeneousExtra (Array pack property) extra Source #

Methods

zeroFrom :: (HomogeneousExtra (Array pack property) xl, HomogeneousExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra (Array pack property) xl, HomogeneousExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra (Array pack property) xl, HomogeneousExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a Source #

(Homogeneous typ0, Homogeneous typ1) => Homogeneous (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type HomogeneousExtra (Diagonal typ0 typ1) extra Source #

Methods

zeroFrom :: (HomogeneousExtra (Diagonal typ0 typ1) xl, HomogeneousExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra (Diagonal typ0 typ1) xl, HomogeneousExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra (Diagonal typ0 typ1) xl, HomogeneousExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source #

(Homogeneous typ0, Homogeneous typOff, Homogeneous typ1) => Homogeneous (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type HomogeneousExtra (Triangular typ0 typOff typ1) extra Source #

Methods

zeroFrom :: (HomogeneousExtra (Triangular typ0 typOff typ1) xl, HomogeneousExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra (Triangular typ0 typOff typ1) xl, HomogeneousExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra (Triangular typ0 typOff typ1) xl, HomogeneousExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source #

(Homogeneous typ0, Homogeneous typ1) => Homogeneous (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type HomogeneousExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

zeroFrom :: (HomogeneousExtra (Append typ0 typ1 sh0 sh1) xl, HomogeneousExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra (Append typ0 typ1 sh0 sh1) xl, HomogeneousExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra (Append typ0 typ1 sh0 sh1) xl, HomogeneousExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source #

(Homogeneous typ00, Homogeneous typ11) => Homogeneous (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

zeroFrom :: (HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) xl, HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) xl, HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) xl, HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source #

(Homogeneous typ0, Homogeneous typOff, Homogeneous typ1, HomogeneousExtra typOff xlOff, HomogeneousExtra typOff xuOff) => Homogeneous (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

zeroFrom :: (HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source #

negate :: (HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source #

type family HomogeneousExtra typ extra :: Constraint Source #

Instances

Instances details
type HomogeneousExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type HomogeneousExtra Scale extra = extra ~ ()
type HomogeneousExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type HomogeneousExtra (Array pack property) extra = extra ~ ()
type HomogeneousExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type HomogeneousExtra (Diagonal typ0 typ1) extra
type HomogeneousExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type HomogeneousExtra (Triangular typ0 typOff typ1) extra
type HomogeneousExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type HomogeneousExtra (Append typ0 typ1 sh0 sh1) extra
type HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type HomogeneousExtra (Square typ00 measOff vertOff horizOff typ11) extra
type HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type HomogeneousExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

zero :: Homogeneous property => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Omni pack property lower upper meas vert horiz height width -> ArrayMatrix pack property lower upper meas vert horiz height width a Source #

zeroFrom :: (Homogeneous typ, HomogeneousExtra typ xl, HomogeneousExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a Source #

negate :: (Homogeneous typ, HomogeneousExtra typ xl, HomogeneousExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a Source #

class Homogeneous typ => Scale typ Source #

Minimal complete definition

scale

Instances

Instances details
Scale Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type ScaleExtra Scale extra Source #

Methods

scale :: (ScaleExtra Scale xl, ScaleExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source #

Scale property => Scale (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type ScaleExtra (Array pack property) extra Source #

Methods

scale :: (ScaleExtra (Array pack property) xl, ScaleExtra (Array pack property) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a Source #

(Scale typ0, Scale typ1) => Scale (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type ScaleExtra (Diagonal typ0 typ1) extra Source #

Methods

scale :: (ScaleExtra (Diagonal typ0 typ1) xl, ScaleExtra (Diagonal typ0 typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source #

(Scale typ0, Scale typOff, Scale typ1) => Scale (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type ScaleExtra (Triangular typ0 typOff typ1) extra Source #

Methods

scale :: (ScaleExtra (Triangular typ0 typOff typ1) xl, ScaleExtra (Triangular typ0 typOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source #

(Scale typ0, Scale typ1) => Scale (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type ScaleExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

scale :: (ScaleExtra (Append typ0 typ1 sh0 sh1) xl, ScaleExtra (Append typ0 typ1 sh0 sh1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source #

(Scale typ00, Scale typ11) => Scale (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type ScaleExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

scale :: (ScaleExtra (Square typ00 measOff vertOff horizOff typ11) xl, ScaleExtra (Square typ00 measOff vertOff horizOff typ11) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source #

(Scale typ0, Scale typOff, Scale typ1, ScaleExtra typOff xlOff, ScaleExtra typOff xuOff, HomogeneousExtra typOff xlOff, HomogeneousExtra typOff xuOff) => Scale (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type ScaleExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

scale :: (ScaleExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, ScaleExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source #

type family ScaleExtra typ extra :: Constraint Source #

Instances

Instances details
type ScaleExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type ScaleExtra Scale extra = extra ~ ()
type ScaleExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type ScaleExtra (Array pack property) extra = extra ~ ()
type ScaleExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type ScaleExtra (Diagonal typ0 typ1) extra
type ScaleExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type ScaleExtra (Triangular typ0 typOff typ1) extra
type ScaleExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type ScaleExtra (Append typ0 typ1 sh0 sh1) extra
type ScaleExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type ScaleExtra (Square typ00 measOff vertOff horizOff typ11) extra
type ScaleExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type ScaleExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

scale :: (Scale typ, ScaleExtra typ xl, ScaleExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a Source #

scaleReal :: (Homogeneous typ, HomogeneousExtra typ xl, HomogeneousExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => RealOf a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a Source #

scaleRealReal :: (Homogeneous typ, HomogeneousExtra typ xl, HomogeneousExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Real a) => a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a Source #

(.*#) :: (Scale typ, ScaleExtra typ xl, ScaleExtra typ xu) => (Measure meas, C vert, C horiz) => (C height, C width, Floating a) => a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a infixl 7 Source #

class Additive typ Source #

Minimal complete definition

add

Instances

Instances details
Additive Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type AdditiveExtra Scale extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra Scale xl, AdditiveExtra Scale xu, C height, Eq height, C width, Eq width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source #

Additive property => Additive (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type AdditiveExtra (Array pack property) extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra (Array pack property) xl, AdditiveExtra (Array pack property) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a Source #

(Additive typ0, Additive typ1) => Additive (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type AdditiveExtra (Diagonal typ0 typ1) extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra (Diagonal typ0 typ1) xl, AdditiveExtra (Diagonal typ0 typ1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source #

(Additive typ0, Additive typOff, Additive typ1) => Additive (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type AdditiveExtra (Triangular typ0 typOff typ1) extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra (Triangular typ0 typOff typ1) xl, AdditiveExtra (Triangular typ0 typOff typ1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source #

(Additive typ0, Additive typ1, Eq sh0, Eq sh1) => Additive (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type AdditiveExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra (Append typ0 typ1 sh0 sh1) xl, AdditiveExtra (Append typ0 typ1 sh0 sh1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source #

(Additive typ00, Additive typ11) => Additive (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type AdditiveExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra (Square typ00 measOff vertOff horizOff typ11) xl, AdditiveExtra (Square typ00 measOff vertOff horizOff typ11) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source #

(Additive typ0, Additive typOff, Additive typ1, AdditiveExtra typOff xlOff, AdditiveExtra typOff xuOff) => Additive (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type AdditiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

add :: (Measure meas, C vert, C horiz, AdditiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, AdditiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source #

class Additive typ => Subtractive typ Source #

Minimal complete definition

sub

Instances

Instances details
Subtractive Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type SubtractiveExtra Scale extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra Scale xl, SubtractiveExtra Scale xu, C height, Eq height, C width, Eq width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source #

Subtractive property => Subtractive (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

Associated Types

type SubtractiveExtra (Array pack property) extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra (Array pack property) xl, SubtractiveExtra (Array pack property) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a Source #

(Subtractive typ0, Subtractive typ1) => Subtractive (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SubtractiveExtra (Diagonal typ0 typ1) extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra (Diagonal typ0 typ1) xl, SubtractiveExtra (Diagonal typ0 typ1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a Source #

(Subtractive typ0, Subtractive typOff, Subtractive typ1) => Subtractive (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SubtractiveExtra (Triangular typ0 typOff typ1) extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra (Triangular typ0 typOff typ1) xl, SubtractiveExtra (Triangular typ0 typOff typ1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a Source #

(Subtractive typ0, Subtractive typ1, Eq sh0, Eq sh1) => Subtractive (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SubtractiveExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra (Append typ0 typ1 sh0 sh1) xl, SubtractiveExtra (Append typ0 typ1 sh0 sh1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a Source #

(Subtractive typ00, Subtractive typ11) => Subtractive (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SubtractiveExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra (Square typ00 measOff vertOff horizOff typ11) xl, SubtractiveExtra (Square typ00 measOff vertOff horizOff typ11) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a Source #

(Subtractive typ0, Subtractive typOff, Subtractive typ1, SubtractiveExtra typOff xlOff, SubtractiveExtra typOff xuOff, AdditiveExtra typOff xlOff, AdditiveExtra typOff xuOff) => Subtractive (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SubtractiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

sub :: (Measure meas, C vert, C horiz, SubtractiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, SubtractiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, C height, Eq height, C width, Eq width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a Source #

type family AdditiveExtra typ extra :: Constraint Source #

Instances

Instances details
type AdditiveExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type AdditiveExtra Scale extra = extra ~ ()
type AdditiveExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type AdditiveExtra (Array pack property) extra = extra ~ ()
type AdditiveExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type AdditiveExtra (Diagonal typ0 typ1) extra
type AdditiveExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type AdditiveExtra (Triangular typ0 typOff typ1) extra
type AdditiveExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type AdditiveExtra (Append typ0 typ1 sh0 sh1) extra
type AdditiveExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type AdditiveExtra (Square typ00 measOff vertOff horizOff typ11) extra
type AdditiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type AdditiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

type family SubtractiveExtra typ extra :: Constraint Source #

Instances

Instances details
type SubtractiveExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type SubtractiveExtra Scale extra = extra ~ ()
type SubtractiveExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Class

type SubtractiveExtra (Array pack property) extra = extra ~ ()
type SubtractiveExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SubtractiveExtra (Diagonal typ0 typ1) extra
type SubtractiveExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SubtractiveExtra (Triangular typ0 typOff typ1) extra
type SubtractiveExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SubtractiveExtra (Append typ0 typ1 sh0 sh1) extra
type SubtractiveExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SubtractiveExtra (Square typ00 measOff vertOff horizOff typ11) extra
type SubtractiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SubtractiveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

add :: (Additive typ, Measure meas, C vert, C horiz) => (AdditiveExtra typ xl, AdditiveExtra typ xu, C height, Eq height, C width, Eq width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a infixl 6 Source #

sub :: (Subtractive typ, Measure meas, C vert, C horiz) => (SubtractiveExtra typ xl, SubtractiveExtra typ xu, C height, Eq height, C width, Eq width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a infixl 6 Source #

(#+#) :: (Measure meas, C vert, C horiz) => (Additive typ, AdditiveExtra typ xl, AdditiveExtra typ xu, C height, Eq height, C width, Eq width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a infixl 6 Source #

(#-#) :: (Measure meas, C vert, C horiz) => (Subtractive typ, SubtractiveExtra typ xl, SubtractiveExtra typ xu, C height, Eq height, C width, Eq width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix typ xl xu lower upper meas vert horiz height width a infixl 6 Source #

class (Box typA, Box typB) => Multiply typA xlA xuA typB xlB xuB lowerC upperC measC Source #

Minimal complete definition

matrixMatrix

Instances

Instances details
(xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ ()) => Multiply Permutation xlA xuA Permutation xlB xuB lowerC upperC measC Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type Multiplied Permutation xlA xuA Permutation xlB xuB lowerC upperC measC

type MultipliedExtra Permutation xlA xuA Permutation xlB xuB

Methods

matrixMatrix :: (Box Permutation, Strip lowerA, Strip upperA, Box Permutation, Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied Permutation xlA xuA Permutation xlB xuB lowerC upperC measC ~ typC, MultipliedExtra Permutation xlA xuA Permutation xlB xuB ~ xlC, MultipliedExtra Permutation xuA xlA Permutation xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix Permutation xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix Permutation xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a

(xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ (), lowerC ~ Empty, upperC ~ Empty) => Multiply Scale xlA xuA Scale xlB xuB lowerC upperC measC Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type Multiplied Scale xlA xuA Scale xlB xuB lowerC upperC measC

type MultipliedExtra Scale xlA xuA Scale xlB xuB

Methods

matrixMatrix :: (Box Scale, Strip lowerA, Strip upperA, Box Scale, Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied Scale xlA xuA Scale xlB xuB lowerC upperC measC ~ typC, MultipliedExtra Scale xlA xuA Scale xlB xuB ~ xlC, MultipliedExtra Scale xuA xlA Scale xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix Scale xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix Scale xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a

(Scale property, xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ ()) => Multiply Scale xlA xuA (Array pack property) xlB xuB lowerC upperC measC Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type Multiplied Scale xlA xuA (Array pack property) xlB xuB lowerC upperC measC

type MultipliedExtra Scale xlA xuA (Array pack property) xlB xuB

Methods

matrixMatrix :: (Box Scale, Strip lowerA, Strip upperA, Box (Array pack property), Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied Scale xlA xuA (Array pack property) xlB xuB lowerC upperC measC ~ typC, MultipliedExtra Scale xlA xuA (Array pack property) xlB xuB ~ xlC, MultipliedExtra Scale xuA xlA (Array pack property) xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix Scale xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix (Array pack property) xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a

(Scale property, xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ ()) => Multiply (Array pack property) xlA xuA Scale xlB xuB lowerC upperC measC Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type Multiplied (Array pack property) xlA xuA Scale xlB xuB lowerC upperC measC

type MultipliedExtra (Array pack property) xlA xuA Scale xlB xuB

Methods

matrixMatrix :: (Box (Array pack property), Strip lowerA, Strip upperA, Box Scale, Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied (Array pack property) xlA xuA Scale xlB xuB lowerC upperC measC ~ typC, MultipliedExtra (Array pack property) xlA xuA Scale xlB xuB ~ xlC, MultipliedExtra (Array pack property) xuA xlA Scale xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix (Array pack property) xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix Scale xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a

(Packing packA, Property propertyA, xlA ~ (), xuA ~ (), Packing packB, Property propertyB, xlB ~ (), xuB ~ (), Packing packC, Property propertyC, MultipliedPacking packA packB ~ pack, MultipliedPacking packB packA ~ pack, MultipliedProperty propertyA propertyB ~ propertyAB, MultipliedProperty propertyB propertyA ~ propertyAB, UnitIfTriangular lowerC upperC ~ diag, UnitIfTriangular upperC lowerC ~ diag, PackingByStrip lowerC upperC measC pack ~ packC, PackingByStrip upperC lowerC measC pack ~ packC, MergeUnit propertyAB diag ~ propertyC, MergeUnit diag propertyAB ~ propertyC) => Multiply (Array packA propertyA) xlA xuA (Array packB propertyB) xlB xuB lowerC upperC measC Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type Multiplied (Array packA propertyA) xlA xuA (Array packB propertyB) xlB xuB lowerC upperC measC

type MultipliedExtra (Array packA propertyA) xlA xuA (Array packB propertyB) xlB xuB

Methods

matrixMatrix :: (Box (Array packA propertyA), Strip lowerA, Strip upperA, Box (Array packB propertyB), Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied (Array packA propertyA) xlA xuA (Array packB propertyB) xlB xuB lowerC upperC measC ~ typC, MultipliedExtra (Array packA propertyA) xlA xuA (Array packB propertyB) xlB xuB ~ xlC, MultipliedExtra (Array packA propertyA) xuA xlA (Array packB propertyB) xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix (Array packA propertyA) xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix (Array packB propertyB) xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a

(#*#) :: (Box typA, Strip lowerA, Strip upperA) => (Box typB, Strip lowerB, Strip upperB) => (Box typC, Strip lowerC, Strip upperC) => Multiply typA xlA xuA typB xlB xuB lowerC upperC measC => Multiplied typA xlA xuA typB xlB xuB lowerC upperC measC ~ typC => MultipliedExtra typA xlA xuA typB xlB xuB ~ xlC => MultipliedExtra typA xuA xlA typB xuB xlB ~ xuC => MultipliedStrip lowerA lowerB ~ lowerC => MultipliedStrip lowerB lowerA ~ lowerC => MultipliedStrip upperA upperB ~ upperC => MultipliedStrip upperB upperA ~ upperC => MultipliedBands lowerA lowerB ~ lowerC => MultipliedBands lowerB lowerA ~ lowerC => MultipliedBands upperA upperB ~ upperC => MultipliedBands upperB upperA ~ upperC => (Measure measA, C vertA, C horizA) => (Measure measB, C vertB, C horizB) => MultiplyMeasure measA measB ~ measC => MultiplyMeasure measB measA ~ measC => Multiply vertA vertB ~ vertC => Multiply vertB vertA ~ vertC => Multiply horizA horizB ~ horizC => Multiply horizB horizA ~ horizC => (C height, C fuse, Eq fuse, C width) => Floating a => Matrix typA xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix typB xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a infixl 7 Source #

class Box typ => MultiplyVector typ Source #

Minimal complete definition

matrixVector, vectorMatrix

Instances

Instances details
MultiplyVector Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type MultiplyVectorExtra Permutation extra Source #

Methods

matrixVector :: (MultiplyVectorExtra Permutation xl, MultiplyVectorExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra Permutation xl, MultiplyVectorExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> Vector width a

MultiplyVector Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type MultiplyVectorExtra Scale extra Source #

Methods

matrixVector :: (MultiplyVectorExtra Scale xl, MultiplyVectorExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra Scale xl, MultiplyVectorExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Vector width a

(Solve typ, ToQuadratic typ) => MultiplyVector (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type MultiplyVectorExtra (Inverse typ) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Inverse typ) xl, MultiplyVectorExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Inverse typ) xl, MultiplyVectorExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Vector width a

(MultiplyVector typ, ToQuadratic typ) => MultiplyVector (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type MultiplyVectorExtra (FillStrips typ) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (FillStrips typ) xl, MultiplyVectorExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (FillStrips typ) xl, MultiplyVectorExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Vector width a

(Packing pack, Property property) => MultiplyVector (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type MultiplyVectorExtra (Array pack property) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Array pack property) xl, MultiplyVectorExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Array pack property) xl, MultiplyVectorExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> Vector width a

(MultiplyVector typ0, MultiplyVector typ1) => MultiplyVector (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplyVectorExtra (Diagonal typ0 typ1) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Diagonal typ0 typ1) xl, MultiplyVectorExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Diagonal typ0 typ1) xl, MultiplyVectorExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz height width a -> Vector width a

(MultiplyVector typ, ToQuadratic typ, Measure meas) => MultiplyVector (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type MultiplyVectorExtra (MapExtent typ meas) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (MapExtent typ meas) xl, MultiplyVectorExtra (MapExtent typ meas) xu, Strip lower, Strip upper, Measure meas0, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (MapExtent typ meas) xl, MultiplyVectorExtra (MapExtent typ meas) xu, Strip lower, Strip upper, Measure meas0, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Vector width a

(MultiplyVector typ0, MultiplyVector typ1, MultiplyVector typOff) => MultiplyVector (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplyVectorExtra (Triangular typ0 typOff typ1) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Triangular typ0 typOff typ1) xl, MultiplyVectorExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Triangular typ0 typOff typ1) xl, MultiplyVectorExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz height width a -> Vector width a

(MultiplyVector typ0, MultiplyVector typ1, Eq sh0, Eq sh1) => MultiplyVector (Append typ0 typ1 sh0 sh1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) xl, MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) xl, MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Append typ0 typ1 sh0 sh1) xl xu lower upper meas vert horiz height width a -> Vector width a

(MultiplyVector typ00, MultiplyVector typ11) => MultiplyVector (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) xl, MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) xl, MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz height width a -> Vector width a

(MultiplyVector typ0, MultiplyVector typ1, BoxExtra typOff xlOff, BoxExtra typOff xuOff, MultiplyVector typOff, MultiplyVectorExtra typOff xlOff, MultiplyVectorExtra typOff xuOff) => MultiplyVector (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

matrixVector :: (MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a

vectorMatrix :: (MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper meas vert horiz height width a -> Vector width a

type family MultiplyVectorExtra typ extra :: Constraint Source #

Instances

Instances details
type MultiplyVectorExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type MultiplyVectorExtra Permutation extra = extra ~ ()
type MultiplyVectorExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type MultiplyVectorExtra Scale extra = extra ~ ()
type MultiplyVectorExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type MultiplyVectorExtra (Inverse typ) extra
type MultiplyVectorExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type MultiplyVectorExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type MultiplyVectorExtra (Array pack property) extra = extra ~ ()
type MultiplyVectorExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Diagonal typ0 typ1) extra
type MultiplyVectorExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type MultiplyVectorExtra (MapExtent typ meas) extra
type MultiplyVectorExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Triangular typ0 typOff typ1) extra
type MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Append typ0 typ1 sh0 sh1) extra
type MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Square typ00 measOff vertOff horizOff typ11) extra
type MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

(#*|) :: (MultiplyVector typ, Strip lower, Strip upper) => (MultiplyVectorExtra typ xl, MultiplyVectorExtra typ xu) => (Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a infixr 7 Source #

(-*#) :: (MultiplyVector typ, Strip lower, Strip upper) => (MultiplyVectorExtra typ xl, MultiplyVectorExtra typ xu) => (Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix typ xl xu lower upper meas vert horiz height width a -> Vector width a infixl 7 Source #

class Box typ => MultiplySquare typ Source #

Minimal complete definition

transposableSquare | fullSquare, squareFull

Instances

Instances details
MultiplySquare Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type MultiplySquareExtra Permutation extra Source #

Methods

transposableSquare :: (MultiplySquareExtra Permutation xl, MultiplySquareExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra Permutation xl, MultiplySquareExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra Permutation xl, MultiplySquareExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Permutation xl xu lower upper width a -> Full meas vert horiz height width a

MultiplySquare Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type MultiplySquareExtra Scale extra Source #

Methods

transposableSquare :: (MultiplySquareExtra Scale xl, MultiplySquareExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra Scale xl, MultiplySquareExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra Scale xl, MultiplySquareExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Scale xl xu lower upper width a -> Full meas vert horiz height width a

(Solve typ, ToQuadratic typ) => MultiplySquare (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type MultiplySquareExtra (Inverse typ) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (Inverse typ) xl, MultiplySquareExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (Inverse typ) xl, MultiplySquareExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (Inverse typ) xl, MultiplySquareExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Inverse typ) xl xu lower upper width a -> Full meas vert horiz height width a

(MultiplySquare typ, ToQuadratic typ) => MultiplySquare (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type MultiplySquareExtra (FillStrips typ) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (FillStrips typ) xl, MultiplySquareExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (FillStrips typ) xl, MultiplySquareExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (FillStrips typ) xl, MultiplySquareExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (FillStrips typ) xl xu lower upper width a -> Full meas vert horiz height width a

(Packing pack, Property property) => MultiplySquare (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type MultiplySquareExtra (Array pack property) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (Array pack property) xl, MultiplySquareExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Array pack property) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (Array pack property) xl, MultiplySquareExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Array pack property) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (Array pack property) xl, MultiplySquareExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Array pack property) xl xu lower upper width a -> Full meas vert horiz height width a

(MultiplySquare typ0, MultiplySquare typ1) => MultiplySquare (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySquareExtra (Diagonal typ0 typ1) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (Diagonal typ0 typ1) xl, MultiplySquareExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Diagonal typ0 typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (Diagonal typ0 typ1) xl, MultiplySquareExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (Diagonal typ0 typ1) xl, MultiplySquareExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper width a -> Full meas vert horiz height width a

(MultiplySquare typ0, MultiplySquare typ1, typOff ~ TypeFull) => MultiplySquare (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySquareExtra (Triangular typ0 typOff typ1) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (Triangular typ0 typOff typ1) xl, MultiplySquareExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (Triangular typ0 typOff typ1) xl, MultiplySquareExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (Triangular typ0 typOff typ1) xl, MultiplySquareExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper width a -> Full meas vert horiz height width a

(MultiplySquare typ00, MultiplySquare typ11) => MultiplySquare (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) xl, MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) xl, MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) xl, MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper width a -> Full meas vert horiz height width a

(MultiplySquare typ0, MultiplySquare typ1, typOff ~ TypeFull, xlOff ~ (), xuOff ~ ()) => MultiplySquare (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

transposableSquare :: (MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

squareFull :: (MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a

fullSquare :: (MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper width a -> Full meas vert horiz height width a

type family MultiplySquareExtra typ extra :: Constraint Source #

Instances

Instances details
type MultiplySquareExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type MultiplySquareExtra Permutation extra = extra ~ ()
type MultiplySquareExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type MultiplySquareExtra Scale extra = extra ~ ()
type MultiplySquareExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type MultiplySquareExtra (Inverse typ) extra
type MultiplySquareExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type MultiplySquareExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type MultiplySquareExtra (Array pack property) extra = extra ~ ()
type MultiplySquareExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySquareExtra (Diagonal typ0 typ1) extra
type MultiplySquareExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySquareExtra (Triangular typ0 typOff typ1) extra
type MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySquareExtra (Square typ00 measOff vertOff horizOff typ11) extra
type MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySquareExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

multiplySquare :: MultiplySquare typ => (MultiplySquareExtra typ xl, MultiplySquareExtra typ xu) => (Strip lower, Strip upper) => (Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

class Box typ => MultiplySame typ where Source #

Methods

multiplySame :: (matrix ~ Matrix typ xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra typ xl, MultiplySameExtra typ xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

Instances

Instances details
MultiplySame Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type MultiplySameExtra Permutation extra Source #

Methods

multiplySame :: (matrix ~ Matrix Permutation xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra Permutation xl, MultiplySameExtra Permutation xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

MultiplySame Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

Associated Types

type MultiplySameExtra Scale extra Source #

Methods

multiplySame :: (matrix ~ Matrix Scale xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra Scale xl, MultiplySameExtra Scale xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

MultiplySame typ => MultiplySame (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type MultiplySameExtra (Inverse typ) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (Inverse typ) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (Inverse typ) xl, MultiplySameExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

MultiplySame typ => MultiplySame (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type MultiplySameExtra (FillStrips typ) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (FillStrips typ) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (FillStrips typ) xl, MultiplySameExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

(Packing pack, TriDiag diag) => MultiplySame (Array pack diag) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

Associated Types

type MultiplySameExtra (Array pack diag) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (Array pack diag) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (Array pack diag) xl, MultiplySameExtra (Array pack diag) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

(MultiplySame typ0, MultiplySame typ1) => MultiplySame (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySameExtra (Diagonal typ0 typ1) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (Diagonal typ0 typ1) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (Diagonal typ0 typ1) xl, MultiplySameExtra (Diagonal typ0 typ1) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

(MultiplySame typ, Measure meas) => MultiplySame (MapExtent typ meas) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type MultiplySameExtra (MapExtent typ meas) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz sh sh a, MultiplySameExtra (MapExtent typ meas) xl, MultiplySameExtra (MapExtent typ meas) xu, PowerStrip lower, PowerStrip upper, Measure meas0, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

(typ0 ~ TypeFull, typOff ~ TypeFull, typ1 ~ TypeFull) => MultiplySame (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySameExtra (Triangular typ0 typOff typ1) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (Triangular typ0 typOff typ1) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (Triangular typ0 typOff typ1) xl, MultiplySameExtra (Triangular typ0 typOff typ1) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

(typ00 ~ TypeFull, typ11 ~ TypeFull) => MultiplySame (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type MultiplySameExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

multiplySame :: (matrix ~ Matrix (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (Square typ00 measOff vertOff horizOff typ11) xl, MultiplySameExtra (Square typ00 measOff vertOff horizOff typ11) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source #

type family MultiplySameExtra typ extra :: Constraint Source #

Instances

Instances details
type MultiplySameExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type MultiplySameExtra Permutation extra = extra ~ ()
type MultiplySameExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Type.Private

type MultiplySameExtra Scale extra = extra ~ ()
type MultiplySameExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type MultiplySameExtra (Inverse typ) extra
type MultiplySameExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type MultiplySameExtra (FillStrips typ) extra
type MultiplySameExtra (Array pack diag) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Private

type MultiplySameExtra (Array pack diag) extra = extra ~ ()
type MultiplySameExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySameExtra (Diagonal typ0 typ1) extra
type MultiplySameExtra (MapExtent typ meas) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type MultiplySameExtra (MapExtent typ meas) extra
type MultiplySameExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySameExtra (Triangular typ0 typOff typ1) extra
type MultiplySameExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySameExtra (Square typ00 measOff vertOff horizOff typ11) extra

class Box typ => Power typ Source #

Minimal complete definition

square, power, powers1

Instances

Instances details
Power Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type PowerExtra Permutation extra Source #

Methods

square :: (PowerExtra Permutation xl, PowerExtra Permutation xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Quadratic Permutation xl xu lower upper sh a Source #

power :: (PowerExtra Permutation xl, PowerExtra Permutation xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic Permutation xl xu lower upper sh a -> Quadratic Permutation xl xu lower upper sh a Source #

powers1 :: (PowerExtra Permutation xl, PowerExtra Permutation xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Stream (Quadratic Permutation xl xu lower upper sh a) Source #

Power Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type PowerExtra Scale extra Source #

Methods

square :: (PowerExtra Scale xl, PowerExtra Scale xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Quadratic Scale xl xu lower upper sh a Source #

power :: (PowerExtra Scale xl, PowerExtra Scale xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic Scale xl xu lower upper sh a -> Quadratic Scale xl xu lower upper sh a Source #

powers1 :: (PowerExtra Scale xl, PowerExtra Scale xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Stream (Quadratic Scale xl xu lower upper sh a) Source #

Power typ => Power (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type PowerExtra (Inverse typ) extra Source #

Methods

square :: (PowerExtra (Inverse typ) xl, PowerExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Inverse typ) xl xu lower upper sh a -> Quadratic (Inverse typ) xl xu lower upper sh a Source #

power :: (PowerExtra (Inverse typ) xl, PowerExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (Inverse typ) xl xu lower upper sh a -> Quadratic (Inverse typ) xl xu lower upper sh a Source #

powers1 :: (PowerExtra (Inverse typ) xl, PowerExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Inverse typ) xl xu lower upper sh a -> Stream (Quadratic (Inverse typ) xl xu lower upper sh a) Source #

Power typ => Power (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type PowerExtra (FillStrips typ) extra Source #

Methods

square :: (PowerExtra (FillStrips typ) xl, PowerExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (FillStrips typ) xl xu lower upper sh a -> Quadratic (FillStrips typ) xl xu lower upper sh a Source #

power :: (PowerExtra (FillStrips typ) xl, PowerExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (FillStrips typ) xl xu lower upper sh a -> Quadratic (FillStrips typ) xl xu lower upper sh a Source #

powers1 :: (PowerExtra (FillStrips typ) xl, PowerExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (FillStrips typ) xl xu lower upper sh a -> Stream (Quadratic (FillStrips typ) xl xu lower upper sh a) Source #

(Packing pack, Property property) => Power (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

type PowerExtra (Array pack property) extra Source #

Methods

square :: (PowerExtra (Array pack property) xl, PowerExtra (Array pack property) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Array pack property) xl xu lower upper sh a -> Quadratic (Array pack property) xl xu lower upper sh a Source #

power :: (PowerExtra (Array pack property) xl, PowerExtra (Array pack property) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (Array pack property) xl xu lower upper sh a -> Quadratic (Array pack property) xl xu lower upper sh a Source #

powers1 :: (PowerExtra (Array pack property) xl, PowerExtra (Array pack property) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Array pack property) xl xu lower upper sh a -> Stream (Quadratic (Array pack property) xl xu lower upper sh a) Source #

(Power typ0, Power typ1) => Power (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type PowerExtra (Diagonal typ0 typ1) extra Source #

Methods

square :: (PowerExtra (Diagonal typ0 typ1) xl, PowerExtra (Diagonal typ0 typ1) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a Source #

power :: (PowerExtra (Diagonal typ0 typ1) xl, PowerExtra (Diagonal typ0 typ1) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a Source #

powers1 :: (PowerExtra (Diagonal typ0 typ1) xl, PowerExtra (Diagonal typ0 typ1) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a -> Stream (Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a) Source #

(typ0 ~ TypeFull, typOff ~ TypeFull, typ1 ~ TypeFull) => Power (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type PowerExtra (Triangular typ0 typOff typ1) extra Source #

Methods

square :: (PowerExtra (Triangular typ0 typOff typ1) xl, PowerExtra (Triangular typ0 typOff typ1) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a Source #

power :: (PowerExtra (Triangular typ0 typOff typ1) xl, PowerExtra (Triangular typ0 typOff typ1) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a Source #

powers1 :: (PowerExtra (Triangular typ0 typOff typ1) xl, PowerExtra (Triangular typ0 typOff typ1) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a -> Stream (Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a) Source #

(typ00 ~ TypeFull, typ11 ~ TypeFull) => Power (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type PowerExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

square :: (PowerExtra (Square typ00 measOff vertOff horizOff typ11) xl, PowerExtra (Square typ00 measOff vertOff horizOff typ11) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a Source #

power :: (PowerExtra (Square typ00 measOff vertOff horizOff typ11) xl, PowerExtra (Square typ00 measOff vertOff horizOff typ11) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a Source #

powers1 :: (PowerExtra (Square typ00 measOff vertOff horizOff typ11) xl, PowerExtra (Square typ00 measOff vertOff horizOff typ11) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a -> Stream (Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a) Source #

type family PowerExtra typ extra :: Constraint Source #

Instances

Instances details
type PowerExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type PowerExtra Permutation extra = extra ~ ()
type PowerExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type PowerExtra Scale extra = extra ~ ()
type PowerExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type PowerExtra (Inverse typ) extra
type PowerExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type PowerExtra (FillStrips typ) extra
type PowerExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Multiply

type PowerExtra (Array pack property) extra = extra ~ ()
type PowerExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type PowerExtra (Diagonal typ0 typ1) extra
type PowerExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type PowerExtra (Triangular typ0 typOff typ1) extra
type PowerExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type PowerExtra (Square typ00 measOff vertOff horizOff typ11) extra

square :: (Power typ, PowerExtra typ xl, PowerExtra typ xu) => (PowerStrip lower, PowerStrip upper) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Quadratic typ xl xu lower upper sh a Source #

power :: (Power typ, PowerExtra typ xl, PowerExtra typ xu) => (PowerStrip lower, PowerStrip upper) => (C sh, Floating a) => Integer -> Quadratic typ xl xu lower upper sh a -> Quadratic typ xl xu lower upper sh a Source #

powers :: (Power typ, PowerExtra typ xl, PowerExtra typ xu) => (SquareShape typ, SquareShapeExtra typ xl, SquareShapeExtra typ xu) => (PowerStrip lower, PowerStrip upper) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Stream (Quadratic typ xl xu lower upper sh a) Source #

powers1 :: (Power typ, PowerExtra typ xl, PowerExtra typ xu) => (PowerStrip lower, PowerStrip upper) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> Stream (Quadratic typ xl xu lower upper sh a) Source #

(##*#) :: (MultiplySquare typ, ToQuadratic typ) => (MultiplySquareExtra typ xl, MultiplySquareExtra typ xu) => (BoxExtra typ xl, BoxExtra typ xu) => (Strip lowerA, Strip upperA) => (Strip lowerB, Strip upperB) => (Strip lowerC, Strip upperC) => MultipliedBands lowerA lowerB ~ lowerC => MultipliedBands lowerB lowerA ~ lowerC => MultipliedBands upperA upperB ~ upperC => MultipliedBands upperB upperA ~ upperC => (Measure measA, Measure measB, Measure measC, MultiplyMeasure measA measB ~ measC) => (C vert, C horiz) => (C height, C fuse, Eq fuse, C width, Floating a) => Unpacked lowerB upperB measB vert horiz height fuse a -> QuadraticMeas typ xl xu lowerA upperA measA fuse width a -> Unpacked lowerC upperC measC vert horiz height width a infixl 7 Source #

(#*##) :: (MultiplySquare typ, ToQuadratic typ) => (MultiplySquareExtra typ xl, MultiplySquareExtra typ xu) => (BoxExtra typ xl, BoxExtra typ xu) => (Strip lowerA, Strip upperA) => (Strip lowerB, Strip upperB) => (Strip lowerC, Strip upperC) => MultipliedBands lowerA lowerB ~ lowerC => MultipliedBands lowerB lowerA ~ lowerC => MultipliedBands upperA upperB ~ upperC => MultipliedBands upperB upperA ~ upperC => (Measure measA, Measure measB, Measure measC, MultiplyMeasure measA measB ~ measC) => (C vert, C horiz) => (C height, C fuse, Eq fuse, C width, Floating a) => QuadraticMeas typ xl xu lowerA upperA measA height fuse a -> Unpacked lowerB upperB measB vert horiz fuse width a -> Unpacked lowerC upperC measC vert horiz height width a infixr 7 Source #

class Box typ => Indexed typ Source #

Minimal complete definition

(#!)

Instances

Instances details
Indexed Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a Source #

Indexed Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a Source #

Indexed (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a Source #

(#!) :: (Indexed typ, Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix typ xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a infixl 9 Source #

class Box typ => Determinant typ Source #

Minimal complete definition

determinant

Instances

Instances details
Determinant Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type DeterminantExtra Permutation extra Source #

Methods

determinant :: (DeterminantExtra Permutation xl, DeterminantExtra Permutation xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> a Source #

Determinant Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type DeterminantExtra Scale extra Source #

Methods

determinant :: (DeterminantExtra Scale xl, DeterminantExtra Scale xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> a Source #

Determinant typ => Determinant (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type DeterminantExtra (Inverse typ) extra Source #

Methods

determinant :: (DeterminantExtra (Inverse typ) xl, DeterminantExtra (Inverse typ) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Inverse typ) xl xu lower upper sh a -> a Source #

Determinant typ => Determinant (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type DeterminantExtra (FillStrips typ) extra Source #

Methods

determinant :: (DeterminantExtra (FillStrips typ) xl, DeterminantExtra (FillStrips typ) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (FillStrips typ) xl xu lower upper sh a -> a Source #

(Packing pack, Property property) => Determinant (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type DeterminantExtra (Array pack property) extra Source #

Methods

determinant :: (DeterminantExtra (Array pack property) xl, DeterminantExtra (Array pack property) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Array pack property) xl xu lower upper sh a -> a Source #

(Determinant typ0, Determinant typ1) => Determinant (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type DeterminantExtra (Diagonal typ0 typ1) extra Source #

Methods

determinant :: (DeterminantExtra (Diagonal typ0 typ1) xl, DeterminantExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper sh a -> a Source #

(Determinant typ0, Box typOff, Determinant typ1) => Determinant (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type DeterminantExtra (Triangular typ0 typOff typ1) extra Source #

Methods

determinant :: (DeterminantExtra (Triangular typ0 typOff typ1) xl, DeterminantExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper sh a -> a Source #

(typ00 ~ TypeFull, Solve typ11, Determinant typ11) => Determinant (Square typ00 measOff vertOff horizOff typ11) Source #

Requires that the bottom right sub-matrix is regular.

The order is chosen such that no nested Schur complements are necessary. However, in some common examples like the resistor network and Lagrange multiplicators we have a zero bottom right sub-matrix and the top left matrix is regular.

Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type DeterminantExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

determinant :: (DeterminantExtra (Square typ00 measOff vertOff horizOff typ11) xl, DeterminantExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper sh a -> a Source #

(typ0 ~ TypeFull, Solve typ1, typOff ~ TypeFull, xlOff ~ (), xuOff ~ ()) => Determinant (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type DeterminantExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

determinant :: (DeterminantExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, DeterminantExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper sh a -> a Source #

type family DeterminantExtra typ extra :: Constraint Source #

Instances

Instances details
type DeterminantExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type DeterminantExtra Permutation extra = extra ~ ()
type DeterminantExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type DeterminantExtra Scale extra = extra ~ ()
type DeterminantExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type DeterminantExtra (Inverse typ) extra
type DeterminantExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type DeterminantExtra (FillStrips typ) extra
type DeterminantExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type DeterminantExtra (Array pack property) extra = extra ~ ()
type DeterminantExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type DeterminantExtra (Diagonal typ0 typ1) extra
type DeterminantExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type DeterminantExtra (Triangular typ0 typOff typ1) extra
type DeterminantExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type DeterminantExtra (Square typ00 measOff vertOff horizOff typ11) extra
type DeterminantExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type DeterminantExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

determinant :: (Determinant typ, DeterminantExtra typ xl, DeterminantExtra typ xu) => (Strip lower, Strip upper) => (C sh, Floating a) => Quadratic typ xl xu lower upper sh a -> a Source #

class Box typ => Solve typ Source #

Minimal complete definition

solve | solveLeft, solveRight

Instances

Instances details
Solve Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type SolveExtra Permutation extra Source #

Methods

solve :: (SolveExtra Permutation xl, SolveExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra Permutation xl, SolveExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra Permutation xl, SolveExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Permutation xl xu lower upper width a -> Full meas vert horiz height width a Source #

Solve Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type SolveExtra Scale extra Source #

Methods

solve :: (SolveExtra Scale xl, SolveExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra Scale xl, SolveExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra Scale xl, SolveExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Scale xl xu lower upper width a -> Full meas vert horiz height width a Source #

(MultiplySquare typ, ToQuadratic typ) => Solve (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type SolveExtra (Inverse typ) extra Source #

Methods

solve :: (SolveExtra (Inverse typ) xl, SolveExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (Inverse typ) xl, SolveExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (Inverse typ) xl, SolveExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Inverse typ) xl xu lower upper width a -> Full meas vert horiz height width a Source #

(Solve typ, ToQuadratic typ) => Solve (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type SolveExtra (FillStrips typ) extra Source #

Methods

solve :: (SolveExtra (FillStrips typ) xl, SolveExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (FillStrips typ) xl, SolveExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (FillStrips typ) xl, SolveExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (FillStrips typ) xl xu lower upper width a -> Full meas vert horiz height width a Source #

(Packing pack, Property property) => Solve (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type SolveExtra (Array pack property) extra Source #

Methods

solve :: (SolveExtra (Array pack property) xl, SolveExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Array pack property) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (Array pack property) xl, SolveExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Array pack property) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (Array pack property) xl, SolveExtra (Array pack property) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Array pack property) xl xu lower upper width a -> Full meas vert horiz height width a Source #

(Solve typ0, Solve typ1) => Solve (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SolveExtra (Diagonal typ0 typ1) extra Source #

Methods

solve :: (SolveExtra (Diagonal typ0 typ1) xl, SolveExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Diagonal typ0 typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (Diagonal typ0 typ1) xl, SolveExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Diagonal typ0 typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (Diagonal typ0 typ1) xl, SolveExtra (Diagonal typ0 typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Diagonal typ0 typ1) xl xu lower upper width a -> Full meas vert horiz height width a Source #

(Solve typ0, Solve typ1, typOff ~ TypeFull) => Solve (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SolveExtra (Triangular typ0 typOff typ1) extra Source #

Methods

solve :: (SolveExtra (Triangular typ0 typOff typ1) xl, SolveExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (Triangular typ0 typOff typ1) xl, SolveExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Triangular typ0 typOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (Triangular typ0 typOff typ1) xl, SolveExtra (Triangular typ0 typOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Triangular typ0 typOff typ1) xl xu lower upper width a -> Full meas vert horiz height width a Source #

(typ00 ~ TypeFull, Solve typ11) => Solve (Square typ00 measOff vertOff horizOff typ11) Source #

Requires that the bottom right sub-matrix is regular.

Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SolveExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

solve :: (SolveExtra (Square typ00 measOff vertOff horizOff typ11) xl, SolveExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (Square typ00 measOff vertOff horizOff typ11) xl, SolveExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (Square typ00 measOff vertOff horizOff typ11) xl, SolveExtra (Square typ00 measOff vertOff horizOff typ11) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper width a -> Full meas vert horiz height width a Source #

(typ0 ~ TypeFull, Solve typ1, typOff ~ TypeFull, xlOff ~ (), xuOff ~ ()) => Solve (Symmetric typ0 typOff xlOff xuOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source #

Methods

solve :: (SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveRight :: (SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xl, SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) xl xu lower upper width a -> Full meas vert horiz height width a Source #

type family SolveExtra typ extra :: Constraint Source #

Instances

Instances details
type SolveExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type SolveExtra Permutation extra = extra ~ ()
type SolveExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type SolveExtra Scale extra = extra ~ ()
type SolveExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type SolveExtra (Inverse typ) extra
type SolveExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type SolveExtra (FillStrips typ) extra
type SolveExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type SolveExtra (Array pack property) extra = extra ~ ()
type SolveExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SolveExtra (Diagonal typ0 typ1) extra
type SolveExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SolveExtra (Triangular typ0 typOff typ1) extra
type SolveExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SolveExtra (Square typ00 measOff vertOff horizOff typ11) extra
type SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SolveExtra (Symmetric typ0 typOff xlOff xuOff typ1) extra

solve :: (Solve typ, SolveExtra typ xl, SolveExtra typ xu) => (Strip lower, Strip upper) => (Measure meas, C vert, C horiz) => (C height, C width, Eq height, Floating a) => Transposition -> Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

solveLeft :: (Solve typ, SolveExtra typ xl, SolveExtra typ xu) => (Strip lower, Strip upper) => (Measure meas, C vert, C horiz) => (C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic typ xl xu lower upper width a -> Full meas vert horiz height width a Source #

solveRight :: (Solve typ, SolveExtra typ xl, SolveExtra typ xu) => (Strip lower, Strip upper) => (Measure meas, C vert, C horiz) => (C height, C width, Eq height, Floating a) => Quadratic typ xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source #

(##/#) :: (Solve typ, ToQuadratic typ, SolveExtra typ xl, SolveExtra typ xu, BoxExtra typ xl, BoxExtra typ xu, Strip lower, Strip upper, C height, C width, Eq width, C nrhs, Measure measA, Measure measB, Measure measC, MultiplyMeasure measA measB ~ measC, C vert, C horiz, Floating a) => Full measB vert horiz nrhs width a -> QuadraticMeas typ xl xu lower upper measA height width a -> Full measC vert horiz nrhs height a infixl 7 Source #

(#\##) :: (Solve typ, ToQuadratic typ, SolveExtra typ xl, SolveExtra typ xu, BoxExtra typ xl, BoxExtra typ xu, Strip lower, Strip upper, C height, Eq height, C width, C nrhs, Measure measA, Measure measB, Measure measC, MultiplyMeasure measA measB ~ measC, C vert, C horiz, Floating a) => QuadraticMeas typ xl xu lower upper measA height width a -> Full measB vert horiz height nrhs a -> Full measC vert horiz width nrhs a infixr 7 Source #

solveVector :: (Solve typ, SolveExtra typ xl, SolveExtra typ xu, Strip lower, Strip upper, C sh, Eq sh, Floating a) => Transposition -> Quadratic typ xl xu lower upper sh a -> Vector sh a -> Vector sh a Source #

(-/#) :: (Solve typ, ToQuadratic typ, SolveExtra typ xl, SolveExtra typ xu, BoxExtra typ xl, BoxExtra typ xu, Strip lower, Strip upper, Measure meas, C height, C width, Eq width, Floating a) => Vector width a -> QuadraticMeas typ xl xu lower upper meas height width a -> Vector height a infixl 7 Source #

(#\|) :: (Solve typ, ToQuadratic typ, SolveExtra typ xl, SolveExtra typ xu, BoxExtra typ xl, BoxExtra typ xu, Strip lower, Strip upper, Measure meas, C height, C width, Eq height, Floating a) => QuadraticMeas typ xl xu lower upper meas height width a -> Vector height a -> Vector width a infixr 7 Source #

class Solve typ => Inverse typ Source #

Minimal complete definition

inverse

Instances

Instances details
Inverse Permutation Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type InverseExtra Permutation extra Source #

Methods

inverse :: (InverseExtra Permutation xl, InverseExtra Permutation xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas Permutation xl xu lower upper meas height width a -> QuadraticMeas Permutation xl xu lower upper meas width height a Source #

Inverse Scale Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type InverseExtra Scale extra Source #

Methods

inverse :: (InverseExtra Scale xl, InverseExtra Scale xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas Scale xl xu lower upper meas height width a -> QuadraticMeas Scale xl xu lower upper meas width height a Source #

(Inverse typ, MultiplySquare typ, ToQuadratic typ) => Inverse (Inverse typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

Associated Types

type InverseExtra (Inverse typ) extra Source #

Methods

inverse :: (InverseExtra (Inverse typ) xl, InverseExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> QuadraticMeas (Inverse typ) xl xu lower upper meas width height a Source #

(Inverse typ, ToQuadratic typ) => Inverse (FillStrips typ) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

Associated Types

type InverseExtra (FillStrips typ) extra Source #

Methods

inverse :: (InverseExtra (FillStrips typ) xl, InverseExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (FillStrips typ) xl xu lower upper meas height width a -> QuadraticMeas (FillStrips typ) xl xu lower upper meas width height a Source #

(Packing pack, Property property) => Inverse (Array pack property) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Associated Types

type InverseExtra (Array pack property) extra Source #

Methods

inverse :: (InverseExtra (Array pack property) xl, InverseExtra (Array pack property) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (Array pack property) xl xu lower upper meas height width a -> QuadraticMeas (Array pack property) xl xu lower upper meas width height a Source #

(Inverse typ0, Inverse typ1) => Inverse (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type InverseExtra (Diagonal typ0 typ1) extra Source #

Methods

inverse :: (InverseExtra (Diagonal typ0 typ1) xl, InverseExtra (Diagonal typ0 typ1) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (Diagonal typ0 typ1) xl xu lower upper meas height width a -> QuadraticMeas (Diagonal typ0 typ1) xl xu lower upper meas width height a Source #

(Inverse typ0, Inverse typ1, typOff ~ TypeFull) => Inverse (Triangular typ0 typOff typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type InverseExtra (Triangular typ0 typOff typ1) extra Source #

Methods

inverse :: (InverseExtra (Triangular typ0 typOff typ1) xl, InverseExtra (Triangular typ0 typOff typ1) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (Triangular typ0 typOff typ1) xl xu lower upper meas height width a -> QuadraticMeas (Triangular typ0 typOff typ1) xl xu lower upper meas width height a Source #

(typ00 ~ TypeFull, typ11 ~ TypeFull) => Inverse (Square typ00 measOff vertOff horizOff typ11) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type InverseExtra (Square typ00 measOff vertOff horizOff typ11) extra Source #

Methods

inverse :: (InverseExtra (Square typ00 measOff vertOff horizOff typ11) xl, InverseExtra (Square typ00 measOff vertOff horizOff typ11) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas height width a -> QuadraticMeas (Square typ00 measOff vertOff horizOff typ11) xl xu lower upper meas width height a Source #

type family InverseExtra typ extra :: Constraint Source #

Instances

Instances details
type InverseExtra Permutation extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type InverseExtra Permutation extra = extra ~ ()
type InverseExtra Scale extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type InverseExtra Scale extra = extra ~ ()
type InverseExtra (Inverse typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

type InverseExtra (Inverse typ) extra
type InverseExtra (FillStrips typ) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Wrapper

type InverseExtra (FillStrips typ) extra
type InverseExtra (Array pack property) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

type InverseExtra (Array pack property) extra = extra ~ ()
type InverseExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type InverseExtra (Diagonal typ0 typ1) extra
type InverseExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type InverseExtra (Triangular typ0 typOff typ1) extra
type InverseExtra (Square typ00 measOff vertOff horizOff typ11) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type InverseExtra (Square typ00 measOff vertOff horizOff typ11) extra

inverse :: (Inverse typ, InverseExtra typ xl, InverseExtra typ xu) => (PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas typ xl xu lower upper meas height width a -> QuadraticMeas typ xl xu lower upper meas width height a Source #

data Transposition #

Constructors

NonTransposed 
Transposed 

Instances

Instances details
Monoid Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Semigroup Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Bounded Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Enum Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Show Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier

Eq Transposition 
Instance details

Defined in Numeric.BLAS.Matrix.Modifier