Skip to content

Commit a7738e1

Browse files
committed
fix typos in documentations
1 parent 9317095 commit a7738e1

38 files changed

+152
-152
lines changed

SRC/chesv_aa.f

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@
4242
*> matrices.
4343
*>
4444
*> Aasen's algorithm is used to factor A as
45-
*> A = U * T * U**H, if UPLO = 'U', or
45+
*> A = U**H * T * U, if UPLO = 'U', or
4646
*> A = L * T * L**H, if UPLO = 'L',
4747
*> where U (or L) is a product of permutation and unit upper (lower)
4848
*> triangular matrices, and T is Hermitian and tridiagonal. The factored form
@@ -86,7 +86,7 @@
8686
*>
8787
*> On exit, if INFO = 0, the tridiagonal matrix T and the
8888
*> multipliers used to obtain the factor U or L from the
89-
*> factorization A = U*T*U**H or A = L*T*L**H as computed by
89+
*> factorization A = U**H*T*U or A = L*T*L**H as computed by
9090
*> CHETRF_AA.
9191
*> \endverbatim
9292
*>
@@ -230,7 +230,7 @@ SUBROUTINE CHESV_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
230230
RETURN
231231
END IF
232232
*
233-
* Compute the factorization A = U*T*U**H or A = L*T*L**H.
233+
* Compute the factorization A = U**H*T*U or A = L*T*L**H.
234234
*
235235
CALL CHETRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
236236
IF( INFO.EQ.0 ) THEN

