lapack-0.5: Numerical Linear Algebra using LAPACK
Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.Special

Documentation

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

Instances

Instances details
(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 lowerA lowerB lowerC upperA upperB upperC typA xlA xuA meas vert horiz height fuse a typB xlB xuB width. (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
data Matrix (Inverse typ) extraLower extraUpper lowerf upperf meas vert horiz height width a Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Inverse

data Matrix (Inverse typ) extraLower extraUpper lowerf upperf meas vert horiz height width a where
  • Inverse :: forall typ xl xu upper lower meas width height a. 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 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 vert0 horiz0 meas0 meas1 vert1 horiz1 height width typ xl xu lower upper a. (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 sh0 sh1 typ0 xl0 xu0 lower upper a typ1 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

type Scale sh = Quadratic Scale () () Empty Empty sh Source #

type Inverse typ lower upper sh = Quadratic (Inverse typ) lower upper Filled Filled sh Source #

inverse :: (PowerStrip lower, PowerStrip upper) => QuadraticMeas typ xl xu upper lower meas width height a -> QuadraticMeas (Inverse typ) (xl, lower) (xu, upper) lower upper meas height width a Source #