Skip to content

Commit

Permalink
DBCSR update: changes in tensor API (#842)
Browse files Browse the repository at this point in the history
  • Loading branch information
pseewald committed Apr 8, 2020
1 parent 063995b commit 3265c56
Show file tree
Hide file tree
Showing 6 changed files with 36 additions and 20 deletions.
2 changes: 1 addition & 1 deletion exts/dbcsr
15 changes: 8 additions & 7 deletions src/hfx_ri.F
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,10 @@ MODULE hfx_ri
dbcsr_t_batched_contract_finalize, dbcsr_t_batched_contract_init, dbcsr_t_clear, &
dbcsr_t_contract, dbcsr_t_contract_index, dbcsr_t_copy, dbcsr_t_copy_matrix_to_tensor, &
dbcsr_t_copy_tensor_to_matrix, dbcsr_t_create, dbcsr_t_destroy, dbcsr_t_filter, &
dbcsr_t_get_num_blocks_total, dbcsr_t_mp_environ_pgrid, dbcsr_t_nd_mp_comm, &
dbcsr_t_pgrid_change_dims, dbcsr_t_pgrid_create, dbcsr_t_pgrid_destroy, &
dbcsr_t_pgrid_type, dbcsr_t_reserve_blocks, dbcsr_t_reserved_block_indices, dbcsr_t_type
dbcsr_t_get_num_blocks, dbcsr_t_get_num_blocks_total, dbcsr_t_max_nblks_local, &
dbcsr_t_mp_environ_pgrid, dbcsr_t_nd_mp_comm, dbcsr_t_ndims, dbcsr_t_pgrid_change_dims, &
dbcsr_t_pgrid_create, dbcsr_t_pgrid_destroy, dbcsr_t_pgrid_type, dbcsr_t_reserve_blocks, &
dbcsr_t_reserved_block_indices, dbcsr_t_type
USE distribution_2d_types, ONLY: distribution_2d_type
USE hfx_types, ONLY: hfx_ri_type
USE input_constants, ONLY: hfx_ri_do_2c_cholesky,&
Expand Down Expand Up @@ -636,6 +637,7 @@ SUBROUTINE hfx_ri_pre_scf_Pmat(qs_env, ri_data)

CALL dbcsr_t_copy(ri_data%t_3c_int_ctr_1(1, 1), RI_AO_structure, order=[2, 1, 3])

ALLOCATE (blk_ind(dbcsr_t_get_num_blocks(RI_AO_structure), 3))
CALL dbcsr_t_reserved_block_indices(RI_AO_structure, blk_ind)
CALL dbcsr_t_destroy(RI_AO_structure)

Expand Down Expand Up @@ -1394,15 +1396,14 @@ SUBROUTINE hfx_ri_update_ks_Pmat(qs_env, ri_data, ks_matrix, rho_ao, &

! impose sparsity of 3-center integrals:

ALLOCATE (ctr_ind(dbcsr_t_max_nblks_local(t_3c_2), dbcsr_t_ndims(t_3c_2)))
CALL dbcsr_t_contract_index(dbcsr_scalar(1.0_dp), ri_data%t_2c_int(1, 1), ri_data%t_3c_int_ctr_3(1, 1), &
dbcsr_scalar(0.0_dp), t_3c_2, &
contract_1=[2], notcontract_1=[1], &
contract_2=[1], notcontract_2=[2, 3], &
map_1=[1], map_2=[2, 3], result_index=ctr_ind, filter_eps=ri_data%filter_eps)
map_1=[1], map_2=[2, 3], filter_eps=ri_data%filter_eps, &
nblks_local=nblk, result_index=ctr_ind)

CPASSERT(ALLOCATED(ctr_ind))

nblk = SIZE(ctr_ind, 1)
ALLOCATE (ctr_ind_tmp(nblk, 3))
iblk_filter = 0
DO iblk = 1, nblk
Expand Down
18 changes: 12 additions & 6 deletions src/qs_tensors.F
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,9 @@ MODULE qs_tensors
dbcsr_t_distribution_destroy, dbcsr_t_distribution_new, dbcsr_t_distribution_type, &
dbcsr_t_filter, dbcsr_t_get_block, dbcsr_t_get_info, dbcsr_t_get_mapping_info, &
dbcsr_t_get_nze_total, dbcsr_t_get_stored_coordinates, dbcsr_t_mp_environ_pgrid, &
dbcsr_t_ndims, dbcsr_t_pgrid_type, dbcsr_t_put_block, dbcsr_t_reserve_blocks, &
dbcsr_t_type, dbcsr_t_write_split_info
dbcsr_t_nblks_total, dbcsr_t_ndims, dbcsr_t_ndims_matrix_column, dbcsr_t_ndims_matrix_row, &
dbcsr_t_pgrid_type, dbcsr_t_put_block, dbcsr_t_reserve_blocks, dbcsr_t_type, &
dbcsr_t_write_split_info
USE distribution_1d_types, ONLY: distribution_1d_type
USE distribution_2d_types, ONLY: distribution_2d_type
USE gamma, ONLY: init_md_ftable
Expand Down Expand Up @@ -1570,13 +1571,15 @@ SUBROUTINE tensor_change_pgrid(t_3c, pgrid, nodata, &
CHARACTER(default_string_length) :: name
INTEGER :: handle, imem, memcut_1, memcut_2, &
memcut_3, size_cut
INTEGER, ALLOCATABLE, DIMENSION(:) :: bs1, bs2, bs3, dist1, dist2, dist3, &
map1, map2
INTEGER, ALLOCATABLE, DIMENSION(:) :: bs1, bs2, bs3, dist1, dist2, dist3
INTEGER, DIMENSION(3) :: pcoord, pcoord_ref, pdims, pdims_ref, &
tdims
LOGICAL :: mem_aware_1, mem_aware_2, mem_aware_3
TYPE(dbcsr_t_distribution_type) :: dist
TYPE(dbcsr_t_type) :: t_tmp
TYPE(dbcsr_t_distribution_type) :: dist
LOGICAL :: mem_aware_1, mem_aware_2, mem_aware_3
INTEGER, DIMENSION(dbcsr_t_ndims_matrix_row(t_3c)) :: map1
INTEGER, &
DIMENSION(dbcsr_t_ndims_matrix_column(t_3c)) :: map2

CALL dbcsr_t_mp_environ_pgrid(pgrid, pdims, pcoord)
CALL dbcsr_t_mp_environ_pgrid(t_3c%pgrid, pdims_ref, pcoord_ref)
Expand All @@ -1597,6 +1600,9 @@ SUBROUTINE tensor_change_pgrid(t_3c, pgrid, nodata, &
IF (mem_aware_2) memcut_2 = SIZE(starts_array_mc_block_2)
IF (mem_aware_3) memcut_3 = SIZE(starts_array_mc_block_3)

ALLOCATE (bs1(dbcsr_t_nblks_total(t_3c, 1)))
ALLOCATE (bs2(dbcsr_t_nblks_total(t_3c, 2)))
ALLOCATE (bs3(dbcsr_t_nblks_total(t_3c, 3)))
CALL dbcsr_t_get_info(t_3c, nblks_total=tdims, blk_size_1=bs1, blk_size_2=bs2, blk_size_3=bs3, &
name=name)

Expand Down
6 changes: 4 additions & 2 deletions src/rpa_gw.F
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,8 @@ MODULE rpa_gw
dbcsr_t_contract, dbcsr_t_copy, dbcsr_t_copy_matrix_to_tensor, dbcsr_t_create, &
dbcsr_t_destroy, dbcsr_t_get_block, dbcsr_t_get_info, dbcsr_t_iterator_blocks_left, &
dbcsr_t_iterator_next_block, dbcsr_t_iterator_start, dbcsr_t_iterator_stop, &
dbcsr_t_iterator_type, dbcsr_t_pgrid_create, dbcsr_t_pgrid_destroy, dbcsr_t_pgrid_type, &
dbcsr_t_type
dbcsr_t_iterator_type, dbcsr_t_nblks_total, dbcsr_t_pgrid_create, dbcsr_t_pgrid_destroy, &
dbcsr_t_pgrid_type, dbcsr_t_type
USE input_constants, ONLY: gw_pade_approx,&
gw_two_pole_model,&
ri_rpa_g0w0_crossing_bisection,&
Expand Down Expand Up @@ -4893,6 +4893,7 @@ SUBROUTINE compute_sigma_gw(t_3c_overl_int_gw_AO, t_3c_overl_int_gw_RI, &
t_3c_ctr_RI_prv = t_3c_ctr_RI
ELSE

ALLOCATE (sizes_RI(dbcsr_t_nblks_total(t_3c_overl_int_gw_RI, 1)))
CALL dbcsr_t_get_info(t_3c_overl_int_gw_RI, blk_size_1=sizes_RI)

CALL create_2c_tensor(t_RI, dist1, dist2, pgrid_2d, sizes_RI, sizes_RI, name="(RI|RI)")
Expand All @@ -4919,6 +4920,7 @@ SUBROUTINE compute_sigma_gw(t_3c_overl_int_gw_AO, t_3c_overl_int_gw_RI, &

ENDIF

ALLOCATE (sizes_AO(dbcsr_t_nblks_total(t_3c_overl_int_gw_AO, 1)))
CALL dbcsr_t_get_info(t_3c_overl_int_gw_AO, blk_size_1=sizes_AO)
CALL create_2c_tensor(t_AO, dist1, dist2, pgrid_2d, sizes_AO, sizes_AO, name="(AO|AO)")
DEALLOCATE (dist1, dist2, sizes_AO)
Expand Down
5 changes: 3 additions & 2 deletions src/rpa_gw_ic.F
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,8 @@ MODULE rpa_gw_ic
dbcsr_t_contract, dbcsr_t_copy, dbcsr_t_copy_matrix_to_tensor, dbcsr_t_create, &
dbcsr_t_destroy, dbcsr_t_get_block, dbcsr_t_get_info, dbcsr_t_iterator_blocks_left, &
dbcsr_t_iterator_next_block, dbcsr_t_iterator_start, dbcsr_t_iterator_stop, &
dbcsr_t_iterator_type, dbcsr_t_pgrid_create, dbcsr_t_pgrid_destroy, dbcsr_t_pgrid_type, &
dbcsr_t_type
dbcsr_t_iterator_type, dbcsr_t_nblks_total, dbcsr_t_pgrid_create, dbcsr_t_pgrid_destroy, &
dbcsr_t_pgrid_type, dbcsr_t_type
USE kinds, ONLY: dp
USE message_passing, ONLY: mp_alltoall,&
mp_dims_create,&
Expand Down Expand Up @@ -114,6 +114,7 @@ SUBROUTINE calculate_ic_correction(Eigenval, mat_SinvVSinv, &
mo_end = homo + gw_corr_lev_virt
CPASSERT(mo_end - mo_start + 1 == gw_corr_lev_tot)

ALLOCATE (sizes_RI_split(dbcsr_t_nblks_total(t_3c_overl_nnP_ic_reflected, 1)))
CALL dbcsr_t_get_info(t_3c_overl_nnP_ic_reflected, blk_size_1=sizes_RI_split)

CALL dbcsr_t_create(mat_SinvVSinv%matrix, t_SinvVSinv_tmp)
Expand Down
10 changes: 8 additions & 2 deletions src/rpa_im_time.F
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,9 @@ MODULE rpa_im_time
USE dbcsr_tensor_api, ONLY: &
dbcsr_t_batched_contract_finalize, dbcsr_t_batched_contract_init, dbcsr_t_contract, &
dbcsr_t_copy, dbcsr_t_copy_matrix_to_tensor, dbcsr_t_copy_tensor_to_matrix, &
dbcsr_t_create, dbcsr_t_destroy, dbcsr_t_filter, dbcsr_t_get_info, dbcsr_t_nd_mp_comm, &
dbcsr_t_need_contract, dbcsr_t_pgrid_destroy, dbcsr_t_pgrid_type, dbcsr_t_type
dbcsr_t_create, dbcsr_t_destroy, dbcsr_t_filter, dbcsr_t_get_info, dbcsr_t_nblks_total, &
dbcsr_t_nd_mp_comm, dbcsr_t_need_contract, dbcsr_t_pgrid_destroy, dbcsr_t_pgrid_type, &
dbcsr_t_type
USE kinds, ONLY: dp,&
int_8
USE kpoint_types, ONLY: get_kpoint_info,&
Expand Down Expand Up @@ -281,11 +282,16 @@ SUBROUTINE compute_mat_P_omega(mat_P_omega, fm_scaled_dm_occ_tau, &
CALL dbcsr_distribution_get(dist_P, group=comm_2d, nprows=pdims_2d(1), npcols=pdims_2d(2))

pgrid_2d = dbcsr_t_nd_mp_comm(comm_2d, [1], [2], pdims_2d=pdims_2d)
ALLOCATE (size_P(dbcsr_t_nblks_total(t_3c_M, 1)))
CALL dbcsr_t_get_info(t_3c_M, blk_size_1=size_P)

ALLOCATE (size_dm(dbcsr_t_nblks_total(t_3c_O(1, 1), 3)))
CALL dbcsr_t_get_info(t_3c_O(1, 1), blk_size_3=size_dm)
CALL create_2c_tensor(t_dm, dist_1, dist_2, pgrid_2d, size_dm, size_dm, name="D (AO | AO)")
DEALLOCATE (size_dm)
DEALLOCATE (dist_1, dist_2)
CALL create_2c_tensor(t_P, dist_1, dist_2, pgrid_2d, size_P, size_P, name="P (RI | RI)")
DEALLOCATE (size_P)
DEALLOCATE (dist_1, dist_2)
CALL dbcsr_t_pgrid_destroy(pgrid_2d)

Expand Down

0 comments on commit 3265c56

Please sign in to comment.