SRC/chesv_aa_2stage.f

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@
4343
*> matrices.
4444
*>
4545
*> Aasen's 2-stage algorithm is used to factor A as
46-
*> A = U * T * U**H, if UPLO = 'U', or
46+
*> A = U**H * T * U, if UPLO = 'U', or
4747
*> A = L * T * L**H, if UPLO = 'L',
4848
*> where U (or L) is a product of permutation and unit upper (lower)
4949
*> triangular matrices, and T is Hermitian and band. The matrix T is
@@ -257,7 +257,7 @@ SUBROUTINE CHESV_AA_2STAGE( UPLO, N, NRHS, A, LDA, TB, LTB,
257257
END IF
258258
*
259259
*
260-
* Compute the factorization A = U*T*U**H or A = L*T*L**H.
260+
* Compute the factorization A = U**H*T*U or A = L*T*L**H.
261261
*
262262
CALL CHETRF_AA_2STAGE( UPLO, N, A, LDA, TB, LTB, IPIV, IPIV2,
263263
$ WORK, LWORK, INFO )

SRC/chetrf_aa.f

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@
3737
*> CHETRF_AA computes the factorization of a complex hermitian matrix A
3838
*> using the Aasen's algorithm. The form of the factorization is
3939
*>
40-
*> A = U*T*U**H or A = L*T*L**H
40+
*> A = U**H*T*U or A = L*T*L**H
4141
*>
4242
*> where U (or L) is a product of permutation and unit upper (lower)
4343
*> triangular matrices, and T is a hermitian tridiagonal matrix.
@@ -223,7 +223,7 @@ SUBROUTINE CHETRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
223223
IF( UPPER ) THEN
224224
*
225225
* .....................................................
226-
* Factorize A as L*D*L**H using the upper triangle of A
226+
* Factorize A as U**H*D*U using the upper triangle of A
227227
* .....................................................
228228
*
229229
* copy first row A(1, 1:N) into H(1:n) (stored in WORK(1:N))

SRC/chetrf_aa_2stage.f

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@
3838
*> CHETRF_AA_2STAGE computes the factorization of a real hermitian matrix A
3939
*> using the Aasen's algorithm. The form of the factorization is
4040
*>
41-
*> A = U*T*U**T or A = L*T*L**T
41+
*> A = U**T*T*U or A = L*T*L**T
4242
*>
4343
*> where U (or L) is a product of permutation and unit upper (lower)
4444
*> triangular matrices, and T is a hermitian band matrix with the
@@ -277,7 +277,7 @@ SUBROUTINE CHETRF_AA_2STAGE( UPLO, N, A, LDA, TB, LTB, IPIV,
277277
IF( UPPER ) THEN
278278
*
279279
* .....................................................
280-
* Factorize A as L*D*L**T using the upper triangle of A
280+
* Factorize A as U**T*D*U using the upper triangle of A
281281
* .....................................................
282282
*
283283
DO J = 0, NT-1

SRC/chetrs_aa.f

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@
3737
*> \verbatim
3838
*>
3939
*> CHETRS_AA solves a system of linear equations A*X = B with a complex
40-
*> hermitian matrix A using the factorization A = U*T*U**H or
40+
*> hermitian matrix A using the factorization A = U**H*T*U or
4141
*> A = L*T*L**H computed by CHETRF_AA.
4242
*> \endverbatim
4343
*
@@ -49,7 +49,7 @@
4949
*> UPLO is CHARACTER*1
5050
*> Specifies whether the details of the factorization are stored
5151
*> as an upper or lower triangular matrix.
52-
*> = 'U': Upper triangular, form is A = U*T*U**H;
52+
*> = 'U': Upper triangular, form is A = U**H*T*U;
5353
*> = 'L': Lower triangular, form is A = L*T*L**H.
5454
*> \endverbatim
5555
*>
@@ -200,9 +200,9 @@ SUBROUTINE CHETRS_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB,
200200
*
201201
IF( UPPER ) THEN
202202
*
203-
* Solve A*X = B, where A = U**T*T*U.
203+
* Solve A*X = B, where A = U**H*T*U.
204204
*
205-
* 1) Forward substitution with U**T
205+
* 1) Forward substitution with U**H
206206
*
207207
IF( N.GT.1 ) THEN
208208
*
@@ -216,15 +216,15 @@ SUBROUTINE CHETRS_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB,
216216
K = K + 1
217217
END DO
218218
*
219-
* Compute U**T \ B -> B [ (U**T \P**T * B) ]
219+
* Compute U**H \ B -> B [ (U**H \P**T * B) ]
220220
*
221221
CALL CTRSM( 'L', 'U', 'C', 'U', N-1, NRHS, ONE, A( 1, 2 ),
222222
$ LDA, B( 2, 1 ), LDB)
223223
END IF
224224
*
225225
* 2) Solve with triangular matrix T
226226
*
227-
* Compute T \ B -> B [ T \ (U**T \P**T * B) ]
227+
* Compute T \ B -> B [ T \ (U**H \P**T * B) ]
228228
*
229229
CALL CLACPY( 'F', 1, N, A(1, 1), LDA+1, WORK(N), 1)
230230
IF( N.GT.1 ) THEN
@@ -239,12 +239,12 @@ SUBROUTINE CHETRS_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB,
239239
*
240240
IF( N.GT.1 ) THEN
241241
*
242-
* Compute U \ B -> B [ U \ (T \ (U**T \P**T * B) ) ]
242+
* Compute U \ B -> B [ U \ (T \ (U**H \P**T * B) ) ]
243243
*
244244
CALL CTRSM( 'L', 'U', 'N', 'U', N-1, NRHS, ONE, A( 1, 2 ),
245245
$ LDA, B(2, 1), LDB)
246246
*
247-
* Pivot, P * B -> B [ P * (U \ (T \ (U**T \P**T * B) )) ]
247+
* Pivot, P * B -> B [ P * (U \ (T \ (U**H \P**T * B) )) ]
248248
*
249249
K = N
250250
DO WHILE ( K.GE.1 )
@@ -257,7 +257,7 @@ SUBROUTINE CHETRS_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB,
257257
*
258258
ELSE
259259
*
260-
* Solve A*X = B, where A = L*T*L**T.
260+
* Solve A*X = B, where A = L*T*L**H.
261261
*
262262
* 1) Forward substitution with L
263263
*
@@ -292,16 +292,16 @@ SUBROUTINE CHETRS_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB,
292292
CALL CGTSV(N, NRHS, WORK(1), WORK(N), WORK(2*N), B, LDB,
293293
$ INFO)
294294
*
295-
* 3) Backward substitution with L**T
295+
* 3) Backward substitution with L**H
296296
*
297297
IF( N.GT.1 ) THEN
298298
*
299-
* Compute (L**T \ B) -> B [ L**T \ (T \ (L \P**T * B) ) ]
299+
* Compute (L**H \ B) -> B [ L**H \ (T \ (L \P**T * B) ) ]
300300
*
301301
CALL CTRSM( 'L', 'L', 'C', 'U', N-1, NRHS, ONE, A( 2, 1 ),
302302
$ LDA, B( 2, 1 ), LDB )
303303
*
304-
* Pivot, P * B -> B [ P * (L**T \ (T \ (L \P**T * B) )) ]
304+
* Pivot, P * B -> B [ P * (L**H \ (T \ (L \P**T * B) )) ]
305305
*
306306
K = N
307307
DO WHILE ( K.GE.1 )

