(git:e7e05ae)
rpa_im_time_force_types.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \brief Types needed for cubic-scaling RPA and SOS-Laplace-MP2 forces
10 !> \author Augustin Bussy
11 ! **************************************************************************************************
14  USE dbcsr_api, ONLY: dbcsr_p_type,&
15  dbcsr_release,&
16  dbcsr_type
17  USE dbt_api, ONLY: dbt_destroy,&
18  dbt_type
19  USE hfx_types, ONLY: block_ind_type,&
21  hfx_compression_type
22  USE qs_neighbor_list_types, ONLY: neighbor_list_set_p_type,&
25  USE qs_tensors_types, ONLY: neighbor_list_3c_type
26 #include "./base/base_uses.f90"
27 
28  IMPLICIT NONE
29 
30  PRIVATE
31 
32  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'rpa_im_time_force_types'
33 
34  PUBLIC :: im_time_force_type, im_time_force_release
35 
36  !Type definitions
37  TYPE im_time_force_type
38 
39  !The various 2-center integral derivatives
40  TYPE(dbt_type), DIMENSION(3) :: t_2c_der_metric, t_2c_der_pot, t_2c_der_ovlp
41 
42  !The 3-center integral derivatives (with the RI metric operator)
43  TYPE(dbt_type), DIMENSION(3) :: t_3c_der_AO, & ! (RI| AO deriv_AO)
44  t_3c_der_RI ! (deriv_RI| AO AO)
45 
46  !The compressed 3-center derivatives
47  TYPE(hfx_compression_type), ALLOCATABLE, DIMENSION(:, :) :: t_3c_der_AO_comp, t_3c_der_RI_comp
48  TYPE(block_ind_type), ALLOCATABLE, DIMENSION(:, :) :: t_3c_der_AO_ind, t_3c_der_RI_ind
49 
50  !The RI related 2-center quantities
51  TYPE(dbt_type) :: t_2c_pot_psqrt, t_2c_inv_metric, t_2c_K, t_2c_pot_msqrt
52  TYPE(dbcsr_type) :: inv_ovlp, G_PQ
53 
54  !The occupied and virtual density matrices (standard block size, one for each spin)
55  TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: P_occ => null(), p_virt => null()
56 
57  !The weighted sum of the O(tau) matrices for thre response
58  TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: sum_O_tau => null()
59 
60  !The weigthed sum of the YP matrices for the trace with the Fockian derivative
61  TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: sum_YP_tau => null()
62 
63  !Split block size info
64  INTEGER, DIMENSION(:), ALLOCATABLE :: bsizes_RI_split, bsizes_AO_split
65 
66  !Keep track of atom index for splitted blocks
67  INTEGER, DIMENSION(:), ALLOCATABLE :: idx_to_at_AO, idx_to_at_RI
68 
69  !Is it a periodic calculation
70  LOGICAL :: do_periodic = .false.
71 
72  !Necessary stuff for the on-the fly calculation of the virial
73  TYPE(neighbor_list_set_p_type), DIMENSION(:), POINTER :: nl_2c_ovlp => null(), &
74  nl_2c_met => null(), &
75  nl_2c_pot => null()
76  TYPE(neighbor_list_3c_type), POINTER :: nl_3c => null()
77  TYPE(dbcsr_type), POINTER :: RI_virial_pot => null(), &
78  ri_virial_met => null()
79  TYPE(dbt_type), POINTER :: t_3c_virial => null(), &
80  t_3c_virial_split => null()
81 
82  END TYPE im_time_force_type
83 
84 CONTAINS
85 
86 ! **************************************************************************************************
87 !> \brief Cleans everything up
88 !> \param force_data ...
89 ! **************************************************************************************************
90  SUBROUTINE im_time_force_release(force_data)
91 
92  TYPE(im_time_force_type) :: force_data
93 
94  INTEGER :: dummy_int, i, i_xyz, j
95 
96  CALL dbt_destroy(force_data%t_2c_pot_psqrt)
97  CALL dbt_destroy(force_data%t_2c_pot_msqrt)
98  CALL dbt_destroy(force_data%t_2c_K)
99 
100  CALL dbcsr_release(force_data%inv_ovlp)
101  CALL dbcsr_release(force_data%G_PQ)
102  CALL dbcsr_deallocate_matrix_set(force_data%P_virt)
103  CALL dbcsr_deallocate_matrix_set(force_data%P_occ)
104  CALL dbcsr_deallocate_matrix_set(force_data%sum_O_tau)
105  CALL dbcsr_deallocate_matrix_set(force_data%sum_YP_tau)
106 
107  DO i_xyz = 1, 3
108  IF (.NOT. force_data%do_periodic) CALL dbt_destroy(force_data%t_2c_der_pot(i_xyz))
109  CALL dbt_destroy(force_data%t_2c_der_ovlp(i_xyz))
110 
111  CALL dbt_destroy(force_data%t_3c_der_AO(i_xyz))
112  CALL dbt_destroy(force_data%t_3c_der_RI(i_xyz))
113  END DO
114 
115  CALL dbt_destroy(force_data%t_2c_inv_metric)
116  DO i_xyz = 1, 3
117  CALL dbt_destroy(force_data%t_2c_der_metric(i_xyz))
118  END DO
119 
120  DO i = 1, SIZE(force_data%t_3c_der_AO_comp, 1)
121  DO j = 1, SIZE(force_data%t_3c_der_AO_comp, 2)
122  CALL dealloc_containers(force_data%t_3c_der_AO_comp(i, j), dummy_int)
123  END DO
124  END DO
125  DO i = 1, SIZE(force_data%t_3c_der_RI_comp, 1)
126  DO j = 1, SIZE(force_data%t_3c_der_RI_comp, 2)
127  CALL dealloc_containers(force_data%t_3c_der_RI_comp(i, j), dummy_int)
128  END DO
129  END DO
130  DEALLOCATE (force_data%t_3c_der_AO_ind, force_data%t_3c_der_RI_ind)
131 
132  IF (ASSOCIATED(force_data%nl_2c_ovlp)) THEN
133  CALL release_neighbor_list_sets(force_data%nl_2c_ovlp)
134  END IF
135 
136  IF (ASSOCIATED(force_data%nl_2c_pot)) THEN
137  CALL release_neighbor_list_sets(force_data%nl_2c_pot)
138  END IF
139 
140  IF (ASSOCIATED(force_data%nl_2c_met)) THEN
141  CALL release_neighbor_list_sets(force_data%nl_2c_met)
142  END IF
143 
144  IF (ASSOCIATED(force_data%nl_3c)) THEN
145  CALL neighbor_list_3c_destroy(force_data%nl_3c)
146  DEALLOCATE (force_data%nl_3c)
147  END IF
148 
149  IF (ASSOCIATED(force_data%RI_virial_pot)) THEN
150  CALL dbcsr_release(force_data%RI_virial_pot)
151  DEALLOCATE (force_data%RI_virial_pot)
152  END IF
153 
154  IF (ASSOCIATED(force_data%RI_virial_met)) THEN
155  CALL dbcsr_release(force_data%RI_virial_met)
156  DEALLOCATE (force_data%RI_virial_met)
157  END IF
158 
159  IF (ASSOCIATED(force_data%t_3c_virial)) THEN
160  CALL dbt_destroy(force_data%t_3c_virial)
161  DEALLOCATE (force_data%t_3c_virial)
162  END IF
163 
164  IF (ASSOCIATED(force_data%t_3c_virial_split)) THEN
165  CALL dbt_destroy(force_data%t_3c_virial_split)
166  DEALLOCATE (force_data%t_3c_virial_split)
167  END IF
168 
169  END SUBROUTINE im_time_force_release
170 
171 END MODULE rpa_im_time_force_types
DBCSR operations in CP2K.
This is the start of a dbt_api, all publically needed functions are exported here....
Definition: dbt_api.F:17
Types and set/get functions for HFX.
Definition: hfx_types.F:15
subroutine, public dealloc_containers(DATA, memory_usage)
...
Definition: hfx_types.F:2874
Define the neighbor list data types and the corresponding functionality.
subroutine, public release_neighbor_list_sets(nlists)
releases an array of neighbor_list_sets
Utility methods to build 3-center integral tensors of various types.
Utility methods to build 3-center integral tensors of various types.
Definition: qs_tensors.F:11
subroutine, public neighbor_list_3c_destroy(ijk_list)
Destroy 3c neighborlist.
Definition: qs_tensors.F:383
Types needed for cubic-scaling RPA and SOS-Laplace-MP2 forces.
subroutine, public im_time_force_release(force_data)
Cleans everything up.