Skip to content

Commit

Permalink
Fix hardcoded unit number
Browse files Browse the repository at this point in the history
  • Loading branch information
mkrack committed Mar 23, 2021
1 parent 20c7252 commit 8bcee93
Showing 1 changed file with 6 additions and 5 deletions.
11 changes: 6 additions & 5 deletions src/fm/cp_fm_diag.F
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ SUBROUTINE check_diag(matrix, eigenvectors, nvec)
"ELPA "/)
REAL(KIND=dp), PARAMETER :: eps = 1.0E-12_dp

INTEGER :: handle, i, j, ncol, nrow
INTEGER :: handle, i, j, ncol, nrow, output_unit
LOGICAL :: check_eigenvectors
#if defined(__SCALAPACK)
TYPE(cp_blacs_env_type), POINTER :: context
Expand All @@ -227,6 +227,7 @@ SUBROUTINE check_diag(matrix, eigenvectors, nvec)
check_eigenvectors = .FALSE.
#endif
IF (check_eigenvectors) THEN
output_unit = cp_logger_get_default_unit_nr()
#if defined(__SCALAPACK)
nrow = eigenvectors%matrix_struct%nrow_global
ncol = MIN(eigenvectors%matrix_struct%ncol_global, nvec)
Expand All @@ -243,15 +244,15 @@ SUBROUTINE check_diag(matrix, eigenvectors, nvec)
IF ((iprow == myprow) .AND. (ipcol == mypcol)) THEN
IF (i == j) THEN
IF (ABS(matrix%local_data(il, jl) - 1.0_dp) > eps) THEN
WRITE (UNIT=*, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
WRITE (UNIT=output_unit, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
"The eigenvectors returned by "//TRIM(diag_driver(diag_type))//" are not orthonormal", &
"Matrix element (", i, ", ", j, ") = ", matrix%local_data(il, jl), &
"The expected value is 1"
CPABORT("ERROR in "//routineN//": Check of matrix diagonalization failed")
END IF
ELSE
IF (ABS(matrix%local_data(il, jl)) > eps) THEN
WRITE (UNIT=*, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
WRITE (UNIT=output_unit, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
"The eigenvectors returned by "//TRIM(diag_driver(diag_type))//" are not orthonormal", &
"Matrix element (", i, ", ", j, ") = ", matrix%local_data(il, jl), &
"The expected value is 0"
Expand All @@ -272,15 +273,15 @@ SUBROUTINE check_diag(matrix, eigenvectors, nvec)
DO j = 1, ncol
IF (i == j) THEN
IF (ABS(matrix%local_data(i, j) - 1.0_dp) > eps) THEN
WRITE (UNIT=*, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
WRITE (UNIT=output_unit, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
"The eigenvectors returned by "//TRIM(diag_driver(diag_type))//" are not orthonormal", &
"Matrix element (", i, ", ", j, ") = ", matrix%local_data(i, j), &
"The expected value is 1"
CPABORT("ERROR in "//routineN//": Check of matrix diagonalization failed")
END IF
ELSE
IF (ABS(matrix%local_data(i, j)) > eps) THEN
WRITE (UNIT=*, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
WRITE (UNIT=output_unit, FMT="(/,T2,A,/,T2,A,I0,A,I0,A,F0.12,/,T2,A)") &
"The eigenvectors returned by "//TRIM(diag_driver(diag_type))//" are not orthonormal", &
"Matrix element (", i, ", ", j, ") = ", matrix%local_data(i, j), &
"The expected value is 0"
Expand Down

0 comments on commit 8bcee93

Please sign in to comment.