44#include "./base/base_uses.f90"
58 LOGICAL :: do_multipoles = .false.
59 INTEGER :: do_ipol = -1
60 INTEGER :: max_multipole = -1
61 INTEGER :: max_ipol_iter = -1
62 INTEGER :: ewald_type = -1
63 INTEGER :: gmax(3) = -1
64 INTEGER :: ns_max = -1
65 INTEGER :: o_spline = -1
66 REAL(kind=
dp) :: precs = 0.0_dp
67 REAL(kind=
dp) :: alpha = 0.0_dp, rcut = 0.0_dp
68 REAL(kind=
dp) :: epsilon = 0.0_dp
69 REAL(kind=
dp) :: eps_pol = 0.0_dp
75 REAL(kind=
dp),
DIMENSION(:, :, :),
POINTER :: interaction_cutoffs => null()
77 REAL(kind=
dp),
DIMENSION(3, 3) :: cell_hmat = -1.0_dp
91 CHARACTER(len=*),
PARAMETER,
PRIVATE :: modulen =
'ewald_environment_types'
121 gmax, ns_max, o_spline, group, para_env, poisson_section, precs, &
122 rcut, do_multipoles, max_multipole, do_ipol, max_ipol_iter, &
123 interaction_cutoffs, cell_hmat)
125 INTEGER,
OPTIONAL :: ewald_type
126 REAL(kind=
dp),
OPTIONAL :: alpha, eps_pol, epsilon
127 INTEGER,
OPTIONAL :: gmax(3), ns_max, o_spline
131 REAL(kind=
dp),
OPTIONAL :: precs, rcut
132 LOGICAL,
INTENT(OUT),
OPTIONAL :: do_multipoles
133 INTEGER,
INTENT(OUT),
OPTIONAL :: max_multipole, do_ipol, max_ipol_iter
134 REAL(kind=
dp),
DIMENSION(:, :, :),
OPTIONAL, &
135 POINTER :: interaction_cutoffs
136 REAL(kind=
dp),
DIMENSION(3, 3),
OPTIONAL :: cell_hmat
138 IF (
PRESENT(ewald_type)) ewald_type = ewald_env%ewald_type
139 IF (
PRESENT(do_multipoles)) do_multipoles = ewald_env%do_multipoles
140 IF (
PRESENT(do_ipol)) do_ipol = ewald_env%do_ipol
141 IF (
PRESENT(max_multipole)) max_multipole = ewald_env%max_multipole
142 IF (
PRESENT(max_ipol_iter)) max_ipol_iter = ewald_env%max_ipol_iter
143 IF (
PRESENT(alpha)) alpha = ewald_env%alpha
144 IF (
PRESENT(precs)) precs = ewald_env%precs
145 IF (
PRESENT(rcut)) rcut = ewald_env%rcut
146 IF (
PRESENT(epsilon)) epsilon = ewald_env%epsilon
147 IF (
PRESENT(eps_pol)) eps_pol = ewald_env%eps_pol
148 IF (
PRESENT(gmax)) gmax = ewald_env%gmax
149 IF (
PRESENT(ns_max)) ns_max = ewald_env%ns_max
150 IF (
PRESENT(o_spline)) o_spline = ewald_env%o_spline
151 IF (
PRESENT(group)) group = ewald_env%para_env
152 IF (
PRESENT(para_env)) para_env => ewald_env%para_env
153 IF (
PRESENT(poisson_section)) poisson_section => ewald_env%poisson_section
154 IF (
PRESENT(interaction_cutoffs)) interaction_cutoffs => &
155 ewald_env%interaction_cutoffs
156 IF (
PRESENT(cell_hmat)) cell_hmat = ewald_env%cell_hmat
179 gmax, ns_max, precs, o_spline, para_env, poisson_section, &
180 interaction_cutoffs, cell_hmat)
183 INTEGER,
OPTIONAL :: ewald_type
184 REAL(kind=
dp),
OPTIONAL :: alpha, epsilon, eps_pol
185 INTEGER,
OPTIONAL :: gmax(3), ns_max
186 REAL(kind=
dp),
OPTIONAL :: precs
187 INTEGER,
OPTIONAL :: o_spline
190 REAL(kind=
dp),
DIMENSION(:, :, :),
OPTIONAL, &
191 POINTER :: interaction_cutoffs
192 REAL(kind=
dp),
DIMENSION(3, 3),
OPTIONAL :: cell_hmat
194 IF (
PRESENT(ewald_type)) ewald_env%ewald_type = ewald_type
195 IF (
PRESENT(alpha)) ewald_env%alpha = alpha
196 IF (
PRESENT(precs)) ewald_env%precs = precs
197 IF (
PRESENT(epsilon)) ewald_env%epsilon = epsilon
198 IF (
PRESENT(eps_pol)) ewald_env%eps_pol = eps_pol
199 IF (
PRESENT(gmax)) ewald_env%gmax = gmax
200 IF (
PRESENT(ns_max)) ewald_env%ns_max = ns_max
201 IF (
PRESENT(o_spline)) ewald_env%o_spline = o_spline
202 IF (
PRESENT(para_env)) ewald_env%para_env => para_env
203 IF (
PRESENT(poisson_section))
THEN
206 ewald_env%poisson_section => poisson_section
208 IF (
PRESENT(interaction_cutoffs)) ewald_env%interaction_cutoffs => &
210 IF (
PRESENT(cell_hmat)) ewald_env%cell_hmat = cell_hmat
225 NULLIFY (ewald_env%poisson_section)
226 CALL para_env%retain()
227 ewald_env%para_env => para_env
228 NULLIFY (ewald_env%interaction_cutoffs)
243 IF (
ASSOCIATED(ewald_env%interaction_cutoffs))
THEN
244 DEALLOCATE (ewald_env%interaction_cutoffs)
260 INTEGER,
DIMENSION(:),
POINTER :: gmax_read
262 REAL(kind=
dp) :: dummy
269 NULLIFY (enum, keyword, section, multipole_section)
276 ewald_env%rcut = 0.0_dp
282 ewald_env%rcut = find_ewald_optimal_value(ewald_env%precs)/ewald_env%alpha
286 SELECT CASE (ewald_env%ewald_type)
289 SELECT CASE (
SIZE(gmax_read, 1))
291 ewald_env%gmax = gmax_read(1)
293 ewald_env%gmax = gmax_read
305 ewald_env%gmax = huge(0)
306 ewald_env%ns_max = huge(0)
311 CALL section_vals_val_get(multipole_section,
"_SECTION_PARAMETERS_", l_val=ewald_env%do_multipoles)
314 IF (ewald_env%do_multipoles)
THEN
315 SELECT CASE (ewald_env%ewald_type)
318 i_val=ewald_env%max_multipole)
321 cpabort(
"Multipole code works at the moment only with standard EWALD sums.")
328 NULLIFY (keyword, enum)
333 WRITE (iw,
'(/,T2,"EWALD| ",A,T67,A14 )')
'Summation is done by:', &
334 adjustr(trim(
enum_i2c(enum, ewald_env%ewald_type)))
335 IF (ewald_env%do_multipoles)
THEN
336 NULLIFY (keyword, enum)
339 WRITE (iw,
'( T2,"EWALD| ",A )')
'Enabled Multipole Method'
340 WRITE (iw,
'( T2,"EWALD| ",A,T67,A14 )')
'Max Term in Multipole Expansion :', &
341 adjustr(trim(
enum_i2c(enum, ewald_env%max_multipole)))
342 WRITE (iw,
'( T2,"EWALD| ",A,T67,3I10 )')
'Max number Iterations for IPOL :', &
343 ewald_env%max_ipol_iter
346 WRITE (iw,
'( T2,"EWALD| ",A,A18,A,T71,F10.4 )') &
347 'Alpha parameter [',
'ANGSTROM^-1',
']', dummy
349 WRITE (iw,
'( T2,"EWALD| ",A,A18,A,T71,F10.4 )') &
350 'Real Space Cutoff [',
'ANGSTROM',
']', dummy
352 SELECT CASE (ewald_env%ewald_type)
354 WRITE (iw,
'( T2,"EWALD| ",A,T51,3I10 )') &
355 'G-space max. Miller index', ewald_env%gmax
357 WRITE (iw,
'( T2,"EWALD| ",A,T71,I10 )') &
358 'Max small-grid points (input) ', ewald_env%ns_max
359 WRITE (iw,
'( T2,"EWALD| ",A,T71,E10.4 )') &
360 'Gaussian tolerance (input) ', ewald_env%epsilon
362 WRITE (iw,
'( T2,"EWALD| ",A,T51,3I10 )') &
363 'G-space max. Miller index', ewald_env%gmax
364 WRITE (iw,
'( T2,"EWALD| ",A,T71,I10 )') &
365 'Spline interpolation order ', ewald_env%o_spline
370 WRITE (iw,
'( T2,"EWALD| ",T73, A )')
'not used'
375 "PRINT%PROGRAM_RUN_INFO")
391 REAL(kind=
dp),
DIMENSION(3, 3),
INTENT(IN) :: hmat
392 LOGICAL,
INTENT(IN),
OPTIONAL :: silent
393 CHARACTER(LEN=*),
OPTIONAL :: pset
395 CHARACTER(LEN=5) :: param
396 INTEGER :: i, iw, n(3)
397 INTEGER,
DIMENSION(:),
POINTER :: gmax_read
398 LOGICAL :: do_print, explicit
399 REAL(kind=
dp) :: alat, cutoff, dummy, omega
404 IF (
PRESENT(silent)) do_print = .NOT. silent
406 IF (
PRESENT(pset)) param = pset
408 ewald_env%do_multipoles = .false.
409 ewald_env%do_ipol = 0
410 ewald_env%eps_pol = 1.e-12_dp
411 ewald_env%max_multipole = 0
412 ewald_env%max_ipol_iter = 0
413 ewald_env%epsilon = 1.e-12_dp
414 ewald_env%ns_max = huge(0)
420 cpabort(
"TB needs EWALD_TYPE SPME")
432 ewald_env%alpha = 1.0_dp
435 ewald_env%alpha = sqrt(
twopi)/omega**(1./3.)
452 ewald_env%o_spline = 6
454 ewald_env%o_spline = 4
462 ewald_env%rcut = find_ewald_optimal_value(ewald_env%precs)/ewald_env%alpha
468 SELECT CASE (
SIZE(gmax_read, 1))
470 ewald_env%gmax = gmax_read(1)
472 ewald_env%gmax = gmax_read
480 cutoff = 45._dp*ewald_env%alpha
483 cutoff = 30._dp*ewald_env%alpha
486 alat = sum(hmat(:, i)**2)
487 cpassert(alat /= 0._dp)
488 ewald_env%gmax(i) = 2*floor(sqrt(2.0_dp*cutoff*alat)/
twopi) + 1
496 IF (iw > 0 .AND. do_print)
THEN
497 WRITE (iw,
'(/,T2,"EWALD| ",A,T67,A14 )')
'Summation is done by:', adjustr(
"SPME")
499 WRITE (iw,
'( T2,"EWALD| ",A,A18,A,T71,F10.4 )') &
500 'Alpha parameter [',
'ANGSTROM^-1',
']', dummy
502 WRITE (iw,
'( T2,"EWALD| ",A,A18,A,T71,F10.4 )') &
503 'Real Space Cutoff [',
'ANGSTROM',
']', dummy
504 WRITE (iw,
'( T2,"EWALD| ",A,T51,3I10 )') &
505 'G-space max. Miller index', ewald_env%gmax
506 WRITE (iw,
'( T2,"EWALD| ",A,T71,I10 )') &
507 'Spline interpolation order ', ewald_env%o_spline
510 "PRINT%PROGRAM_RUN_INFO")
521 FUNCTION find_ewald_optimal_value(precs)
RESULT(value)
522 REAL(kind=
dp) :: precs,
value
524 REAL(kind=
dp) :: func, func1, func2, s, s1, s2
527 func = exp(-s**2)/s**2 - precs
528 cpassert(func > 0.0_dp)
529 DO WHILE (func > 0.0_dp)
531 func = exp(-s**2)/s**2 - precs
537 func2 = exp(-s2**2)/s2**2 - precs
538 func1 = exp(-s1**2)/s1**2 - precs
542 func = exp(-s**2)/s**2 - precs
543 IF (func > 0.0_dp)
THEN
545 ELSE IF (func < 0.0_dp)
THEN
548 IF (abs(func) < 100.0_dp*epsilon(0.0_dp))
EXIT
551 END FUNCTION find_ewald_optimal_value
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
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_create(ewald_env, para_env)
allocates and intitializes a ewald_env
subroutine, public read_ewald_section(ewald_env, ewald_section)
Purpose: read the EWALD section.
subroutine, public ewald_env_release(ewald_env)
releases the given ewald_env (see doc/ReferenceCounting.html)
subroutine, public read_ewald_section_tb(ewald_env, ewald_section, hmat, silent, pset)
Purpose: read the EWALD section for TB methods.
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.
Defines the basic variable types.
integer, parameter, public dp
Definition of mathematical constants and functions.
real(kind=dp), parameter, public twopi
Collection of simple mathematical functions and subroutines.
Interface to the message passing library MPI.
subroutine, public mp_para_env_release(para_env)
releases the para object (to be called when you don't want anymore the shared copy of this object)
This module returns additional info on PW grids.
integer function, dimension(3), public pw_grid_n_for_fft(n, odd)
returns the closest number of points >= n, on which you can perform ffts
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
type of a logger, at the moment it contains just a print level starting at which level it should be l...
to build arrays of pointers
stores all the informations relevant to an mpi environment