Skip to content

Commit

Permalink
fix conventions
Browse files Browse the repository at this point in the history
  • Loading branch information
hforbert committed Jun 8, 2022
1 parent 9b7da12 commit 2a93ef0
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 5 deletions.
15 changes: 11 additions & 4 deletions src/fm/cp_fm_basic_linalg.F
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,8 @@ MODULE cp_fm_basic_linalg
cp_fm_create, cp_fm_get_diag, cp_fm_get_info, cp_fm_get_submatrix, cp_fm_p_type, &
cp_fm_release, cp_fm_set_all, cp_fm_set_element, cp_fm_set_submatrix, cp_fm_to_fm, &
cp_fm_type
USE cp_log_handling, ONLY: cp_to_string
USE cp_log_handling, ONLY: cp_logger_get_default_unit_nr,&
cp_to_string
USE kahan_sum, ONLY: accurate_dot_product,&
accurate_sum
USE kinds, ONLY: dp,&
Expand Down Expand Up @@ -2310,7 +2311,7 @@ SUBROUTINE cp_fm_Gram_Schmidt_orthonorm(matrix_a, B, nrows, ncols, start_row, st

INTEGER :: end_col_global, end_col_local, end_row_global, end_row_local, handle, i, j, &
j_col, ncol_global, ncol_local, nrow_global, nrow_local, start_col_global, &
start_col_local, start_row_global, start_row_local, this_col
start_col_local, start_row_global, start_row_local, this_col, unit_nr
INTEGER, DIMENSION(:), POINTER :: col_indices, row_indices
LOGICAL :: my_do_norm, my_do_print
REAL(KIND=dp) :: norm
Expand All @@ -2326,6 +2327,12 @@ SUBROUTINE cp_fm_Gram_Schmidt_orthonorm(matrix_a, B, nrows, ncols, start_row, st
my_do_print = .FALSE.
IF (PRESENT(do_print) .AND. (my_do_norm)) my_do_print = do_print

unit_nr = -1
IF (my_do_print) THEN
unit_nr = cp_logger_get_default_unit_nr()
IF (unit_nr < 1) my_do_print = .FALSE.
END IF

IF (SIZE(B) /= 0) THEN
IF (PRESENT(nrows)) THEN
nrow_global = nrows
Expand Down Expand Up @@ -2396,7 +2403,7 @@ SUBROUTINE cp_fm_Gram_Schmidt_orthonorm(matrix_a, B, nrows, ncols, start_row, st
IF (my_do_norm) THEN
norm = SQRT(accurate_dot_product(B(:, this_col), B(:, this_col)))
B(:, this_col) = B(:, this_col)/norm
IF (my_do_print) WRITE (*, '(I3,F8.3)') this_col, norm
IF (my_do_print) WRITE (unit_nr, '(I3,F8.3)') this_col, norm
END IF

DO i = start_col_local + 1, end_col_local
Expand All @@ -2412,7 +2419,7 @@ SUBROUTINE cp_fm_Gram_Schmidt_orthonorm(matrix_a, B, nrows, ncols, start_row, st
IF (my_do_norm) THEN
norm = SQRT(accurate_dot_product(B(:, this_col), B(:, this_col)))
B(:, this_col) = B(:, this_col)/norm
IF (my_do_print) WRITE (*, '(I3,F8.3)') this_col, norm
IF (my_do_print) WRITE (unit_nr, '(I3,F8.3)') this_col, norm
END IF

END DO
Expand Down
2 changes: 1 addition & 1 deletion src/qs_localization_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -777,7 +777,7 @@ SUBROUTINE jacobi_cg_edf_ls(para_env, weights, zij, vectors, max_iter, eps_local
! initialize c_tilde
SELECT CASE (icinit)
CASE (1) ! random coefficients
WRITE (*, *) "RANDOM INITIAL GUESS FOR C"
!WRITE (*, *) "RANDOM INITIAL GUESS FOR C"
CALL cp_fm_create(tmp_fm, c_tilde%matrix_struct)
CALL cp_fm_init_random(tmp_fm, nextra)
CALL make_basis_simple(tmp_fm, nextra)
Expand Down

0 comments on commit 2a93ef0

Please sign in to comment.