(git:e7e05ae)
semi_empirical_store_int_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 Type to store integrals for semi-empirical calculations
10 !> \author Teodoro Laino [tlaino] - University of Zurich
11 !> \date 05.2008
12 ! **************************************************************************************************
14 
18  USE hfx_types, ONLY: hfx_cache_type,&
19  hfx_container_type,&
21  hfx_memory_type,&
24  section_vals_type,&
26  USE kinds, ONLY: dp
27  USE memory_utilities, ONLY: reallocate
28 #include "./base/base_uses.f90"
29 
30  IMPLICIT NONE
31 
32  PRIVATE
33 
34 ! *** Global parameters ***
35 
36  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'semi_empirical_store_int_types'
37 
38 ! **************************************************************************************************
39 !> \brief Semi-empirical store integrals type
40 !> \author Teodoro Laino [tlaino] - University of Zurich
41 !> \date 05.2008
42 ! **************************************************************************************************
43  TYPE semi_empirical_si_type
44  LOGICAL :: filling_containers, compress
45  INTEGER :: nbuffer
46  REAL(KIND=dp), POINTER, DIMENSION(:) :: max_val_buffer, uncompressed_container
47  TYPE(hfx_memory_type) :: memory_parameter
48  TYPE(hfx_cache_type), DIMENSION(:), &
49  POINTER :: integral_caches
50  TYPE(hfx_container_type), DIMENSION(:), &
51  POINTER :: integral_containers
52  END TYPE semi_empirical_si_type
53 
54  PUBLIC :: semi_empirical_si_type, &
59 
60 CONTAINS
61 
62 ! **************************************************************************************************
63 !> \brief Allocate semi-empirical store integrals type
64 !> \param store_int_env ...
65 !> \param se_section ...
66 !> \param compression ...
67 !> \date 05.2008
68 !> \author Teodoro Laino [tlaino] - University of Zurich
69 ! **************************************************************************************************
70  SUBROUTINE semi_empirical_si_create(store_int_env, se_section, compression)
71  TYPE(semi_empirical_si_type), POINTER :: store_int_env
72  TYPE(section_vals_type), POINTER :: se_section
73  LOGICAL, INTENT(in), OPTIONAL :: compression
74 
75  INTEGER :: i
76  TYPE(section_vals_type), POINTER :: se_mem_section
77 
78  cpassert(.NOT. ASSOCIATED(store_int_env))
79  ALLOCATE (store_int_env)
80  store_int_env%filling_containers = .true.
81  store_int_env%nbuffer = 0
82  NULLIFY (store_int_env%max_val_buffer, store_int_env%uncompressed_container)
83 
84  ! Memory section
85  se_mem_section => section_vals_get_subs_vals(se_section, "MEMORY")
86  IF (PRESENT(compression)) THEN
87  store_int_env%compress = compression
88  ELSE
89  CALL section_vals_val_get(se_mem_section, "COMPRESS", l_val=store_int_env%compress)
90  END IF
91  CALL parse_memory_section(store_int_env%memory_parameter, se_mem_section, skip_disk=.true., &
92  skip_in_core_forces=.true.)
93  store_int_env%memory_parameter%ram_counter = 0
94  ! If we don't compress there's no cache
95  IF (.NOT. store_int_env%compress) THEN
96  store_int_env%memory_parameter%cache_size = 1
97  END IF
98 
99  ! Disk Storage disabled for semi-empirical methods
100  IF (store_int_env%memory_parameter%do_disk_storage) &
101  cpabort("Disk storage for SEMIEMPIRICAL methods disabled! ")
102 
103  ! Allocate containers/caches for integral storage if requested
104  IF (.NOT. store_int_env%memory_parameter%do_all_on_the_fly .AND. store_int_env%compress) THEN
105  ALLOCATE (store_int_env%integral_containers(64))
106  ALLOCATE (store_int_env%integral_caches(64))
107  DO i = 1, 64
108  store_int_env%integral_caches(i)%element_counter = 1
109  store_int_env%integral_caches(i)%data = 0
110  ALLOCATE (store_int_env%integral_containers(i)%first)
111  store_int_env%integral_containers(i)%first%prev => null()
112  store_int_env%integral_containers(i)%first%next => null()
113  store_int_env%integral_containers(i)%current => store_int_env%integral_containers(i)%first
114  store_int_env%integral_containers(i)%current%data = 0
115  store_int_env%integral_containers(i)%element_counter = 1
116  END DO
117  END IF
118  END SUBROUTINE semi_empirical_si_create
119 
120 ! **************************************************************************************************
121 !> \brief Deallocate the semi-empirical store integrals type
122 !> \param store_int_env ...
123 !> \date 05.2008
124 !> \author Teodoro Laino [tlaino] - University of Zurich
125 ! **************************************************************************************************
126  SUBROUTINE semi_empirical_si_release(store_int_env)
127  TYPE(semi_empirical_si_type), POINTER :: store_int_env
128 
129  INTEGER :: i
130 
131  IF (ASSOCIATED(store_int_env)) THEN
132  ! Deallocate containers/caches
133  IF (.NOT. store_int_env%memory_parameter%do_all_on_the_fly) THEN
134  IF (store_int_env%compress) THEN
135  ! Deallocate containers/caches
136  DO i = 1, 64
137  CALL hfx_init_container(store_int_env%integral_containers(i), &
138  store_int_env%memory_parameter%actual_memory_usage, &
139  .false.)
140  DEALLOCATE (store_int_env%integral_containers(i)%first)
141  END DO
142  IF (ASSOCIATED(store_int_env%max_val_buffer)) THEN
143  DEALLOCATE (store_int_env%max_val_buffer)
144  END IF
145  DEALLOCATE (store_int_env%integral_containers)
146  DEALLOCATE (store_int_env%integral_caches)
147  ELSE
148  IF (ASSOCIATED(store_int_env%uncompressed_container)) THEN
149  DEALLOCATE (store_int_env%uncompressed_container)
150  END IF
151  END IF
152  END IF
153  ! Deallocate the full store_int_env
154  DEALLOCATE (store_int_env)
155  END IF
156 
157  END SUBROUTINE semi_empirical_si_release
158 
159 ! **************************************************************************************************
160 !> \brief Deallocate the semi-empirical store integrals type
161 !> \param store_int_env ...
162 !> \param geometry_did_change ...
163 !> \date 05.2008
164 !> \author Teodoro Laino [tlaino] - University of Zurich
165 ! **************************************************************************************************
166  SUBROUTINE semi_empirical_si_initialize(store_int_env, geometry_did_change)
167  TYPE(semi_empirical_si_type), POINTER :: store_int_env
168  LOGICAL, INTENT(IN) :: geometry_did_change
169 
170  INTEGER :: i
171 
172  IF (ASSOCIATED(store_int_env)) THEN
173  IF (.NOT. store_int_env%memory_parameter%do_all_on_the_fly) THEN
174  IF (geometry_did_change) THEN
175  store_int_env%filling_containers = .true.
176  store_int_env%nbuffer = 0
177  store_int_env%memory_parameter%ram_counter = huge(store_int_env%memory_parameter%ram_counter)
178  IF (store_int_env%compress) THEN
179  ! Compress integrals
180  CALL reallocate(store_int_env%max_val_buffer, 1, store_int_env%nbuffer)
181  ! Clean containers
182  DO i = 1, 64
183  CALL hfx_init_container(store_int_env%integral_containers(i), &
184  store_int_env%memory_parameter%actual_memory_usage, &
185  .false.)
186  END DO
187  ELSE
188  ! Skip compression
189  CALL reallocate(store_int_env%uncompressed_container, 1, 0)
190  store_int_env%memory_parameter%actual_memory_usage = 1
191  END IF
192  ELSE
193  store_int_env%filling_containers = .false.
194  store_int_env%nbuffer = 0
195  IF (store_int_env%compress) THEN
196  ! Retrieve data into the cache
197  DO i = 1, 64
198  CALL hfx_decompress_first_cache(i, store_int_env%integral_caches(i), &
199  store_int_env%integral_containers(i), &
200  store_int_env%memory_parameter%actual_memory_usage, .false.)
201  END DO
202  ELSE
203  store_int_env%memory_parameter%actual_memory_usage = 1
204  END IF
205  END IF
206  END IF
207  END IF
208 
209  END SUBROUTINE semi_empirical_si_initialize
210 
211 ! **************************************************************************************************
212 !> \brief Deallocate the semi-empirical store integrals type
213 !> \param store_int_env ...
214 !> \param geometry_did_change ...
215 !> \date 05.2008
216 !> \author Teodoro Laino [tlaino] - University of Zurich
217 ! **************************************************************************************************
218  SUBROUTINE semi_empirical_si_finalize(store_int_env, geometry_did_change)
219  TYPE(semi_empirical_si_type), POINTER :: store_int_env
220  LOGICAL, INTENT(IN) :: geometry_did_change
221 
222  INTEGER :: i
223 
224  IF (ASSOCIATED(store_int_env)) THEN
225  IF (.NOT. store_int_env%memory_parameter%do_all_on_the_fly) THEN
226  IF (geometry_did_change) THEN
227  IF (store_int_env%compress) THEN
228  ! Flush last cache
229  DO i = 1, 64
230  CALL hfx_flush_last_cache(i, store_int_env%integral_caches(i), &
231  store_int_env%integral_containers(i), &
232  store_int_env%memory_parameter%actual_memory_usage, .false.)
233  END DO
234  ! Reallocate this array with the proper size
235  CALL reallocate(store_int_env%max_val_buffer, 1, store_int_env%nbuffer)
236  ELSE
237  ! Skip compression
238  CALL reallocate(store_int_env%uncompressed_container, 1, &
239  store_int_env%memory_parameter%actual_memory_usage - 1)
240  END IF
241  END IF
242  IF (store_int_env%compress) THEN
243  ! Reset caches and containers
244  DO i = 1, 64
246  store_int_env%integral_caches(i), &
247  store_int_env%integral_containers(i), store_int_env%memory_parameter%actual_memory_usage, &
248  .false.)
249  END DO
250  END IF
251  END IF
252  END IF
253 
254  END SUBROUTINE semi_empirical_si_finalize
255 
routines and types for Hartree-Fock-Exchange
subroutine, public hfx_flush_last_cache(nbits, cache, container, memory_usage, use_disk_storage)
This routine compresses the last probably not yet compressed cache into a container
subroutine, public hfx_decompress_first_cache(nbits, cache, container, memory_usage, use_disk_storage)
This routine decompresses the first bunch of data in a container and copies them into a cache
subroutine, public hfx_reset_cache_and_container(cache, container, memory_usage, do_disk_storage)
This routine resets the containers list pointer to the first element and moves the element counters o...
Types and set/get functions for HFX.
Definition: hfx_types.F:15
subroutine, public hfx_init_container(container, memory_usage, do_disk_storage)
This routine deletes all list entries in a container in order to deallocate the memory.
Definition: hfx_types.F:2523
subroutine, public parse_memory_section(memory_parameter, hf_sub_section, storage_id, i_thread, n_threads, para_env, irep, skip_disk, skip_in_core_forces)
Parses the memory section
Definition: hfx_types.F:1813
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Utility routines for the memory handling.
Type to store integrals for semi-empirical calculations.
subroutine, public semi_empirical_si_finalize(store_int_env, geometry_did_change)
Deallocate the semi-empirical store integrals type.
subroutine, public semi_empirical_si_initialize(store_int_env, geometry_did_change)
Deallocate the semi-empirical store integrals type.
subroutine, public semi_empirical_si_release(store_int_env)
Deallocate the semi-empirical store integrals type.
subroutine, public semi_empirical_si_create(store_int_env, se_section, compression)
Allocate semi-empirical store integrals type.