Line data Source code
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 : ! **************************************************************************************************
12 : MODULE ewald_pw_methods
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
20 : USE ewald_environment_types, ONLY: ewald_env_get,&
21 : ewald_env_set,&
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
30 : USE pw_poisson_methods, ONLY: pw_poisson_set
31 : USE pw_poisson_read_input, ONLY: pw_poisson_read_parameters
32 : USE pw_poisson_types, ONLY: do_ewald_ewald,&
33 : do_ewald_none,&
34 : do_ewald_pme,&
35 : do_ewald_spme,&
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 84514 : 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 84514 : 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 84514 : NULLIFY (pw_big_pool)
77 84514 : NULLIFY (pw_small_pool)
78 84514 : 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 84514 : cell_hmat=old_cell_hmat)
84 :
85 913846 : IF (ALL(cell_hmat == old_cell_hmat)) RETURN ! rebuild not needed
86 :
87 15800 : CALL ewald_env_set(ewald_env, cell_hmat=cell_hmat)
88 :
89 1850 : SELECT CASE (ewald_type)
90 : CASE (do_ewald_ewald)
91 : CALL ewald_pw_get(ewald_pw, pw_big_pool=pw_big_pool, &
92 1850 : dg=dg, poisson_env=poisson_env)
93 1850 : CALL pw_grid_change(cell_hmat, pw_big_pool%pw_grid)
94 1850 : CALL ewald_pw_rho0_setup(ewald_env, pw_big_pool%pw_grid, dg)
95 1850 : IF (ASSOCIATED(poisson_env)) THEN
96 0 : CALL poisson_env%release()
97 0 : DEALLOCATE (poisson_env)
98 : NULLIFY (poisson_env)
99 : END IF
100 : CALL ewald_pw_set(ewald_pw, pw_big_pool=pw_big_pool, &
101 1850 : 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 86 : poisson_env=poisson_env)
106 86 : IF (.NOT. ASSOCIATED(poisson_env)) THEN
107 0 : ALLOCATE (poisson_env)
108 0 : CALL poisson_env%create()
109 0 : CALL ewald_pw_set(ewald_pw, poisson_env=poisson_env)
110 : END IF
111 86 : CALL pw_grid_change(cell_hmat, pw_big_pool%pw_grid)
112 86 : CALL dg_grid_change(cell_hmat, pw_big_pool%pw_grid, pw_small_pool%pw_grid)
113 86 : 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 86 : poisson_env=poisson_env)
117 : CASE (do_ewald_spme)
118 : CALL ewald_pw_get(ewald_pw, pw_big_pool=pw_big_pool, &
119 8884 : poisson_env=poisson_env)
120 8884 : IF (.NOT. ASSOCIATED(poisson_env)) THEN
121 0 : ALLOCATE (poisson_env)
122 0 : CALL poisson_env%create()
123 : END IF
124 8884 : 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 8884 : poisson_env=poisson_env)
127 : CASE (do_ewald_none)
128 : CASE default
129 15800 : CPABORT("")
130 : END SELECT
131 15800 : IF (ASSOCIATED(poisson_env)) THEN
132 17940 : ALLOCATE (pw_pools(1))
133 8970 : pw_pools(1)%pool => pw_big_pool
134 8970 : CALL pw_poisson_read_parameters(poisson_section, poisson_params)
135 8970 : poisson_params%ewald_type = ewald_type
136 8970 : poisson_params%ewald_o_spline = o_spline
137 8970 : poisson_params%ewald_alpha = alpha
138 : CALL pw_poisson_set(poisson_env, cell_hmat=cell_hmat, parameters=poisson_params, &
139 8970 : use_level=1, pw_pools=pw_pools)
140 8970 : DEALLOCATE (pw_pools)
141 : END IF
142 :
143 338056 : 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 1936 : 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 1936 : REAL(dp), POINTER :: gcc(:), zet(:)
162 : TYPE(dg_rho0_type), POINTER :: dg_rho0
163 :
164 1936 : CALL ewald_env_get(ewald_env, alpha=alpha, ewald_type=ewald_type)
165 1936 : CALL dg_get(dg, dg_rho0=dg_rho0)
166 1936 : CALL dg_rho0_get(dg_rho0, gcc=gcc, zet=zet)
167 :
168 1936 : IF (.NOT. ASSOCIATED(zet)) THEN
169 907 : ALLOCATE (zet(1))
170 : END IF
171 :
172 : ! No contracted Gaussians are used here
173 1936 : NULLIFY (gcc)
174 :
175 1936 : zet(1) = alpha
176 1936 : CALL dg_rho0_set(dg_rho0, TYPE=ewald_type, zet=zet)
177 :
178 1936 : CALL dg_rho0_init(dg_rho0, pw_grid)
179 :
180 1936 : END SUBROUTINE ewald_pw_rho0_setup
181 :
182 : END MODULE ewald_pw_methods
183 :
|