Skip to content

Commit

Permalink
Fix bugs
Browse files Browse the repository at this point in the history
  • Loading branch information
sh-zheng committed Mar 14, 2024
1 parent eb41c88 commit f956d92
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 7 deletions.
8 changes: 4 additions & 4 deletions SRC/dkteqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -166,8 +166,8 @@ SUBROUTINE DKTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
* ..
* .. External Functions ..
LOGICAL LSAME
DOUBLE PRECISION DLAMCH, DLAPY2
EXTERNAL LSAME, DLAMCH, DLAPY2
DOUBLE PRECISION DLAMCH, DLAPY2, DLANKT
EXTERNAL LSAME, DLAMCH, DLAPY2, DLANKT
* ..
* .. External Subroutines ..
EXTERNAL DLAE2, DLAEV2, DLARTG, DLASCL, DLASET,
Expand Down Expand Up @@ -224,7 +224,7 @@ SUBROUTINE DKTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
END IF
IF( E(1).LT.ZERO ) THEN
E(1) = -E(1)
CALL SSWAP( N, Z( 1, 1 ), 1, Z( 1, 2 ), 1 )
CALL DSWAP( N, Z( 1, 1 ), 1, Z( 1, 2 ), 1 )
END IF
RETURN
END IF
Expand Down Expand Up @@ -292,7 +292,7 @@ SUBROUTINE DKTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
*
* Scale submatrix in rows and columns L to LEND
*
ANORM = SLANKT( 'M', LEND-L+1, D( L ), E( L ) )
ANORM = DLANKT( 'M', LEND-L+1, D( L ), E( L ) )
ISCALE = 0
IF( ANORM.EQ.ZERO )
$ GO TO 10
Expand Down
6 changes: 3 additions & 3 deletions SRC/dlatrdk.f
Original file line number Diff line number Diff line change
Expand Up @@ -216,7 +216,7 @@ SUBROUTINE DLATRDK( UPLO, N, NB, A, LDA, E, TAU, W, LDW )
DOUBLE PRECISION ALPHA
* ..
* .. External Subroutines ..
EXTERNAL DAXPY, DGEMV, DLARFG, DSCAL, DSYMV
EXTERNAL DAXPY, DGEMV, DLARFG, DSCAL, DKYMV
* ..
* .. External Functions ..
LOGICAL LSAME
Expand Down Expand Up @@ -259,7 +259,7 @@ SUBROUTINE DLATRDK( UPLO, N, NB, A, LDA, E, TAU, W, LDW )
*
* Compute W(1:i-1,i)
*
CALL SKYMV( 'Upper', I-1, ONE, A, LDA, A( 1, I ), 1,
CALL DKYMV( 'Upper', I-1, ONE, A, LDA, A( 1, I ), 1,
$ ZERO, W( 1, IW ), 1 )
IF( I.LT.N ) THEN
CALL DGEMV( 'Transpose', I-1, N-I, ONE, W( 1, IW+1 ),
Expand Down Expand Up @@ -304,7 +304,7 @@ SUBROUTINE DLATRDK( UPLO, N, NB, A, LDA, E, TAU, W, LDW )
*
* Compute W(i+1:n,i)
*
CALL SKYMV( 'Lower', N-I, ONE, A( I+1, I+1 ), LDA,
CALL DKYMV( 'Lower', N-I, ONE, A( I+1, I+1 ), LDA,
$ A( I+1, I ), 1, ZERO, W( I+1, I ), 1 )
CALL DGEMV( 'Transpose', N-I, I-1, ONE, W( I+1, 1 ), LDW,
$ A( I+1, I ), 1, ZERO, W( 1, I ), 1 )
Expand Down

0 comments on commit f956d92

Please sign in to comment.