Skip to content

Commit

Permalink
style: Fix typo in docstrings
Browse files Browse the repository at this point in the history
Issues were identified using the open-source tool codespell [1]
running the following command from the source directory:

[1] https://github.com/codespell-project/codespell#readme


$ codespell -q6 \
  --skip=".git,Doxyfile,Doxyfile_man,CMakeLists.txt,Makefile" \
  --regex="\w[a-z\-\_]+" \
  --ignore-words-list="fro,ith,nd,noe,numer" \
  --summary

[...]

-------8<-------
SUMMARY:
acoording     2
agressive     8
ajust        12
arithmetics   5
comleted      2
contraints    8
equaly        4
everytime     4
febuary       1
matix         8
otherwize     4
overwrittes   4
owerflow      8
parmeter      4
permutaions  32
specturm      8
  • Loading branch information
jcfr committed Nov 7, 2018
1 parent 7f2a965 commit 6e26afd
Show file tree
Hide file tree
Showing 70 changed files with 118 additions and 118 deletions.
2 changes: 1 addition & 1 deletion SRC/VARIANTS/README
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ References:For a more detailed description please refer to
=========

These variants are compiled by default in the build process but they are not tested by default.
The build process creates one new library per variants in the four arithmetics (single real/double real/single complex/double complex).
The build process creates one new library per variants in the four arithmetic (single real/double real/single complex/double complex).
The libraries are in the SRC/VARIANTS directory.

