Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Numeric.LAPACK.Matrix.Type
Synopsis
- data Scale
- data Identity
- data Permutation
- data Product fuse
- data Inverse typ
- data FillStrips typ
- data MapExtent typ meas
Documentation
Instances
Additive Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type AdditiveExtra Scale extra Source # Methods add :: (Measure meas, C vert, C horiz, AdditiveExtra Scale xl, AdditiveExtra Scale xu, C height, Eq height, C width, Eq width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source # | |
Complex Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Methods conjugate :: (Matrix Scale xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source # fromReal :: (Matrix Scale xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source # toComplex :: (Matrix Scale xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source # | |
Homogeneous Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type HomogeneousExtra Scale extra Source # Methods zeroFrom :: (HomogeneousExtra Scale xl, HomogeneousExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source # negate :: (HomogeneousExtra Scale xl, HomogeneousExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source # scaleReal :: (HomogeneousExtra Scale xl, HomogeneousExtra Scale xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => RealOf a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source # | |
MapSquareSize Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
Scale Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type ScaleExtra Scale extra Source # | |
SquareShape Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type SquareShapeExtra Scale extra Source # Methods takeDiagonal :: (SquareShapeExtra Scale xl, SquareShapeExtra Scale xu, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Vector sh a Source # identityFrom :: (SquareShapeExtra Scale xl, SquareShapeExtra Scale xu, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Quadratic Scale xl xu lower upper sh a Source # | |
Subtractive Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type SubtractiveExtra Scale extra Source # Methods sub :: (Measure meas, C vert, C horiz, SubtractiveExtra Scale xl, SubtractiveExtra Scale xu, C height, Eq height, C width, Eq width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Matrix Scale xl xu lower upper meas vert horiz height width a Source # | |
Unpack Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type UnpackExtra Scale extra Source # Methods unpack :: (UnpackExtra Scale xl, UnpackExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source # | |
Determinant Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Divide Associated Types type DeterminantExtra Scale extra Source # Methods determinant :: (DeterminantExtra Scale xl, DeterminantExtra Scale xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> a Source # | |
Inverse Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Divide Associated Types type InverseExtra Scale extra Source # Methods inverse :: (InverseExtra Scale xl, InverseExtra Scale xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas Scale xl xu lower upper meas height width a -> QuadraticMeas Scale xl xu lower upper meas width height a Source # | |
Solve Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Divide Associated Types type SolveExtra Scale extra Source # Methods solve :: (SolveExtra Scale xl, SolveExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveRight :: (SolveExtra Scale xl, SolveExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveLeft :: (SolveExtra Scale xl, SolveExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Scale xl xu lower upper width a -> Full meas vert horiz height width a Source # | |
Indexed Scale Source # | |
MultiplySquare Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type MultiplySquareExtra Scale extra Source # Methods transposableSquare :: (MultiplySquareExtra Scale xl, MultiplySquareExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a squareFull :: (MultiplySquareExtra Scale xl, MultiplySquareExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic Scale xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a fullSquare :: (MultiplySquareExtra Scale xl, MultiplySquareExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Scale xl xu lower upper width a -> Full meas vert horiz height width a | |
MultiplyVector Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type MultiplyVectorExtra Scale extra Source # Methods matrixVector :: (MultiplyVectorExtra Scale xl, MultiplyVectorExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a vectorMatrix :: (MultiplyVectorExtra Scale xl, MultiplyVectorExtra Scale xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix Scale xl xu lower upper meas vert horiz height width a -> Vector width a | |
Power Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type PowerExtra Scale extra Source # Methods square :: (PowerExtra Scale xl, PowerExtra Scale xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Quadratic Scale xl xu lower upper sh a Source # power :: (PowerExtra Scale xl, PowerExtra Scale xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic Scale xl xu lower upper sh a -> Quadratic Scale xl xu lower upper sh a Source # powers1 :: (PowerExtra Scale xl, PowerExtra Scale xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Scale xl xu lower upper sh a -> Stream (Quadratic Scale xl xu lower upper sh a) Source # | |
Box Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Methods extent :: (BoxExtra Scale xl, BoxExtra Scale xu, Measure meas, C vert, C horiz) => Matrix Scale xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source # height :: (BoxExtra Scale xl, BoxExtra Scale xu, Measure meas, C vert, C horiz) => Matrix Scale xl xu lower upper meas vert horiz height width a -> height Source # width :: (BoxExtra Scale xl, BoxExtra Scale xu, Measure meas, C vert, C horiz) => Matrix Scale xl xu lower upper meas vert horiz height width a -> width Source # | |
Format Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type FormatExtra Scale extra Source # | |
Layout Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type LayoutExtra Scale extra Source # | |
MultiplySame Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type MultiplySameExtra Scale extra Source # Methods multiplySame :: (matrix ~ Matrix Scale xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra Scale xl, MultiplySameExtra Scale xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source # | |
ToQuadratic Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Methods heightToQuadratic :: Measure meas => QuadraticMeas Scale xl xu lower upper meas height width a -> Quadratic Scale xl xu lower upper height a Source # widthToQuadratic :: Measure meas => QuadraticMeas Scale xl xu lower upper meas height width a -> Quadratic Scale xl xu lower upper width a Source # | |
Transpose Scale Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type TransposeExtra Scale extra Source # | |
(xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ (), lowerC ~ Empty, upperC ~ Empty) => Multiply Scale xlA xuA Scale xlB xuB lowerC upperC measC Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Methods matrixMatrix :: (Box Scale, Strip lowerA, Strip upperA, Box Scale, Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied Scale xlA xuA Scale xlB xuB lowerC upperC measC ~ typC, MultipliedExtra Scale xlA xuA Scale xlB xuB ~ xlC, MultipliedExtra Scale xuA xlA Scale xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix Scale xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix Scale xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a | |
(Scale property, xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ ()) => Multiply Scale xlA xuA (Array pack property) xlB xuB lowerC upperC measC Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type Multiplied Scale xlA xuA (Array pack property) xlB xuB lowerC upperC measC type MultipliedExtra Scale xlA xuA (Array pack property) xlB xuB Methods matrixMatrix :: (Box Scale, Strip lowerA, Strip upperA, Box (Array pack property), Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied Scale xlA xuA (Array pack property) xlB xuB lowerC upperC measC ~ typC, MultipliedExtra Scale xlA xuA (Array pack property) xlB xuB ~ xlC, MultipliedExtra Scale xuA xlA (Array pack property) xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix Scale xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix (Array pack property) xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a | |
(Scale property, xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ ()) => Multiply (Array pack property) xlA xuA Scale xlB xuB lowerC upperC measC Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type Multiplied (Array pack property) xlA xuA Scale xlB xuB lowerC upperC measC type MultipliedExtra (Array pack property) xlA xuA Scale xlB xuB Methods matrixMatrix :: (Box (Array pack property), Strip lowerA, Strip upperA, Box Scale, Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied (Array pack property) xlA xuA Scale xlB xuB lowerC upperC measC ~ typC, MultipliedExtra (Array pack property) xlA xuA Scale xlB xuB ~ xlC, MultipliedExtra (Array pack property) xuA xlA Scale xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix (Array pack property) xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix Scale xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a | |
(C height, Show height, Show a) => Show (Matrix Scale xl xu lower upper meas vert horiz height width a) Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
data Matrix Scale xl xu lower upper meas vert horiz height width a Source # | |
type AdditiveExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type HomogeneousExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type ScaleExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type SquareShapeExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type SubtractiveExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type UnpackExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type DeterminantExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Divide | |
type InverseExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Divide | |
type SolveExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Divide | |
type MultiplySquareExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply | |
type MultiplyVectorExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply | |
type PowerExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply | |
type BoxExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type FormatExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type LayoutExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type MultiplySameExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type TransposeExtra Scale extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private |
Instances
Box Identity Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Methods extent :: (BoxExtra Identity xl, BoxExtra Identity xu, Measure meas, C vert, C horiz) => Matrix Identity xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source # height :: (BoxExtra Identity xl, BoxExtra Identity xu, Measure meas, C vert, C horiz) => Matrix Identity xl xu lower upper meas vert horiz height width a -> height Source # width :: (BoxExtra Identity xl, BoxExtra Identity xu, Measure meas, C vert, C horiz) => Matrix Identity xl xu lower upper meas vert horiz height width a -> width Source # | |
ToQuadratic Identity Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Methods heightToQuadratic :: Measure meas => QuadraticMeas Identity xl xu lower upper meas height width a -> Quadratic Identity xl xu lower upper height a Source # widthToQuadratic :: Measure meas => QuadraticMeas Identity xl xu lower upper meas height width a -> Quadratic Identity xl xu lower upper width a Source # | |
Transpose Identity Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type TransposeExtra Identity extra Source # | |
data Matrix Identity xl xu lower upper meas vert horiz height width a Source # | |
type BoxExtra Identity extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type TransposeExtra Identity extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private |
data Permutation Source #
Instances
Complex Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Class Methods conjugate :: (Matrix Permutation xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source # fromReal :: (Matrix Permutation xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source # toComplex :: (Matrix Permutation xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source # | |
MapSquareSize Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Class Methods mapSquareSize :: (C shA, C shB) => (shA -> shB) -> Quadratic Permutation xl xu lower upper shA a -> Quadratic Permutation xl xu lower upper shB a Source # | |
SquareShape Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type SquareShapeExtra Permutation extra Source # Methods takeDiagonal :: (SquareShapeExtra Permutation xl, SquareShapeExtra Permutation xu, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Vector sh a Source # identityFrom :: (SquareShapeExtra Permutation xl, SquareShapeExtra Permutation xu, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Quadratic Permutation xl xu lower upper sh a Source # | |
Unpack Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Class Associated Types type UnpackExtra Permutation extra Source # Methods unpack :: (UnpackExtra Permutation xl, UnpackExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source # | |
Determinant Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Divide Associated Types type DeterminantExtra Permutation extra Source # Methods determinant :: (DeterminantExtra Permutation xl, DeterminantExtra Permutation xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> a Source # | |
Inverse Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Divide Associated Types type InverseExtra Permutation extra Source # Methods inverse :: (InverseExtra Permutation xl, InverseExtra Permutation xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas Permutation xl xu lower upper meas height width a -> QuadraticMeas Permutation xl xu lower upper meas width height a Source # | |
Solve Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Divide Associated Types type SolveExtra Permutation extra Source # Methods solve :: (SolveExtra Permutation xl, SolveExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveRight :: (SolveExtra Permutation xl, SolveExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveLeft :: (SolveExtra Permutation xl, SolveExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Permutation xl xu lower upper width a -> Full meas vert horiz height width a Source # | |
Indexed Permutation Source # | |
MultiplySquare Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type MultiplySquareExtra Permutation extra Source # Methods transposableSquare :: (MultiplySquareExtra Permutation xl, MultiplySquareExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a squareFull :: (MultiplySquareExtra Permutation xl, MultiplySquareExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic Permutation xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a fullSquare :: (MultiplySquareExtra Permutation xl, MultiplySquareExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic Permutation xl xu lower upper width a -> Full meas vert horiz height width a | |
MultiplyVector Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type MultiplyVectorExtra Permutation extra Source # Methods matrixVector :: (MultiplyVectorExtra Permutation xl, MultiplyVectorExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a vectorMatrix :: (MultiplyVectorExtra Permutation xl, MultiplyVectorExtra Permutation xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> Vector width a | |
Power Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type PowerExtra Permutation extra Source # Methods square :: (PowerExtra Permutation xl, PowerExtra Permutation xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Quadratic Permutation xl xu lower upper sh a Source # power :: (PowerExtra Permutation xl, PowerExtra Permutation xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic Permutation xl xu lower upper sh a -> Quadratic Permutation xl xu lower upper sh a Source # powers1 :: (PowerExtra Permutation xl, PowerExtra Permutation xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic Permutation xl xu lower upper sh a -> Stream (Quadratic Permutation xl xu lower upper sh a) Source # | |
Box Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type BoxExtra Permutation extra Source # Methods extent :: (BoxExtra Permutation xl, BoxExtra Permutation xu, Measure meas, C vert, C horiz) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source # height :: (BoxExtra Permutation xl, BoxExtra Permutation xu, Measure meas, C vert, C horiz) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> height Source # width :: (BoxExtra Permutation xl, BoxExtra Permutation xu, Measure meas, C vert, C horiz) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> width Source # | |
Format Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type FormatExtra Permutation extra Source # Methods format :: (FormatExtra Permutation xl, FormatExtra Permutation xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix Permutation xl xu lower upper meas vert horiz height width a -> out Source # | |
Layout Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type LayoutExtra Permutation extra Source # Methods layout :: (LayoutExtra Permutation xl, LayoutExtra Permutation xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source # | |
MultiplySame Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type MultiplySameExtra Permutation extra Source # Methods multiplySame :: (matrix ~ Matrix Permutation xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra Permutation xl, MultiplySameExtra Permutation xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source # | |
ToQuadratic Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Methods heightToQuadratic :: Measure meas => QuadraticMeas Permutation xl xu lower upper meas height width a -> Quadratic Permutation xl xu lower upper height a Source # widthToQuadratic :: Measure meas => QuadraticMeas Permutation xl xu lower upper meas height width a -> Quadratic Permutation xl xu lower upper width a Source # | |
Transpose Permutation Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type TransposeExtra Permutation extra Source # Methods transpose :: (TransposeExtra Permutation xl, TransposeExtra Permutation xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> Matrix Permutation xu xl upper lower meas horiz vert width height a Source # | |
(xlA ~ (), xuA ~ (), xlB ~ (), xuB ~ ()) => Multiply Permutation xlA xuA Permutation xlB xuB lowerC upperC measC Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply Associated Types type Multiplied Permutation xlA xuA Permutation xlB xuB lowerC upperC measC type MultipliedExtra Permutation xlA xuA Permutation xlB xuB Methods matrixMatrix :: (Box Permutation, Strip lowerA, Strip upperA, Box Permutation, Strip lowerB, Strip upperB, Box typC, Strip lowerC, Strip upperC, Multiplied Permutation xlA xuA Permutation xlB xuB lowerC upperC measC ~ typC, MultipliedExtra Permutation xlA xuA Permutation xlB xuB ~ xlC, MultipliedExtra Permutation xuA xlA Permutation xuB xlB ~ xuC, MultipliedStrip lowerA lowerB ~ lowerC, MultipliedStrip lowerB lowerA ~ lowerC, MultipliedStrip upperA upperB ~ upperC, MultipliedStrip upperB upperA ~ upperC, MultipliedBands lowerA lowerB ~ lowerC, MultipliedBands lowerB lowerA ~ lowerC, MultipliedBands upperA upperB ~ upperC, MultipliedBands upperB upperA ~ upperC, Measure measA, C vertA, C horizA, Measure measB, C vertB, C horizB, MultiplyMeasure measA measB ~ measC, MultiplyMeasure measB measA ~ measC, Multiply vertA vertB ~ vertC, Multiply vertB vertA ~ vertC, Multiply horizA horizB ~ horizC, Multiply horizB horizA ~ horizC, C height, C fuse, Eq fuse, C width, Floating a) => Matrix Permutation xlA xuA lowerA upperA measA vertA horizA height fuse a -> Matrix Permutation xlB xuB lowerB upperB measB vertB horizB fuse width a -> Matrix typC xlC xuC lowerC upperC measC vertC horizC height width a | |
(C height, Show height) => Show (Matrix Permutation xl xu lower upper meas vert horiz height width a) Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
(C height, Eq height) => Eq (Matrix Permutation xl xu lower upper meas vert horiz height width a) Source # | |
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 # | |
data Matrix Permutation xl xu lower upper meas vert horiz height width a Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private data Matrix Permutation xl xu lower upper meas vert horiz height width a where
| |
type SquareShapeExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type UnpackExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Class | |
type DeterminantExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Divide | |
type InverseExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Divide | |
type SolveExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Divide | |
type MultiplySquareExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply | |
type MultiplyVectorExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply | |
type PowerExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply | |
type BoxExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type FormatExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type LayoutExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type MultiplySameExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type TransposeExtra Permutation extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private |
Instances
Eq fuse => Box (Product fuse) Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Methods extent :: (BoxExtra (Product fuse) xl, BoxExtra (Product fuse) xu, Measure meas, C vert, C horiz) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source # height :: (BoxExtra (Product fuse) xl, BoxExtra (Product fuse) xu, Measure meas, C vert, C horiz) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> height Source # width :: (BoxExtra (Product fuse) xl, BoxExtra (Product fuse) xu, Measure meas, C vert, C horiz) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> width Source # | |
(C fuse, Eq fuse) => Transpose (Product fuse) Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private Associated Types type TransposeExtra (Product fuse) extra Source # Methods transpose :: (TransposeExtra (Product fuse) xl, TransposeExtra (Product fuse) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Product fuse) xl xu lower upper meas vert horiz height width a -> Matrix (Product fuse) xu xl upper lower meas horiz vert width height a Source # | |
data Matrix (Product fuse) xl xu lower upper meas vert horiz height width a Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private data Matrix (Product fuse) xl xu lower upper meas vert horiz height width a where
| |
type BoxExtra (Product fuse) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private | |
type TransposeExtra (Product fuse) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Type.Private |
You may wrap non-diagonal band matrices in FillStrips
first
in order to meet the PowerStrip
constraint.
Instances
Complex typ => Complex (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Methods conjugate :: (Matrix (Inverse typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source # fromReal :: (Matrix (Inverse typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source # toComplex :: (Matrix (Inverse typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source # | |
Determinant typ => Determinant (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type DeterminantExtra (Inverse typ) extra Source # Methods determinant :: (DeterminantExtra (Inverse typ) xl, DeterminantExtra (Inverse typ) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (Inverse typ) xl xu lower upper sh a -> a Source # | |
(Inverse typ, MultiplySquare typ, ToQuadratic typ) => Inverse (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type InverseExtra (Inverse typ) extra Source # Methods inverse :: (InverseExtra (Inverse typ) xl, InverseExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> QuadraticMeas (Inverse typ) xl xu lower upper meas width height a Source # | |
(MultiplySquare typ, ToQuadratic typ) => Solve (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type SolveExtra (Inverse typ) extra Source # Methods solve :: (SolveExtra (Inverse typ) xl, SolveExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveRight :: (SolveExtra (Inverse typ) xl, SolveExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveLeft :: (SolveExtra (Inverse typ) xl, SolveExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Inverse typ) xl xu lower upper width a -> Full meas vert horiz height width a Source # | |
(Solve typ, ToQuadratic typ) => MultiplySquare (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type MultiplySquareExtra (Inverse typ) extra Source # Methods transposableSquare :: (MultiplySquareExtra (Inverse typ) xl, MultiplySquareExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a squareFull :: (MultiplySquareExtra (Inverse typ) xl, MultiplySquareExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (Inverse typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a fullSquare :: (MultiplySquareExtra (Inverse typ) xl, MultiplySquareExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (Inverse typ) xl xu lower upper width a -> Full meas vert horiz height width a | |
(Solve typ, ToQuadratic typ) => MultiplyVector (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type MultiplyVectorExtra (Inverse typ) extra Source # Methods matrixVector :: (MultiplyVectorExtra (Inverse typ) xl, MultiplyVectorExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a vectorMatrix :: (MultiplyVectorExtra (Inverse typ) xl, MultiplyVectorExtra (Inverse typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Vector width a | |
Power typ => Power (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type PowerExtra (Inverse typ) extra Source # Methods square :: (PowerExtra (Inverse typ) xl, PowerExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Inverse typ) xl xu lower upper sh a -> Quadratic (Inverse typ) xl xu lower upper sh a Source # power :: (PowerExtra (Inverse typ) xl, PowerExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (Inverse typ) xl xu lower upper sh a -> Quadratic (Inverse typ) xl xu lower upper sh a Source # powers1 :: (PowerExtra (Inverse typ) xl, PowerExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (Inverse typ) xl xu lower upper sh a -> Stream (Quadratic (Inverse typ) xl xu lower upper sh a) Source # | |
Box typ => Box (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Methods extent :: (BoxExtra (Inverse typ) xl, BoxExtra (Inverse typ) xu, Measure meas, C vert, C horiz) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source # height :: (BoxExtra (Inverse typ) xl, BoxExtra (Inverse typ) xu, Measure meas, C vert, C horiz) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> height Source # width :: (BoxExtra (Inverse typ) xl, BoxExtra (Inverse typ) xu, Measure meas, C vert, C horiz) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> width Source # | |
MultiplySame typ => MultiplySame (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type MultiplySameExtra (Inverse typ) extra Source # Methods multiplySame :: (matrix ~ Matrix (Inverse typ) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (Inverse typ) xl, MultiplySameExtra (Inverse typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source # | |
ToQuadratic typ => ToQuadratic (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Methods heightToQuadratic :: Measure meas => QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> Quadratic (Inverse typ) xl xu lower upper height a Source # widthToQuadratic :: Measure meas => QuadraticMeas (Inverse typ) xl xu lower upper meas height width a -> Quadratic (Inverse typ) xl xu lower upper width a Source # | |
Transpose typ => Transpose (Inverse typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse Associated Types type TransposeExtra (Inverse typ) extra Source # Methods transpose :: (TransposeExtra (Inverse typ) xl, TransposeExtra (Inverse typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (Inverse typ) xl xu lower upper meas vert horiz height width a -> Matrix (Inverse typ) xu xl upper lower meas horiz vert width height a Source # | |
data Matrix (Inverse typ) extraLower extraUpper lowerf upperf meas vert horiz height width a Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type DeterminantExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type InverseExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type SolveExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type MultiplySquareExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type MultiplyVectorExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type PowerExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type BoxExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type MultiplySameExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse | |
type TransposeExtra (Inverse typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Inverse |
data FillStrips typ Source #
Instances
Complex typ => Complex (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Methods conjugate :: (Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source # fromReal :: (Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source # toComplex :: (Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width ~ matrix, Measure meas, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source # | |
Unpack typ => Unpack (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type UnpackExtra (FillStrips typ) extra Source # Methods unpack :: (UnpackExtra (FillStrips typ) xl, UnpackExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas vert horiz height width a Source # | |
Determinant typ => Determinant (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type DeterminantExtra (FillStrips typ) extra Source # Methods determinant :: (DeterminantExtra (FillStrips typ) xl, DeterminantExtra (FillStrips typ) xu, Strip lower, Strip upper, C sh, Floating a) => Quadratic (FillStrips typ) xl xu lower upper sh a -> a Source # | |
(Inverse typ, ToQuadratic typ) => Inverse (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type InverseExtra (FillStrips typ) extra Source # Methods inverse :: (InverseExtra (FillStrips typ) xl, InverseExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C height, C width, Floating a) => QuadraticMeas (FillStrips typ) xl xu lower upper meas height width a -> QuadraticMeas (FillStrips typ) xl xu lower upper meas width height a Source # | |
(Solve typ, ToQuadratic typ) => Solve (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type SolveExtra (FillStrips typ) extra Source # Methods solve :: (SolveExtra (FillStrips typ) xl, SolveExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Transposition -> Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveRight :: (SolveExtra (FillStrips typ) xl, SolveExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a Source # solveLeft :: (SolveExtra (FillStrips typ) xl, SolveExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (FillStrips typ) xl xu lower upper width a -> Full meas vert horiz height width a Source # | |
(MultiplySquare typ, ToQuadratic typ) => MultiplySquare (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type MultiplySquareExtra (FillStrips typ) extra Source # Methods transposableSquare :: (MultiplySquareExtra (FillStrips typ) xl, MultiplySquareExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Transposition -> Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a squareFull :: (MultiplySquareExtra (FillStrips typ) xl, MultiplySquareExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, Eq height, C width, Floating a) => Quadratic (FillStrips typ) xl xu lower upper height a -> Full meas vert horiz height width a -> Full meas vert horiz height width a fullSquare :: (MultiplySquareExtra (FillStrips typ) xl, MultiplySquareExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Full meas vert horiz height width a -> Quadratic (FillStrips typ) xl xu lower upper width a -> Full meas vert horiz height width a | |
(MultiplyVector typ, ToQuadratic typ) => MultiplyVector (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type MultiplyVectorExtra (FillStrips typ) extra Source # Methods matrixVector :: (MultiplyVectorExtra (FillStrips typ) xl, MultiplyVectorExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Vector width a -> Vector height a vectorMatrix :: (MultiplyVectorExtra (FillStrips typ) xl, MultiplyVectorExtra (FillStrips typ) xu, Strip lower, Strip upper, Measure meas, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Vector width a | |
Power typ => Power (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type PowerExtra (FillStrips typ) extra Source # Methods square :: (PowerExtra (FillStrips typ) xl, PowerExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (FillStrips typ) xl xu lower upper sh a -> Quadratic (FillStrips typ) xl xu lower upper sh a Source # power :: (PowerExtra (FillStrips typ) xl, PowerExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Integer -> Quadratic (FillStrips typ) xl xu lower upper sh a -> Quadratic (FillStrips typ) xl xu lower upper sh a Source # powers1 :: (PowerExtra (FillStrips typ) xl, PowerExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, C sh, Floating a) => Quadratic (FillStrips typ) xl xu lower upper sh a -> Stream (Quadratic (FillStrips typ) xl xu lower upper sh a) Source # | |
Box typ => Box (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type BoxExtra (FillStrips typ) extra Source # Methods extent :: (BoxExtra (FillStrips typ) xl, BoxExtra (FillStrips typ) xu, Measure meas, C vert, C horiz) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Extent meas vert horiz height width Source # height :: (BoxExtra (FillStrips typ) xl, BoxExtra (FillStrips typ) xu, Measure meas, C vert, C horiz) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> height Source # width :: (BoxExtra (FillStrips typ) xl, BoxExtra (FillStrips typ) xu, Measure meas, C vert, C horiz) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> width Source # | |
Format typ => Format (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type FormatExtra (FillStrips typ) extra Source # Methods format :: (FormatExtra (FillStrips typ) xl, FormatExtra (FillStrips typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a, Output out) => Config -> Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> out Source # | |
Layout typ => Layout (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type LayoutExtra (FillStrips typ) extra Source # Methods layout :: (LayoutExtra (FillStrips typ) xl, LayoutExtra (FillStrips typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Array (height, width) (Separator, Maybe (Style, a)) Source # | |
MultiplySame typ => MultiplySame (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type MultiplySameExtra (FillStrips typ) extra Source # Methods multiplySame :: (matrix ~ Matrix (FillStrips typ) xl xu lower upper meas vert horiz sh sh a, MultiplySameExtra (FillStrips typ) xl, MultiplySameExtra (FillStrips typ) xu, PowerStrip lower, PowerStrip upper, Measure meas, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source # | |
ToQuadratic typ => ToQuadratic (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Methods heightToQuadratic :: Measure meas => QuadraticMeas (FillStrips typ) xl xu lower upper meas height width a -> Quadratic (FillStrips typ) xl xu lower upper height a Source # widthToQuadratic :: Measure meas => QuadraticMeas (FillStrips typ) xl xu lower upper meas height width a -> Quadratic (FillStrips typ) xl xu lower upper width a Source # | |
Transpose typ => Transpose (FillStrips typ) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type TransposeExtra (FillStrips typ) extra Source # Methods transpose :: (TransposeExtra (FillStrips typ) xl, TransposeExtra (FillStrips typ) xu, Measure meas, C vert, C horiz, C height, C width, Floating a) => Matrix (FillStrips typ) xl xu lower upper meas vert horiz height width a -> Matrix (FillStrips typ) xu xl upper lower meas horiz vert width height a Source # | |
data Matrix (FillStrips typ) extraLower extraUpper lower upper meas vert horiz height width a Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper data Matrix (FillStrips typ) extraLower extraUpper lower upper meas vert horiz height width a where
| |
type UnpackExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type DeterminantExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type InverseExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type SolveExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type MultiplySquareExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type MultiplyVectorExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type PowerExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type BoxExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type FormatExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type LayoutExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type MultiplySameExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type TransposeExtra (FillStrips typ) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper |
data MapExtent typ meas Source #
Instances
(Complex typ, Measure meas) => Complex (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Methods conjugate :: (Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width ~ matrix, Measure meas0, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix a Source # fromReal :: (Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width ~ matrix, Measure meas0, C vert, C horiz, C height, C width, Floating a) => matrix (RealOf a) -> matrix a Source # toComplex :: (Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width ~ matrix, Measure meas0, C vert, C horiz, C height, C width, Floating a) => matrix a -> matrix (ComplexOf a) Source # | |
(Unpack typ, Measure meas) => Unpack (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type UnpackExtra (MapExtent typ meas) extra Source # Methods unpack :: (UnpackExtra (MapExtent typ meas) xl, UnpackExtra (MapExtent typ meas) xu, Strip lower, Strip upper, Measure meas0, C vert, C horiz, C height, C width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> ArrayMatrix Unpacked Arbitrary lower upper meas0 vert horiz height width a Source # | |
(MultiplyVector typ, ToQuadratic typ, Measure meas) => MultiplyVector (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type MultiplyVectorExtra (MapExtent typ meas) extra Source # Methods matrixVector :: (MultiplyVectorExtra (MapExtent typ meas) xl, MultiplyVectorExtra (MapExtent typ meas) xu, Strip lower, Strip upper, Measure meas0, C vert, C horiz, C height, C width, Eq width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Vector width a -> Vector height a vectorMatrix :: (MultiplyVectorExtra (MapExtent typ meas) xl, MultiplyVectorExtra (MapExtent typ meas) xu, Strip lower, Strip upper, Measure meas0, C vert, C horiz, C height, C width, Eq height, Floating a) => Vector height a -> Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Vector width a | |
(Box typ, Measure meas) => Box (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Methods extent :: (BoxExtra (MapExtent typ meas) xl, BoxExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Extent meas0 vert horiz height width Source # height :: (BoxExtra (MapExtent typ meas) xl, BoxExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> height Source # width :: (BoxExtra (MapExtent typ meas) xl, BoxExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> width Source # | |
(Format typ, Measure meas) => Format (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type FormatExtra (MapExtent typ meas) extra Source # | |
(Layout typ, Measure meas) => Layout (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type LayoutExtra (MapExtent typ meas) extra Source # | |
(MultiplySame typ, Measure meas) => MultiplySame (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type MultiplySameExtra (MapExtent typ meas) extra Source # Methods multiplySame :: (matrix ~ Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz sh sh a, MultiplySameExtra (MapExtent typ meas) xl, MultiplySameExtra (MapExtent typ meas) xu, PowerStrip lower, PowerStrip upper, Measure meas0, C vert, C horiz, C sh, Eq sh, Floating a) => matrix -> matrix -> matrix Source # | |
(Transpose typ, Measure meas) => Transpose (MapExtent typ meas) Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper Associated Types type TransposeExtra (MapExtent typ meas) extra Source # Methods transpose :: (TransposeExtra (MapExtent typ meas) xl, TransposeExtra (MapExtent typ meas) xu, Measure meas0, C vert, C horiz, C height, C width, Floating a) => Matrix (MapExtent typ meas) xl xu lower upper meas0 vert horiz height width a -> Matrix (MapExtent typ meas) xu xl upper lower meas0 horiz vert width height a Source # | |
data Matrix (MapExtent typ meas) extraLower extraUpper lower upper meas1 vert1 horiz1 height width a Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper data Matrix (MapExtent typ meas) extraLower extraUpper lower upper meas1 vert1 horiz1 height width a where
| |
type UnpackExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type MultiplyVectorExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type BoxExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type FormatExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type LayoutExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type MultiplySameExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper | |
type TransposeExtra (MapExtent typ meas) extra Source # | |
Defined in Numeric.LAPACK.Matrix.Wrapper |