lapack-0.5.0.3: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.Block.Type

Synopsis

Documentation

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

Instances
(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 #

(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 #

(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 (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 #

(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 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 (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 #

(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 #

(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 #

(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 -> () #

(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 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 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 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 (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 fuse xl xu lowerC upperC meas vert horiz height width a lowerA lowerB upperA upperB typA xlA xuA typB xlB xuB. (MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC) => 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) lowerC upperC 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
  • FillStrips :: forall typ extraLower extraUpper lower upper meas vert horiz height width a lower upper xl xu. (Strip lower, Strip upper) => Matrix typ xl xu lower upper meas vert horiz height width a -> Matrix (FillStrips typ) (xl, lower) (xu, upper) Filled Filled meas vert horiz height width a
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 extraLower extraUpper lower upper meas vert horiz height width a xl xu. QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a
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 xl xu 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 (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 typ meas0 extraLower extraUpper lower upper meas1 vert1 horiz1 height width a vert0 horiz0 xl xu. (C vert0, C horiz0) => Map meas0 vert0 horiz0 meas1 vert1 horiz1 height width -> Matrix typ xl xu lower upper meas0 vert0 horiz0 height width a -> Matrix (MapExtent typ meas0) (xl, vert0) (xu, horiz0) lower upper meas1 vert1 horiz1 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
  • Diagonal :: forall typ0 typ1 xl xu lower upper meas vert horiz height width a sh0 sh1 xl0 xu0 xl1 xu1. (C sh0, Eq sh0, C sh1, Eq sh1) => Quadratic typ0 xl0 xu0 lower upper sh0 a -> Quadratic typ1 xl1 xu1 lower upper sh1 a -> Quadratic (Diagonal typ0 typ1) (xl0, xl1) (xu0, xu1) lower upper (sh0 ::+ sh1) 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 (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
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 Diagonal typ0 typ1 Source #

Instances
(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 :: Constraint 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 #

(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 typ1) => Box (Diagonal typ0 typ1) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

Associated Types

type BoxExtra (Diagonal typ0 typ1) extra :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

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

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

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 #

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
  • Diagonal :: forall typ0 typ1 xl xu lower upper meas vert horiz height width a sh0 sh1 xl0 xu0 xl1 xu1. (C sh0, Eq sh0, C sh1, Eq sh1) => Quadratic typ0 xl0 xu0 lower upper sh0 a -> Quadratic typ1 xl1 xu1 lower upper sh1 a -> Quadratic (Diagonal typ0 typ1) (xl0, xl1) (xu0, xu1) lower upper (sh0 ::+ sh1) a
type TransposeExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type TransposeExtra (Diagonal typ0 typ1) extra
type BoxExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Diagonal typ0 typ1) extra
type MultiplySameExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplySameExtra (Diagonal typ0 typ1) extra
type LayoutExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Diagonal typ0 typ1) extra
type FormatExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Diagonal typ0 typ1) extra
type InverseExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type InverseExtra (Diagonal typ0 typ1) extra
type SolveExtra (Diagonal typ0 typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

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

Defined in Numeric.LAPACK.Matrix.Block.Private

type DeterminantExtra (Diagonal typ0 typ1) extra

data Append typ0 typ1 sh0 sh1 Source #

Instances
(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

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

(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 #

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
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 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 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 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 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 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 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 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 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 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

aboveFromFull :: (C height0, Eq height0, C height1, Eq height1, C width, Eq width, Floating a) => General (height0 ::+ height1) width a -> AboveGeneral height0 height1 width a Source #

besideFromFull :: (C height, Eq height, C width0, Eq width0, C width1, Eq width1, Floating a) => General height (width0 ::+ width1) a -> BesideGeneral height width0 width1 a Source #

data Square typ00 measOff vertOff horizOff typ11 Source #

Instances
(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 :: Constraint 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 #

(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 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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

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

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

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 #

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
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 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 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
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 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 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 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 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 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 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 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 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
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 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 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
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 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

data Triangular typ0 typOff typ1 Source #

Instances
(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 :: Constraint 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 #

(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 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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

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

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

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 #

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
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 BoxExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type BoxExtra (Triangular typ0 typOff typ1) 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 LayoutExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type LayoutExtra (Triangular typ0 typOff typ1) 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 SubtractiveExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SubtractiveExtra (Triangular typ0 typOff 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 ScaleExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type ScaleExtra (Triangular typ0 typOff 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 UnpackExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type UnpackExtra (Triangular typ0 typOff 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 PowerExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type PowerExtra (Triangular typ0 typOff 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 MultiplyVectorExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type MultiplyVectorExtra (Triangular typ0 typOff 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 SolveExtra (Triangular typ0 typOff typ1) extra Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Block.Private

type SolveExtra (Triangular typ0 typOff 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

data Symmetric typ0 typOff xlOff xuOff typ1 Source #

It is not necessary that the square blocks on the diagonal are symmetric. But if they are, according specialised algorithms are used.

We have no algorithms that benefit from this structure. Using this data type merely documents the structure and saves a field in the record (which comes in handy for nested block matrices).

Instances
(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 :: Constraint 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 #

(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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 :: Constraint 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 #

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

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

(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 :: Constraint 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 #

(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 :: Constraint 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 #

(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 #

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 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
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
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
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
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
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 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
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
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
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
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
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
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
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

squareFromSymmetric :: (Transpose typOff, TransposeExtra typOff xlOff, TransposeExtra typOff xuOff, Floating a) => Quadratic (Symmetric typ0 typOff xlOff xuOff typ1) (xl0, xl1) (xu0, xu1) lower upper sh a -> Quadratic (Square typ0 Size Big Big typ1) (xl0, xl1, (typOff, xuOff, xlOff)) (xu0, xu1, (typOff, xuOff, xlOff)) lower upper sh a Source #

schurComplement :: (Solve typ11, SolveExtra typ11 xl11, SolveExtra typ11 xu11, Floating a) => Quadratic (Square TypeFull measOff vertOff horizOff typ11) ((), xl11, (TypeFull, (), ())) ((), xu11, (TypeFull, (), ())) Filled Filled (sh0 ::+ sh1) a -> Square sh0 a Source #