(git:374b731)
Loading...
Searching...
No Matches
pw_env_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 container for various plainwaves related things
10!> \par History
11!> 10.2002 created [fawzi]
12!> \author Fawzi Mohamed
13! **************************************************************************************************
15 USE cube_utils, ONLY: cube_info_type,&
20 USE kinds, ONLY: dp
23 USE pw_pool_types, ONLY: pw_pool_p_type,&
32#include "../base/base_uses.f90"
33
34 IMPLICIT NONE
35 PRIVATE
36
37 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
38 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'pw_env_types'
39
40 PUBLIC :: pw_env_type
42
43!***
44
45! **************************************************************************************************
46!> \brief contained for different pw related things
47!> \param pw_pools pools for multigrids
48!> \param rs_descs descriptors for the realspace grids
49!> \param rs_grids the realspace grids
50!> \param xc_pw_pool the pool used for xc calculation on grid (might be the
51!> same as the finest, or finer still).
52!> \param vdw_pw_pool the pool used for vdw-nl calculation on grid (might be the
53!> same or a grid with a new cutoff
54!> \param gridlevel_info gaussian gridlevel info
55!> \param cube_info info on cube and max sphere size for multigrids
56!> \param aux_bas which multigrid is the auxiliar basis
57!>
58!> readonly attributes
59!> \param auxbas_pw_pool a pool that allocates grids in the auxiliary basis
60!> \param auxbas_rs_desc real space grid in the auxiliary basis, be careful
61!> in parallel nsmax is chosen with multigrid in mind!
62!> \note
63!> be careful in parallel nsmax for the rs_grids is chosen with
64!> multigrid in mind! (well not as of this writing but...)
65!> \par History
66!> 10.2002 created [fawzi]
67!> 04.2003 added rs grid pools [fawzi]
68!> \author Fawzi Mohamed
69! **************************************************************************************************
71 INTEGER :: ref_count = -1
72 INTEGER :: auxbas_grid = 0
73 TYPE(pw_pool_p_type), DIMENSION(:), POINTER :: pw_pools => null()
74 TYPE(pw_pool_type), POINTER :: xc_pw_pool => null()
75 TYPE(pw_pool_type), POINTER :: vdw_pw_pool => null()
77 DIMENSION(:), POINTER :: rs_descs => null()
79 DIMENSION(:), POINTER :: rs_grids => null()
80 TYPE(gridlevel_info_type), POINTER :: gridlevel_info => null()
81 TYPE(cube_info_type), DIMENSION(:), POINTER :: cube_info => null()
82 TYPE(pw_poisson_type), POINTER :: poisson_env => null()
83 TYPE(section_vals_type), POINTER :: interp_section => null()
84 ! store current cell, used to rebuild lazily.
85 REAL(kind=dp), DIMENSION(3, 3) :: cell_hmat = -1.0_dp
86 END TYPE pw_env_type
87
88CONTAINS
89
90! **************************************************************************************************
91!> \brief returns the various attributes of the pw env
92!> \param pw_env the einvironment you want info about
93!> \param pw_pools ...
94!> \param cube_info ...
95!> \param gridlevel_info ...
96!> \param auxbas_pw_pool ...
97!> \param auxbas_grid ...
98!> \param auxbas_rs_desc ...
99!> \param auxbas_rs_grid ...
100!> \param rs_descs ...
101!> \param rs_grids ...
102!> \param xc_pw_pool ...
103!> \param vdw_pw_pool ...
104!> \param poisson_env ...
105!> \param interp_section ...
106!> \par History
107!> 10.2002 created [fawzi]
108!> \author Fawzi Mohamed
109! **************************************************************************************************
110 SUBROUTINE pw_env_get(pw_env, pw_pools, cube_info, gridlevel_info, &
111 auxbas_pw_pool, auxbas_grid, auxbas_rs_desc, auxbas_rs_grid, rs_descs, rs_grids, &
112 xc_pw_pool, vdw_pw_pool, poisson_env, interp_section)
113 TYPE(pw_env_type), INTENT(IN) :: pw_env
114 TYPE(pw_pool_p_type), DIMENSION(:), OPTIONAL, &
115 POINTER :: pw_pools
116 TYPE(cube_info_type), DIMENSION(:), OPTIONAL, &
117 POINTER :: cube_info
118 TYPE(gridlevel_info_type), OPTIONAL, POINTER :: gridlevel_info
119 TYPE(pw_pool_type), OPTIONAL, POINTER :: auxbas_pw_pool
120 INTEGER, INTENT(out), OPTIONAL :: auxbas_grid
121 TYPE(realspace_grid_desc_type), OPTIONAL, POINTER :: auxbas_rs_desc
122 TYPE(realspace_grid_type), OPTIONAL, POINTER :: auxbas_rs_grid
123 TYPE(realspace_grid_desc_p_type), DIMENSION(:), &
124 OPTIONAL, POINTER :: rs_descs
125 TYPE(realspace_grid_type), DIMENSION(:), &
126 OPTIONAL, POINTER :: rs_grids
127 TYPE(pw_pool_type), OPTIONAL, POINTER :: xc_pw_pool, vdw_pw_pool
128 TYPE(pw_poisson_type), OPTIONAL, POINTER :: poisson_env
129 TYPE(section_vals_type), OPTIONAL, POINTER :: interp_section
130
131 cpassert(pw_env%ref_count > 0)
132 IF (PRESENT(pw_pools)) pw_pools => pw_env%pw_pools
133 IF (PRESENT(rs_descs)) rs_descs => pw_env%rs_descs
134 IF (PRESENT(rs_grids)) rs_grids => pw_env%rs_grids
135 IF (PRESENT(cube_info)) cube_info => pw_env%cube_info
136 IF (PRESENT(gridlevel_info)) gridlevel_info => pw_env%gridlevel_info
137 IF (PRESENT(auxbas_pw_pool)) THEN
138 auxbas_pw_pool => pw_env%pw_pools(pw_env%auxbas_grid)%pool
139 END IF
140 IF (PRESENT(auxbas_rs_desc)) THEN
141 auxbas_rs_desc => pw_env%rs_descs(pw_env%auxbas_grid)%rs_desc
142 END IF
143 IF (PRESENT(auxbas_rs_grid)) THEN
144 auxbas_rs_grid => pw_env%rs_grids(pw_env%auxbas_grid)
145 END IF
146 IF (PRESENT(auxbas_grid)) auxbas_grid = pw_env%auxbas_grid
147 IF (PRESENT(xc_pw_pool)) xc_pw_pool => pw_env%xc_pw_pool
148 IF (PRESENT(vdw_pw_pool)) vdw_pw_pool => pw_env%vdw_pw_pool
149 IF (PRESENT(poisson_env)) poisson_env => pw_env%poisson_env
150 IF (PRESENT(interp_section)) interp_section => pw_env%interp_section
151 END SUBROUTINE pw_env_get
152
153! **************************************************************************************************
154!> \brief retains the pw_env (see doc/ReferenceCounting.html)
155!> \param pw_env the pw_env to retain
156!> \par History
157!> 10.2002 created [fawzi]
158!> \author Fawzi Mohamed
159! **************************************************************************************************
160 SUBROUTINE pw_env_retain(pw_env)
161 TYPE(pw_env_type), INTENT(INOUT) :: pw_env
162
163 cpassert(pw_env%ref_count > 0)
164 pw_env%ref_count = pw_env%ref_count + 1
165 END SUBROUTINE pw_env_retain
166
167! **************************************************************************************************
168!> \brief releases the given pw_env (see doc/ReferenceCounting.html)
169!> \param pw_env the pw_env to release
170!> \param para_env ...
171!> \par History
172!> 10.2002 created [fawzi]
173!> \author Fawzi Mohamed
174! **************************************************************************************************
175 SUBROUTINE pw_env_release(pw_env, para_env)
176 TYPE(pw_env_type), POINTER :: pw_env
177 TYPE(mp_para_env_type), INTENT(IN), OPTIONAL :: para_env
178
179 INTEGER :: i, igrid_level
180
181 IF (ASSOCIATED(pw_env)) THEN
182 cpassert(pw_env%ref_count > 0)
183 pw_env%ref_count = pw_env%ref_count - 1
184 IF (pw_env%ref_count < 1) THEN
185 IF (ASSOCIATED(pw_env%poisson_env)) THEN
186 CALL pw_env%poisson_env%release()
187 DEALLOCATE (pw_env%poisson_env)
188 END IF
189 CALL pw_pools_dealloc(pw_env%pw_pools)
190 IF (ASSOCIATED(pw_env%gridlevel_info)) THEN
191 CALL destroy_gaussian_gridlevel(pw_env%gridlevel_info, para_env)
192 DEALLOCATE (pw_env%gridlevel_info)
193 END IF
194 IF (ASSOCIATED(pw_env%cube_info)) THEN
195 DO igrid_level = 1, SIZE(pw_env%cube_info)
196 CALL destroy_cube_info(pw_env%cube_info(igrid_level))
197 END DO
198 DEALLOCATE (pw_env%cube_info)
199 END IF
200 CALL pw_pool_release(pw_env%xc_pw_pool)
201 CALL pw_pool_release(pw_env%vdw_pw_pool)
202 IF (ASSOCIATED(pw_env%rs_descs)) THEN
203 DO i = 1, SIZE(pw_env%rs_descs)
204 CALL rs_grid_release_descriptor(pw_env%rs_descs(i)%rs_desc)
205 END DO
206 DEALLOCATE (pw_env%rs_descs)
207 END IF
208 IF (ASSOCIATED(pw_env%rs_grids)) THEN
209 DO i = 1, SIZE(pw_env%rs_grids)
210 CALL rs_grid_release(pw_env%rs_grids(i))
211 END DO
212 DEALLOCATE (pw_env%rs_grids)
213 END IF
214 DEALLOCATE (pw_env)
215 END IF
216 END IF
217 NULLIFY (pw_env)
218 END SUBROUTINE pw_env_release
219
220END MODULE pw_env_types
for a given dr()/dh(r) this will provide the bounds to be used if one wants to go over a sphere-subre...
Definition cube_utils.F:18
subroutine, public destroy_cube_info(info)
...
Definition cube_utils.F:185
subroutine, public destroy_gaussian_gridlevel(gridlevel_info, para_env)
...
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to the message passing library MPI.
container for various plainwaves related things
subroutine, public pw_env_retain(pw_env)
retains the pw_env (see doc/ReferenceCounting.html)
subroutine, public pw_env_release(pw_env, para_env)
releases the given pw_env (see doc/ReferenceCounting.html)
subroutine, public pw_env_get(pw_env, pw_pools, cube_info, gridlevel_info, auxbas_pw_pool, auxbas_grid, auxbas_rs_desc, auxbas_rs_grid, rs_descs, rs_grids, xc_pw_pool, vdw_pw_pool, poisson_env, interp_section)
returns the various attributes of the pw env
functions related to the poisson solver on regular grids
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
subroutine, public pw_pools_dealloc(pools)
deallocates the given pools (releasing each of the underlying pools)
subroutine, public pw_pool_release(pool)
releases the given pool (see cp2k/doc/ReferenceCounting.html)
subroutine, public rs_grid_release_descriptor(rs_desc)
releases the given rs grid descriptor (see doc/ReferenceCounting.html)
subroutine, public rs_grid_release(rs_grid)
releases the given rs grid (see doc/ReferenceCounting.html)
stores all the informations relevant to an mpi environment
contained for different pw related things
environment for the poisson solver
to create arrays of pools
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...