Skip to content

Commit

Permalink
RI-HFX: minor fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
pseewald committed Mar 11, 2020
1 parent 05aa757 commit 329ceef
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 7 deletions.
14 changes: 8 additions & 6 deletions src/hfx_ri.F
Original file line number Diff line number Diff line change
Expand Up @@ -668,6 +668,7 @@ SUBROUTINE hfx_ri_pre_scf_Pmat(qs_env, ri_data)
CALL mp_allgather(cols_local, cols, sizes_proc, offsets_proc, para_env%group)
DEALLOCATE (sizes_proc, offsets_proc, rows_local, cols_local)

IF (ALLOCATED(ri_data%nonzero_pairs)) DEALLOCATE (ri_data%nonzero_pairs)
ALLOCATE (ri_data%nonzero_pairs(nblks_total, 2))
ri_data%nonzero_pairs(:, 1) = rows
ri_data%nonzero_pairs(:, 2) = cols
Expand All @@ -680,6 +681,7 @@ SUBROUTINE hfx_ri_pre_scf_Pmat(qs_env, ri_data)

nrows = SIZE(ri_data%bsizes_RI_split)

IF (ALLOCATED(ri_data%nonzero_rows)) DEALLOCATE (ri_data%nonzero_rows)
ALLOCATE (ri_data%nonzero_rows(nrows + 1))

ASSOCIATE (rows=>ri_data%nonzero_pairs(:, 1))
Expand Down Expand Up @@ -1304,14 +1306,14 @@ SUBROUTINE hfx_ri_update_ks_Pmat(qs_env, ri_data, ks_matrix, rho_ao, &

IF (geometry_did_change) THEN
CALL hfx_ri_pre_scf_Pmat(qs_env, ri_data)
ELSE
IF (ASSOCIATED(ri_data%pgrid_1)) CALL tensor_change_pgrid(ri_data%t_3c_int_ctr_1(1, 1), &
ri_data%pgrid_1, unit_nr=unit_nr_dbcsr)
IF (ASSOCIATED(ri_data%pgrid_3)) CALL tensor_change_pgrid(ri_data%t_3c_int_ctr_3(1, 1), &
ri_data%pgrid_3, unit_nr=unit_nr_dbcsr, &
nodata=.TRUE.)
ENDIF

IF (ASSOCIATED(ri_data%pgrid_1)) CALL tensor_change_pgrid(ri_data%t_3c_int_ctr_1(1, 1), &
ri_data%pgrid_1, unit_nr=unit_nr_dbcsr)
IF (ASSOCIATED(ri_data%pgrid_3)) CALL tensor_change_pgrid(ri_data%t_3c_int_ctr_3(1, 1), &
ri_data%pgrid_3, unit_nr=unit_nr_dbcsr, &
nodata=.TRUE.)

CALL dbcsr_t_create(ks_matrix(1, 1)%matrix, ks_tmp)
CALL dbcsr_t_create(rho_ao(1, 1)%matrix, rho_ao_tmp)

Expand Down
2 changes: 1 addition & 1 deletion tests/QS/regtest-hfx-ri/TEST_FILES
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ H2O-hfx-identity.inp 1 1.0E-10
H2O-hfx-periodic-ri-truncated.inp 1 1.0E-12 -66.83226303451153
H2O-hybrid-b3lyp.inp 1 1.0E-12 -76.15358900494054
CH-hfx-ri-mo.inp 1 1.0E-12 -37.91967383839648
CH-hfx-ri-rho.inp 1 1.0E-12 -38.26006228356700
CH-hfx-ri-rho.inp 1 1.0E-10 -38.26006228356700
CH3-ADMM.inp 1 1.0E-12 -7.36918928540100
CH3-hfx-converged.inp 1 1.0E-12 -7.21317273072467
Ne-hybrid-periodic-shortrange.inp 1 1.0E-12 -772.82989949221326

0 comments on commit 329ceef

Please sign in to comment.