Corresponding libraries created in SRC/VARIANTS:
Expand Down
4 changes: 2 additions & 2 deletions SRC/cgejsv.f
Original file line number Diff line number Diff line change
Expand Up @@ -1763,7 +1763,7 @@ SUBROUTINE CGEJSV( JOBA, JOBU, JOBV, JOBR, JOBT, JOBP,
ELSE
*
* .. ill-conditioned case: second QRF with pivoting
* Note that windowed pivoting would be equaly good
* Note that windowed pivoting would be equally good
* numerically, and more run-time efficient. So, in
* an optimal implementation, the next call to CGEQP3
* should be replaced with eg. CALL CGEQPX (ACM TOMS #782)
Expand Down Expand Up @@ -1821,7 +1821,7 @@ SUBROUTINE CGEJSV( JOBA, JOBU, JOBV, JOBR, JOBT, JOBP,
*
IF ( CONDR2 .GE. COND_OK ) THEN
* .. save the Householder vectors used for Q3
* (this overwrittes the copy of R2, as it will not be
* (this overwrites the copy of R2, as it will not be
* needed in this branch, but it does not overwritte the
* Huseholder vectors of Q2.).
CALL CLACPY( 'U', NR, NR, V, LDV, CWORK(2*N+1), N )
Expand Down
2 changes: 1 addition & 1 deletion SRC/cgesc2.f
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,7 @@
*> \verbatim
*> SCALE is REAL
*> On exit, SCALE contains the scale factor. SCALE is chosen
*> 0 <= SCALE <= 1 to prevent owerflow in the solution.
*> 0 <= SCALE <= 1 to prevent overflow in the solution.
*> \endverbatim
*
* Authors:
Expand Down
8 changes: 4 additions & 4 deletions SRC/cgesvdq.f
Original file line number Diff line number Diff line change
Expand Up @@ -717,7 +717,7 @@ SUBROUTINE CGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
*
* Standard absolute error bound suffices. All sigma_i with
* sigma_i < N*EPS*||A||_F are flushed to zero. This is an
* agressive enforcement of lower numerical rank by introducing a
* aggressive enforcement of lower numerical rank by introducing a
* backward error of the order of N*EPS*||A||_F.
NR = 1
RTMP = SQRT(REAL(N))*EPSLN
Expand All @@ -728,7 +728,7 @@ SUBROUTINE CGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
3002 CONTINUE
*
ELSEIF ( ACCLM ) THEN
* .. similarly as above, only slightly more gentle (less agressive).
* .. similarly as above, only slightly more gentle (less aggressive).
* Sudden drop on the diagonal of R is used as the criterion for being
* close-to-rank-deficient. The threshold is set to EPSLN=SLAMCH('E').
* [[This can be made more flexible by replacing this hard-coded value
Expand Down Expand Up @@ -1039,7 +1039,7 @@ SUBROUTINE CGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
* vectors of R**H
* [[The optimal ratio N/NR for using QRF instead of padding
* with zeros. Here hard coded to 2; it must be at least
* two due to work space contraints.]]
* two due to work space constraints.]]
* OPTRATIO = ILAENV(6, 'CGESVD', 'S' // 'O', NR,N,0,0)
* OPTRATIO = MAX( OPTRATIO, 2 )
OPTRATIO = 2
Expand Down Expand Up @@ -1156,7 +1156,7 @@ SUBROUTINE CGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
* is then N1 (N or M)
* [[The optimal ratio N/NR for using LQ instead of padding
* with zeros. Here hard coded to 2; it must be at least
* two due to work space contraints.]]
* two due to work space constraints.]]
* OPTRATIO = ILAENV(6, 'CGESVD', 'S' // 'O', NR,N,0,0)
* OPTRATIO = MAX( OPTRATIO, 2 )
OPTRATIO = 2
Expand Down
2 changes: 1 addition & 1 deletion SRC/cgsvj1.f
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@
*> In terms of the columns of A, the first N1 columns are rotated 'against'
*> the remaining N-N1 columns, trying to increase the angle between the
*> corresponding subspaces. The off-diagonal block is N1-by(N-N1) and it is
*> tiled using quadratic tiles of side KBL. Here, KBL is a tunning parmeter.
*> tiled using quadratic tiles of side KBL. Here, KBL is a tunning parameter.
*> The number of sweeps is given in NSWEEP and the orthogonality threshold
*> is given in TOL.
*> \endverbatim
Expand Down
2 changes: 1 addition & 1 deletion SRC/chetrd_he2hb.f
Original file line number Diff line number Diff line change
Expand Up @@ -363,7 +363,7 @@ SUBROUTINE CHETRD_HE2HB( UPLO, N, KD, A, LDA, AB, LDAB, TAU,
*
*
* Set the workspace of the triangular matrix T to zero once such a
* way everytime T is generated the upper/lower portion will be always zero
* way every time T is generated the upper/lower portion will be always zero
*
CALL CLASET( "A", LDT, KD, ZERO, ZERO, WORK( TPOS ), LDT )
*
Expand Down
4 changes: 2 additions & 2 deletions SRC/chetrf_aa.f
Original file line number Diff line number Diff line change
Expand Up @@ -256,7 +256,7 @@ SUBROUTINE CHETRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
$ A( MAX(1, J), J+1 ), LDA,
$ IPIV( J+1 ), WORK, N, WORK( N*NB+1 ) )
*
* Ajust IPIV and apply it back (J-th step picks (J+1)-th pivot)
* Adjust IPIV and apply it back (J-th step picks (J+1)-th pivot)
*
DO J2 = J+2, MIN(N, J+JB+1)
IPIV( J2 ) = IPIV( J2 ) + J
Expand Down Expand Up @@ -376,7 +376,7 @@ SUBROUTINE CHETRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
$ A( J+1, MAX(1, J) ), LDA,
$ IPIV( J+1 ), WORK, N, WORK( N*NB+1 ) )
*
* Ajust IPIV and apply it back (J-th step picks (J+1)-th pivot)
* Adjust IPIV and apply it back (J-th step picks (J+1)-th pivot)
*
DO J2 = J+2, MIN(N, J+JB+1)
IPIV( J2 ) = IPIV( J2 ) + J
Expand Down
2 changes: 1 addition & 1 deletion SRC/chseqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@
*> \verbatim
*> LDZ is INTEGER
*> The leading dimension of the array Z. if COMPZ = 'I' or
*> COMPZ = 'V', then LDZ >= MAX(1,N). Otherwize, LDZ >= 1.
*> COMPZ = 'V', then LDZ >= MAX(1,N). Otherwise, LDZ >= 1.
*> \endverbatim
*>
*> \param[out] WORK
Expand Down
2 changes: 1 addition & 1 deletion SRC/cla_wwaddw.f
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@
*> CLA_WWADDW adds a vector W into a doubled-single vector (X, Y).
*>
*> This works for all extant IBM's hex and binary floating point
*> arithmetics, but not for decimal.
*> arithmetic, but not for decimal.
*> \endverbatim
*
* Arguments:
Expand Down
2 changes: 1 addition & 1 deletion SRC/clahqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@
*> If INFO > 0 and WANTT is .FALSE., then on exit,
*> the remaining unconverged eigenvalues are the
*> eigenvalues of the upper Hessenberg matrix
*> rows and columns ILO thorugh INFO of the final,
*> rows and columns ILO through INFO of the final,
*> output value of H.
*>
*> If INFO > 0 and WANTT is .TRUE., then on exit
Expand Down
8 changes: 4 additions & 4 deletions SRC/csyconvf.f
Original file line number Diff line number Diff line change
Expand Up @@ -294,7 +294,7 @@ SUBROUTINE CSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Convert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of upper part of A
* Apply permutations to submatrices of upper part of A
* in factorization order where i decreases from N to 1
*
I = N
Expand Down Expand Up @@ -347,7 +347,7 @@ SUBROUTINE CSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Revert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of upper part of A
* Apply permutations to submatrices of upper part of A
* in reverse factorization order where i increases from 1 to N
*
I = 1
Expand Down Expand Up @@ -438,7 +438,7 @@ SUBROUTINE CSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Convert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of lower part of A
* Apply permutations to submatrices of lower part of A
* in factorization order where k increases from 1 to N
*
I = 1
Expand Down Expand Up @@ -491,7 +491,7 @@ SUBROUTINE CSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Revert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of lower part of A
* Apply permutations to submatrices of lower part of A
* in reverse factorization order where i decreases from N to 1
*
I = N
Expand Down
8 changes: 4 additions & 4 deletions SRC/csyconvf_rook.f
Original file line number Diff line number Diff line change
Expand Up @@ -285,7 +285,7 @@ SUBROUTINE CSYCONVF_ROOK( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Convert PERMUTATIONS
*
* Apply permutaions to submatrices of upper part of A
* Apply permutations to submatrices of upper part of A
* in factorization order where i decreases from N to 1
*
I = N
Expand Down Expand Up @@ -336,7 +336,7 @@ SUBROUTINE CSYCONVF_ROOK( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Revert PERMUTATIONS
*
* Apply permutaions to submatrices of upper part of A
* Apply permutations to submatrices of upper part of A
* in reverse factorization order where i increases from 1 to N
*
I = 1
Expand Down Expand Up @@ -426,7 +426,7 @@ SUBROUTINE CSYCONVF_ROOK( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Convert PERMUTATIONS
*
* Apply permutaions to submatrices of lower part of A
* Apply permutations to submatrices of lower part of A
* in factorization order where i increases from 1 to N
*
I = 1
Expand Down Expand Up @@ -477,7 +477,7 @@ SUBROUTINE CSYCONVF_ROOK( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Revert PERMUTATIONS
*
* Apply permutaions to submatrices of lower part of A
* Apply permutations to submatrices of lower part of A
* in reverse factorization order where i decreases from N to 1
*
I = N
Expand Down
4 changes: 2 additions & 2 deletions SRC/csytrf_aa.f
Original file line number Diff line number Diff line change
Expand Up @@ -256,7 +256,7 @@ SUBROUTINE CSYTRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
$ A( MAX(1, J), J+1 ), LDA,
$ IPIV( J+1 ), WORK, N, WORK( N*NB+1 ) )
*
* Ajust IPIV and apply it back (J-th step picks (J+1)-th pivot)
* Adjust IPIV and apply it back (J-th step picks (J+1)-th pivot)
*
DO J2 = J+2, MIN(N, J+JB+1)
IPIV( J2 ) = IPIV( J2 ) + J
Expand Down Expand Up @@ -375,7 +375,7 @@ SUBROUTINE CSYTRF_AA( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
$ A( J+1, MAX(1, J) ), LDA,
$ IPIV( J+1 ), WORK, N, WORK( N*NB+1 ) )
*
* Ajust IPIV and apply it back (J-th step picks (J+1)-th pivot)
* Adjust IPIV and apply it back (J-th step picks (J+1)-th pivot)
*
DO J2 = J+2, MIN(N, J+JB+1)
IPIV( J2 ) = IPIV( J2 ) + J
Expand Down
4 changes: 2 additions & 2 deletions SRC/dgejsv.f
Original file line number Diff line number Diff line change
Expand Up @@ -1335,7 +1335,7 @@ SUBROUTINE DGEJSV( JOBA, JOBU, JOBV, JOBR, JOBT, JOBP,
ELSE
*
* .. ill-conditioned case: second QRF with pivoting
* Note that windowed pivoting would be equaly good
* Note that windowed pivoting would be equally good
* numerically, and more run-time efficient. So, in
* an optimal implementation, the next call to DGEQP3
* should be replaced with eg. CALL SGEQPX (ACM TOMS #782)
Expand Down Expand Up @@ -1388,7 +1388,7 @@ SUBROUTINE DGEJSV( JOBA, JOBU, JOBV, JOBR, JOBT, JOBP,
*
IF ( CONDR2 .GE. COND_OK ) THEN
* .. save the Householder vectors used for Q3
* (this overwrittes the copy of R2, as it will not be
* (this overwrites the copy of R2, as it will not be
* needed in this branch, but it does not overwritte the
* Huseholder vectors of Q2.).
CALL DLACPY( 'U', NR, NR, V, LDV, WORK(2*N+1), N )
Expand Down
4 changes: 2 additions & 2 deletions SRC/dgesc2.f
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,7 @@
*> \verbatim
*> SCALE is DOUBLE PRECISION
*> On exit, SCALE contains the scale factor. SCALE is chosen
*> 0 <= SCALE <= 1 to prevent owerflow in the solution.
*> 0 <= SCALE <= 1 to prevent overflow in the solution.
*> \endverbatim
*
* Authors:
Expand Down Expand Up @@ -151,7 +151,7 @@ SUBROUTINE DGESC2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
* ..
* .. Executable Statements ..
*
* Set constant to control owerflow
* Set constant to control overflow
*
EPS = DLAMCH( 'P' )
SMLNUM = DLAMCH( 'S' ) / EPS
Expand Down
8 changes: 4 additions & 4 deletions SRC/dgesvdq.f
Original file line number Diff line number Diff line change
Expand Up @@ -717,7 +717,7 @@ SUBROUTINE DGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
*
* Standard absolute error bound suffices. All sigma_i with
* sigma_i < N*EPS*||A||_F are flushed to zero. This is an
* agressive enforcement of lower numerical rank by introducing a
* aggressive enforcement of lower numerical rank by introducing a
* backward error of the order of N*EPS*||A||_F.
NR = 1
RTMP = SQRT(DBLE(N))*EPSLN
Expand All @@ -728,7 +728,7 @@ SUBROUTINE DGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
3002 CONTINUE
*
ELSEIF ( ACCLM ) THEN
* .. similarly as above, only slightly more gentle (less agressive).
* .. similarly as above, only slightly more gentle (less aggressive).
* Sudden drop on the diagonal of R is used as the criterion for being
* close-to-rank-deficient. The threshold is set to EPSLN=DLAMCH('E').
* [[This can be made more flexible by replacing this hard-coded value
Expand Down Expand Up @@ -1032,7 +1032,7 @@ SUBROUTINE DGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
* vectors of R**T
* [[The optimal ratio N/NR for using QRF instead of padding
* with zeros. Here hard coded to 2; it must be at least
* two due to work space contraints.]]
* two due to work space constraints.]]
* OPTRATIO = ILAENV(6, 'DGESVD', 'S' // 'O', NR,N,0,0)
* OPTRATIO = MAX( OPTRATIO, 2 )
OPTRATIO = 2
Expand Down Expand Up @@ -1147,7 +1147,7 @@ SUBROUTINE DGESVDQ( JOBA, JOBP, JOBR, JOBU, JOBV, M, N, A, LDA,
* is then N1 (N or M)
* [[The optimal ratio N/NR for using LQ instead of padding
* with zeros. Here hard coded to 2; it must be at least
* two due to work space contraints.]]
* two due to work space constraints.]]
* OPTRATIO = ILAENV(6, 'DGESVD', 'S' // 'O', NR,N,0,0)
* OPTRATIO = MAX( OPTRATIO, 2 )
OPTRATIO = 2
Expand Down
2 changes: 1 addition & 1 deletion SRC/dgetc2.f
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@
*> \verbatim
*> INFO is INTEGER
*> = 0: successful exit
*> > 0: if INFO = k, U(k, k) is likely to produce owerflow if
*> > 0: if INFO = k, U(k, k) is likely to produce overflow if
*> we try to solve for x in Ax = b. So U is perturbed to
*> avoid the overflow.
*> \endverbatim
Expand Down
2 changes: 1 addition & 1 deletion SRC/dgsvj0.f
Original file line number Diff line number Diff line change
Expand Up @@ -1045,7 +1045,7 @@ SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,

1993 CONTINUE
* end i=1:NSWEEP loop
* #:) Reaching this point means that the procedure has comleted the given
* #:) Reaching this point means that the procedure has completed the given
* number of iterations.
INFO = NSWEEP - 1
GO TO 1995
Expand Down
2 changes: 1 addition & 1 deletion SRC/dgsvj1.f
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@
*> In terms of the columns of A, the first N1 columns are rotated 'against'
*> the remaining N-N1 columns, trying to increase the angle between the
*> corresponding subspaces. The off-diagonal block is N1-by(N-N1) and it is
*> tiled using quadratic tiles of side KBL. Here, KBL is a tunning parmeter.
*> tiled using quadratic tiles of side KBL. Here, KBL is a tunning parameter.
*> The number of sweeps is given in NSWEEP and the orthogonality threshold
*> is given in TOL.
*> \endverbatim
Expand Down
2 changes: 1 addition & 1 deletion SRC/dhseqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -156,7 +156,7 @@
*> \verbatim
*> LDZ is INTEGER
*> The leading dimension of the array Z. if COMPZ = 'I' or
*> COMPZ = 'V', then LDZ >= MAX(1,N). Otherwize, LDZ >= 1.
*> COMPZ = 'V', then LDZ >= MAX(1,N). Otherwise, LDZ >= 1.
*> \endverbatim
*>
*> \param[out] WORK
Expand Down
2 changes: 1 addition & 1 deletion SRC/dla_wwaddw.f
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@
*> DLA_WWADDW adds a vector W into a doubled-single vector (X, Y).
*>
*> This works for all extant IBM's hex and binary floating point
*> arithmetics, but not for decimal.
*> arithmetic, but not for decimal.
*> \endverbatim
*
* Arguments:
Expand Down
2 changes: 1 addition & 1 deletion SRC/dlahqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -160,7 +160,7 @@
*> If INFO > 0 and WANTT is .FALSE., then on exit,
*> the remaining unconverged eigenvalues are the
*> eigenvalues of the upper Hessenberg matrix rows
*> and columns ILO thorugh INFO of the final, output
*> and columns ILO through INFO of the final, output
*> value of H.
*>
*> If INFO > 0 and WANTT is .TRUE., then on exit
Expand Down
2 changes: 1 addition & 1 deletion SRC/dlatdf.f
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@
*> RHS is DOUBLE PRECISION array, dimension (N)
*> On entry, RHS contains contributions from other subsystems.
*> On exit, RHS contains the solution of the subsystem with
*> entries acoording to the value of IJOB (see above).
*> entries according to the value of IJOB (see above).
*> \endverbatim
*>
*> \param[in,out] RDSUM
Expand Down
8 changes: 4 additions & 4 deletions SRC/dsyconvf.f
Original file line number Diff line number Diff line change
Expand Up @@ -291,7 +291,7 @@ SUBROUTINE DSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Convert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of upper part of A
* Apply permutations to submatrices of upper part of A
* in factorization order where i decreases from N to 1
*
I = N
Expand Down Expand Up @@ -344,7 +344,7 @@ SUBROUTINE DSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Revert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of upper part of A
* Apply permutations to submatrices of upper part of A
* in reverse factorization order where i increases from 1 to N
*
I = 1
Expand Down Expand Up @@ -435,7 +435,7 @@ SUBROUTINE DSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Convert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of lower part of A
* Apply permutations to submatrices of lower part of A
* in factorization order where k increases from 1 to N
*
I = 1
Expand Down Expand Up @@ -488,7 +488,7 @@ SUBROUTINE DSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
*
* Revert PERMUTATIONS and IPIV
*
* Apply permutaions to submatrices of lower part of A
* Apply permutations to submatrices of lower part of A
* in reverse factorization order where i decreases from N to 1
*
I = N
Expand Down
Loading

0 comments on commit 6e26afd

Please sign in to comment.