(git:34ef472)
ewald_pw_methods.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 pw_methods
10 !> \author CJM
11 ! **************************************************************************************************
13  USE dg_rho0_types, ONLY: dg_rho0_get,&
14  dg_rho0_init,&
15  dg_rho0_set,&
16  dg_rho0_type
17  USE dg_types, ONLY: dg_get,&
18  dg_type
19  USE dgs, ONLY: dg_grid_change
22  ewald_environment_type
23  USE ewald_pw_types, ONLY: ewald_pw_get,&
24  ewald_pw_set,&
25  ewald_pw_type
26  USE input_section_types, ONLY: section_vals_type
27  USE kinds, ONLY: dp
28  USE pw_grid_types, ONLY: pw_grid_type
29  USE pw_grids, ONLY: pw_grid_change
32  USE pw_poisson_types, ONLY: do_ewald_ewald,&
34  do_ewald_pme,&
36  pw_poisson_parameter_type,&
37  pw_poisson_type
38  USE pw_pool_types, ONLY: pw_pool_p_type,&
39  pw_pool_type
40 #include "./base/base_uses.f90"
41 
42  IMPLICIT NONE
43 
44  PRIVATE
45 
46  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'ewald_pw_methods'
47 
48  PUBLIC :: ewald_pw_grid_update
49 
50 CONTAINS
51 
52 ! **************************************************************************************************
53 !> \brief Rescales pw_grids for given box, if necessary
54 !> \param ewald_pw ...
55 !> \param ewald_env ...
56 !> \param cell_hmat ...
57 !> \par History
58 !> none
59 !> \author JGH (15-Mar-2001)
60 ! **************************************************************************************************
61  SUBROUTINE ewald_pw_grid_update(ewald_pw, ewald_env, cell_hmat)
62  TYPE(ewald_pw_type), POINTER :: ewald_pw
63  TYPE(ewald_environment_type), POINTER :: ewald_env
64  REAL(kind=dp), DIMENSION(3, 3) :: cell_hmat
65 
66  INTEGER :: ewald_type, o_spline
67  REAL(dp) :: alpha
68  REAL(kind=dp), DIMENSION(3, 3) :: old_cell_hmat
69  TYPE(dg_type), POINTER :: dg
70  TYPE(pw_poisson_parameter_type) :: poisson_params
71  TYPE(pw_poisson_type), POINTER :: poisson_env
72  TYPE(pw_pool_p_type), DIMENSION(:), POINTER :: pw_pools
73  TYPE(pw_pool_type), POINTER :: pw_big_pool, pw_small_pool
74  TYPE(section_vals_type), POINTER :: poisson_section
75 
76  NULLIFY (pw_big_pool)
77  NULLIFY (pw_small_pool)
78  NULLIFY (dg, poisson_env, poisson_section)
79 
80  CALL ewald_env_get(ewald_env, ewald_type=ewald_type, &
81  alpha=alpha, o_spline=o_spline, &
82  poisson_section=poisson_section, &
83  cell_hmat=old_cell_hmat)
84 
85  IF (all(cell_hmat == old_cell_hmat)) RETURN ! rebuild not needed
86 
87  CALL ewald_env_set(ewald_env, cell_hmat=cell_hmat)
88 
89  SELECT CASE (ewald_type)
90  CASE (do_ewald_ewald)
91  CALL ewald_pw_get(ewald_pw, pw_big_pool=pw_big_pool, &
92  dg=dg, poisson_env=poisson_env)
93  CALL pw_grid_change(cell_hmat, pw_big_pool%pw_grid)
94  CALL ewald_pw_rho0_setup(ewald_env, pw_big_pool%pw_grid, dg)
95  IF (ASSOCIATED(poisson_env)) THEN
96  CALL poisson_env%release()
97  DEALLOCATE (poisson_env)
98  NULLIFY (poisson_env)
99  END IF
100  CALL ewald_pw_set(ewald_pw, pw_big_pool=pw_big_pool, &
101  poisson_env=poisson_env)
102  CASE (do_ewald_pme)
103  CALL ewald_pw_get(ewald_pw, pw_big_pool=pw_big_pool, &
104  pw_small_pool=pw_small_pool, dg=dg, &
105  poisson_env=poisson_env)
106  IF (.NOT. ASSOCIATED(poisson_env)) THEN
107  ALLOCATE (poisson_env)
108  CALL poisson_env%create()
109  CALL ewald_pw_set(ewald_pw, poisson_env=poisson_env)
110  END IF
111  CALL pw_grid_change(cell_hmat, pw_big_pool%pw_grid)
112  CALL dg_grid_change(cell_hmat, pw_big_pool%pw_grid, pw_small_pool%pw_grid)
113  CALL ewald_pw_rho0_setup(ewald_env, pw_small_pool%pw_grid, dg)
114  CALL ewald_pw_set(ewald_pw, pw_big_pool=pw_big_pool, &
115  pw_small_pool=pw_small_pool, &
116  poisson_env=poisson_env)
117  CASE (do_ewald_spme)
118  CALL ewald_pw_get(ewald_pw, pw_big_pool=pw_big_pool, &
119  poisson_env=poisson_env)
120  IF (.NOT. ASSOCIATED(poisson_env)) THEN
121  ALLOCATE (poisson_env)
122  CALL poisson_env%create()
123  END IF
124  CALL pw_grid_change(cell_hmat, pw_big_pool%pw_grid)
125  CALL ewald_pw_set(ewald_pw, pw_big_pool=pw_big_pool, &
126  poisson_env=poisson_env)
127  CASE (do_ewald_none)
128  CASE default
129  cpabort("")
130  END SELECT
131  IF (ASSOCIATED(poisson_env)) THEN
132  ALLOCATE (pw_pools(1))
133  pw_pools(1)%pool => pw_big_pool
134  CALL pw_poisson_read_parameters(poisson_section, poisson_params)
135  poisson_params%ewald_type = ewald_type
136  poisson_params%ewald_o_spline = o_spline
137  poisson_params%ewald_alpha = alpha
138  CALL pw_poisson_set(poisson_env, cell_hmat=cell_hmat, parameters=poisson_params, &
139  use_level=1, pw_pools=pw_pools)
140  DEALLOCATE (pw_pools)
141  END IF
142 
143  END SUBROUTINE ewald_pw_grid_update
144 
145 ! **************************************************************************************************
146 !> \brief Calculates the Fourier transform of the "Ewald function"
147 !> \param ewald_env ...
148 !> \param pw_grid ...
149 !> \param dg ...
150 !> \par History
151 !> none
152 !> \author JGH (15-Mar-2001)
153 ! **************************************************************************************************
154  SUBROUTINE ewald_pw_rho0_setup(ewald_env, pw_grid, dg)
155  TYPE(ewald_environment_type), POINTER :: ewald_env
156  TYPE(pw_grid_type), POINTER :: pw_grid
157  TYPE(dg_type), POINTER :: dg
158 
159  INTEGER :: ewald_type
160  REAL(dp) :: alpha
161  REAL(dp), POINTER :: gcc(:), zet(:)
162  TYPE(dg_rho0_type), POINTER :: dg_rho0
163 
164  CALL ewald_env_get(ewald_env, alpha=alpha, ewald_type=ewald_type)
165  CALL dg_get(dg, dg_rho0=dg_rho0)
166  CALL dg_rho0_get(dg_rho0, gcc=gcc, zet=zet)
167 
168  IF (.NOT. ASSOCIATED(zet)) THEN
169  ALLOCATE (zet(1))
170  END IF
171 
172 ! No contracted Gaussians are used here
173  NULLIFY (gcc)
174 
175  zet(1) = alpha
176  CALL dg_rho0_set(dg_rho0, type=ewald_type, zet=zet)
177 
178  CALL dg_rho0_init(dg_rho0, pw_grid)
179 
180  END SUBROUTINE ewald_pw_rho0_setup
181 
182 END MODULE ewald_pw_methods
183 
subroutine, public dg_rho0_init(dg_rho0, pw_grid)
...
subroutine, public dg_rho0_get(dg_rho0, cutoff_radius, TYPE, grid, kind, gcc, zet, density)
Get the dg_rho0_type.
Definition: dg_rho0_types.F:95
subroutine, public dg_rho0_set(dg_rho0, TYPE, grid, kind, cutoff_radius, gcc, zet, density)
Set the dg_rho0_type.
Definition: dg_rho0_types.F:65
subroutine, public dg_get(dg, dg_rho0)
Get the dg_type.
Definition: dg_types.F:44
Definition: dgs.F:13
subroutine, public dg_grid_change(b_cell_hmat, grid_b, grid_s)
...
Definition: dgs.F:244
subroutine, public ewald_env_set(ewald_env, ewald_type, alpha, epsilon, eps_pol, gmax, ns_max, precs, o_spline, para_env, poisson_section, interaction_cutoffs, cell_hmat)
Purpose: Set the EWALD environment.
subroutine, public ewald_env_get(ewald_env, ewald_type, alpha, eps_pol, epsilon, gmax, ns_max, o_spline, group, para_env, poisson_section, precs, rcut, do_multipoles, max_multipole, do_ipol, max_ipol_iter, interaction_cutoffs, cell_hmat)
Purpose: Get the EWALD environment.
subroutine, public ewald_pw_grid_update(ewald_pw, ewald_env, cell_hmat)
Rescales pw_grids for given box, if necessary.
subroutine, public ewald_pw_set(ewald_pw, pw_big_pool, pw_small_pool, rs_desc, dg, poisson_env)
set the ewald_pw environment to the correct program.
subroutine, public ewald_pw_get(ewald_pw, pw_big_pool, pw_small_pool, rs_desc, poisson_env, dg)
get the ewald_pw environment to the correct program.
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
This module defines the grid data type and some basic operations on it.
Definition: pw_grids.F:36
subroutine, public pw_grid_change(cell_hmat, pw_grid)
Recalculate the g-vectors after a change of the box.
Definition: pw_grids.F:2068
subroutine, public pw_poisson_set(poisson_env, cell_hmat, parameters, pw_pools, use_level, mt_super_ref_pw_grid, dct_pw_grid, force_rebuild)
sets cell, grids and parameters used by the poisson solver You should call this at least once (and se...
Reading of input parameters for the pw_poisson-modules.
subroutine, public pw_poisson_read_parameters(poisson_section, params)
Reads the POISSON input-section and into pw_poisson_parameter_type.
functions related to the poisson solver on regular grids
integer, parameter, public do_ewald_pme
integer, parameter, public do_ewald_ewald
integer, parameter, public do_ewald_none
integer, parameter, public do_ewald_spme
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
Definition: pw_pool_types.F:24