SRC/chetrs_aa_2stage.f

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@
3838
*> \verbatim
3939
*>
4040
*> CHETRS_AA_2STAGE solves a system of linear equations A*X = B with a real
41-
*> hermitian matrix A using the factorization A = U*T*U**T or
41+
*> hermitian matrix A using the factorization A = U**T*T*U or
4242
*> A = L*T*L**T computed by CHETRF_AA_2STAGE.
4343
*> \endverbatim
4444
*
@@ -50,7 +50,7 @@
5050
*> UPLO is CHARACTER*1
5151
*> Specifies whether the details of the factorization are stored
5252
*> as an upper or lower triangular matrix.
53-
*> = 'U': Upper triangular, form is A = U*T*U**T;
53+
*> = 'U': Upper triangular, form is A = U**T*T*U;
5454
*> = 'L': Lower triangular, form is A = L*T*L**T.
5555
*> \endverbatim
5656
*>
@@ -210,15 +210,15 @@ SUBROUTINE CHETRS_AA_2STAGE( UPLO, N, NRHS, A, LDA, TB, LTB,
210210
*
211211
IF( UPPER ) THEN
212212
*
213-
* Solve A*X = B, where A = U*T*U**T.
213+
* Solve A*X = B, where A = U**T*T*U.
214214
*
215215
IF( N.GT.NB ) THEN
216216
*
217-
* Pivot, P**T * B
217+
* Pivot, P**T * B -> B
218218
*
219219
CALL CLASWP( NRHS, B, LDB, NB+1, N, IPIV, 1 )
220220
*
221-
* Compute (U**T \P**T * B) -> B [ (U**T \P**T * B) ]
221+
* Compute (U**T \ B) -> B [ (U**T \P**T * B) ]
222222
*
223223
CALL CTRSM( 'L', 'U', 'C', 'U', N-NB, NRHS, ONE, A(1, NB+1),
224224
$ LDA, B(NB+1, 1), LDB)

SRC/csysv_aa.f

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@
4242
*> matrices.
4343
*>
4444
*> Aasen's algorithm is used to factor A as
45-
*> A = U * T * U**T, if UPLO = 'U', or
45+
*> A = U**T * T * U, if UPLO = 'U', or
4646
*> A = L * T * L**T, if UPLO = 'L',
4747
*> where U (or L) is a product of permutation and unit upper (lower)
4848
*> triangular matrices, and T is symmetric tridiagonal. The factored
@@ -86,7 +86,7 @@
8686
*>
8787
*> On exit, if INFO = 0, the tridiagonal matrix T and the
8888
*> multipliers used to obtain the factor U or L from the
89-
*> factorization A = U*T*U**T or A = L*T*L**T as computed by
89+
*> factorization A = U**T*T*U or A = L*T*L**T as computed by
9090
*> CSYTRF.
9191
*> \endverbatim
9292
*>
@@ -230,7 +230,7 @@ SUBROUTINE CSYSV_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
230230
RETURN
231231
END IF
232232
*
233-
* Compute the factorization A = U*T*U**T or A = L*T*L**T.
233+
* Compute the factorization A = U**T*T*U or A = L*T*L**T.
234234
*
235235
CALL CSYTRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
236236
IF( INFO.EQ.0 ) THEN

SRC/csysv_aa_2stage.f

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -43,8 +43,8 @@
4343
*> matrices.
4444
*>
4545
*> Aasen's 2-stage algorithm is used to factor A as
46-
*> A = U * T * U**H, if UPLO = 'U', or
47-
*> A = L * T * L**H, if UPLO = 'L',
46+
*> A = U**T * T * U, if UPLO = 'U', or
47+
*> A = L * T * L**T, if UPLO = 'L',
4848
*> where U (or L) is a product of permutation and unit upper (lower)
4949
*> triangular matrices, and T is symmetric and band. The matrix T is
5050
*> then LU-factored with partial pivoting. The factored form of A
@@ -257,7 +257,7 @@ SUBROUTINE CSYSV_AA_2STAGE( UPLO, N, NRHS, A, LDA, TB, LTB,
257257
END IF
258258
*
259259
*
260-
* Compute the factorization A = U*T*U**H or A = L*T*L**H.
260+
* Compute the factorization A = U**T*T*U or A = L*T*L**T.
261261
*
262262
CALL CSYTRF_AA_2STAGE( UPLO, N, A, LDA, TB, LTB, IPIV, IPIV2,
263263
$ WORK, LWORK, INFO )

SRC/csytrf_aa.f

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@
3737
*> CSYTRF_AA computes the factorization of a complex symmetric matrix A
3838
*> using the Aasen's algorithm. The form of the factorization is
3939
*>
40-
*> A = U*T*U**T or A = L*T*L**T
40+
*> A = U**T*T*U or A = L*T*L**T
4141
*>
4242
*> where U (or L) is a product of permutation and unit upper (lower)
4343
*> triangular matrices, and T is a complex symmetric tridiagonal matrix.
@@ -223,7 +223,7 @@ SUBROUTINE CSYTRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
223223
IF( UPPER ) THEN
224224
*
225225
* .....................................................
226-
* Factorize A as L*D*L**T using the upper triangle of A
226+
* Factorize A as U**T*D*U using the upper triangle of A
227227
* .....................................................
228228
*
229229
* Copy first row A(1, 1:N) into H(1:n) (stored in WORK(1:N))

SRC/csytrf_aa_2stage.f

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@
3838
*> CSYTRF_AA_2STAGE computes the factorization of a complex symmetric matrix A
3939
*> using the Aasen's algorithm. The form of the factorization is
4040
*>
41-
*> A = U*T*U**T or A = L*T*L**T
41+
*> A = U**T*T*U or A = L*T*L**T
4242
*>
4343
*> where U (or L) is a product of permutation and unit upper (lower)
4444
*> triangular matrices, and T is a complex symmetric band matrix with the
@@ -275,7 +275,7 @@ SUBROUTINE CSYTRF_AA_2STAGE( UPLO, N, A, LDA, TB, LTB, IPIV,
275275
IF( UPPER ) THEN
276276
*
277277
* .....................................................
278-
* Factorize A as L*D*L**T using the upper triangle of A
278+
* Factorize A as U**T*D*U using the upper triangle of A
279279
* .....................................................
280280
*
281281
DO J = 0, NT-1

0 commit comments

Comments
 (0)