Octopus
pcm_eom.F90
Go to the documentation of this file.
1!! Copyright (C) 2017 Gabriel Gil, Stefano Corni, Silvio Pipolo, Carlo Andrea Rozzi
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18#include "global.h"
19
20module pcm_eom_oct_m
21 use debug_oct_m
22 use global_oct_m
23 use io_oct_m
24 use, intrinsic :: iso_fortran_env
25 use math_oct_m
29 implicit none
30
31 private
32 public :: &
41 pcm_nuclei, &
46 save
47
49 type :: pcm_tessera_t
50 real(real64) :: point(1:3)
51 real(real64) :: area
52 real(real64) :: normal(1:3)
53 real(real64) :: r_sphere
54 end type pcm_tessera_t
55
56 type(pcm_tessera_t), allocatable :: cts_act(:)
57 integer :: nts_act
58
60 type :: debye_param_t
61 real(real64) :: eps_0
62 real(real64) :: eps_d
63 real(real64) :: tau
64 end type debye_param_t
65
69 type :: drude_param_t
70 real(real64) :: aa
71 real(real64) :: gm
72 real(real64) :: w0
73 end type drude_param_t
74
75 integer, parameter :: &
76 PCM_DEBYE_MODEL = 1, &
78
79 integer, parameter :: &
80 PCM_ELECTRONS = 0, &
81 pcm_nuclei = 1, &
83 pcm_kick = 3, &
85
86
87 type(debye_param_t) :: deb
88 type(drude_param_t) :: drl
89
90
91 integer :: which_eom
93
94 integer :: which_eps
95
96 real(real64) :: dt
97
98 ! polarization charges and variation of it in the previous iteration:
99 real(real64), allocatable :: q_tp(:), dq_tp(:)
100 real(real64), allocatable :: qext_tp(:), dqext_tp(:)
101 real(real64), allocatable :: qkick_tp(:), dqkick_tp(:)
102
103 real(real64), allocatable :: pot_tp(:)
104 real(real64), allocatable :: potext_tp(:)
105
106 ! See Chem.Phys.Lett. 429 (2006) 310-316 for Velocity-Verlet (VV) algorithm...
107 real(real64) :: f1, f2, f3, f4, f5
108 ! analogous to force in the equation of motion for the pol.charges, prev. iter.
109 real(real64), allocatable :: force_tp(:)
110 real(real64), allocatable :: force_qext_tp(:)
111 real(real64), allocatable :: force_qkick_tp(:)
112
113 ! In Ref.1 - J.Phys.Chem.A 2015, 119, 5405-5416... - Debye dielectric func. (eps)
114 ! In Ref.2 - In J. Phys. Chem. C 2016, 120, 28774−28781... - Drude-Lorentz eps
115 real(real64), allocatable :: cals(:,:), cald(:,:)
116 real(real64), allocatable :: eigv(:), eigt(:,:)
117 real(real64), allocatable :: sm12(:,:), sp12(:,:)
119 real(real64), allocatable :: matq0(:,:), matqd(:,:)
120 real(real64), allocatable :: matq0_lf(:,:), matqd_lf(:,:)
121 ! !! \f$ \tilde{Q} \f$ and R matrices from Eq.(38)-(39) (Ref.1), respectively
122 ! !! Q_f and Q_{\omega} from Eq.(17)-(16) (Ref.2), respectively
123 real(real64), allocatable :: matqv(:,:), matqq(:,:)
124 real(real64), allocatable :: matqv_lf(:,:)
125 ! !! Q^{IEF(d)}_d, \f$ \tilde{Q} \f$ and R matrices enter the EOM in eq.(37), Ref.1
126 ! !! Q_f and Q_{\omega} matrices enter the EOM in eq.(15), Ref.2
127 ! !! N.B.: matrices R (in case of Debye) and Q_{\omega} (in case of Drude-Lorentz),
128 ! !! i.e., matqq in this implementation,
129 ! !! are the same in the EOMs for polarization charges due to the solute or ext.pot.
130
131 logical :: enough_initial = .false.
132
133contains
134
135 !------------------------------------------------------------------------------------------------------------------------------
138 subroutine pcm_charges_propagation(q_t, pot_t, this_dt, this_cts_act, input_asc, this_eom, &
139 this_eps, namespace, this_deb, this_drl)
140 save
141 real(real64), intent(out) :: q_t(:)
142 real(real64), intent(in) :: pot_t(:)
143 real(real64), intent(in) :: this_dt
144 type(pcm_tessera_t), intent(in) :: this_cts_act(:)
145 logical, intent(in) :: input_asc
146 integer, intent(in) :: this_eom
147 ! !! or due to external potential ('external')
148 integer, intent(in) :: this_eps
149 ! !!(PCM_DEBYE_MODEL) or Drude-Lorentz (PCM_DRUDE_MODEL)
150 type(namespace_t), intent(in) :: namespace
151 type(debye_param_t), optional, intent(in) :: this_deb
152 type(drude_param_t), optional, intent(in) :: this_drl
154 logical :: firsttime = .true.
155 logical :: initial_electron = .true.
156 logical :: initial_external = .true.
157 logical :: initial_kick = .true.
158
160
161 which_eom = this_eom
162 if (which_eom /= pcm_electrons .and. which_eom /= pcm_external_potential .and. &
163 which_eom /= pcm_external_plus_kick .and. which_eom /= pcm_kick) then
164 message(1) = "pcm_charges_propagation: EOM evolution of PCM charges can only be due to solute electrons"
165 message(2) = "or external potential (including the kick)."
166 call messages_fatal(2, namespace=namespace)
167 end if
169 if (firsttime) then
170 dt = this_dt
171 nts_act = size(this_cts_act)
172 if (size(q_t) /= nts_act) then
173 message(1) = "pcm_charges_propagation: Number of tesserae do not coincide with size of PCM charges array."
174 call messages_fatal(1, namespace=namespace)
175 end if
176
177 safe_allocate(cts_act(1:nts_act))
178 cts_act = this_cts_act
179
180 which_eps = this_eps
181 select case (which_eps)
182 case (pcm_debye_model)
183 if (present(this_deb)) then
184 deb = this_deb
185 else
186 message(1) = "pcm_charges_propagation: EOM-PCM error. Debye dielectric function requires three parameters."
187 call messages_fatal(1, namespace=namespace)
188 end if
190 if (present(this_drl)) then
191 drl = this_drl
192 else
193 message(1) = "pcm_charges_propagation: EOM-PCM error. Drude-Lorentz dielectric function requires three parameters."
194 call messages_fatal(1, namespace=namespace)
195 end if
196 case default
197 message(1) = "pcm_charges_propagation: EOM-PCM error. Only Debye or Drude-Lorent dielectric models are allowed."
198 call messages_fatal(1, namespace=namespace)
199 end select
201 if (abs(deb%tau) <= m_epsilon) then
202 message(1) = "pcm_charges_propagation: EOM-PCM error. Debye EOM-PCM require a non-null Debye relaxation time."
203 call messages_fatal(1, namespace=namespace)
204 end if
205 firsttime = .false.
206 end if
207
209 if (input_asc) then
210 select case (which_eps)
211 case (pcm_debye_model)
212 ! initialize pcm charges due to electrons, external potential or kick
213 call pcm_charges_from_input_file(q_t, pot_t, namespace)
214
216 return
217 case default
218 message(1) = "pcm_charges_propagation: EOM-PCM error. Only Debye EOM-PCM can startup from input charges."
219 call messages_fatal(1, namespace=namespace)
220 end select
221 end if
222
223 if ((initial_electron .and. which_eom == pcm_electrons) .or. &
224 (initial_external .and. (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick)) .or. &
225 (initial_kick .and. which_eom == pcm_kick)) then
226
227 ! initialize pcm matrices
228 call pcm_bem_init(namespace)
229
230 ! initialize pcm charges due to electrons, external potential or kick
231 call init_charges(q_t, pot_t, namespace)
232
233 if (initial_electron .and. which_eom == pcm_electrons) initial_electron = .false.
234 if (initial_external .and. (which_eom == pcm_external_potential .or. &
235 which_eom == pcm_external_plus_kick)) initial_external = .false.
236 if (initial_kick .and. which_eom == pcm_kick) initial_kick = .false.
237
238 else
239
240 ! propagate pcm charges due to electrons or external potential (including possible kick)
241 if (which_eps == pcm_debye_model) then
242 call pcm_ief_prop_deb(q_t, pot_t)
243 else if (which_eps == pcm_drude_model) then
244 call pcm_ief_prop_vv_ief_drl(q_t, pot_t)
245 end if
246
247 end if
248
250 end subroutine pcm_charges_propagation
251
252 !------------------------------------------------------------------------------------------------------------------------------
254 subroutine pcm_charges_from_input_file(q_t, pot_t, namespace)
255 real(real64), intent(out) :: q_t(:)
256 real(real64), intent(in) :: pot_t(:)
257 type(namespace_t), intent(in) :: namespace
258
259 real(real64) :: aux1(3)
260 integer :: aux2
261 integer :: asc_unit
262 integer :: ia
263
265
266 if (which_eom == pcm_electrons) then
267 safe_allocate(q_tp(1:nts_act))
268 asc_unit = io_open(pcm_dir//'ASC_e.dat', namespace, action='read')
269 do ia = 1, nts_act
270 read(asc_unit,*) aux1, q_t(ia), aux2
271 end do
272 q_tp = q_t
273
274 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick) then
275 safe_allocate(qext_tp(1:nts_act))
276 asc_unit = io_open(pcm_dir//'ASC_ext.dat', namespace, action='read')
277 do ia = 1, nts_act
278 read(asc_unit,*) aux1, q_t(ia), aux2
279 end do
280 qext_tp = q_t
281
282 else if (which_eom == pcm_kick) then
283 safe_allocate(qkick_tp(1:nts_act))
284 asc_unit = io_open(pcm_dir//'ASC_kick.dat', namespace, action='read')
285 do ia = 1, nts_act
286 read(asc_unit,*) aux1, q_t(ia), aux2
287 end do
288 qkick_tp = q_t
289 end if
290 call io_close(asc_unit)
291
292 safe_allocate(pot_tp(1:nts_act))
293 pot_tp = pot_t
294
296 end subroutine pcm_charges_from_input_file
297
298 !------------------------------------------------------------------------------------------------------------------------------
300 subroutine init_charges(q_t,pot_t, namespace)
301 real(real64), intent(out) :: q_t(:)
302 real(real64), intent(in) :: pot_t(:)
303 type(namespace_t), intent(in) :: namespace
304
305 push_sub(init_charges)
306
307 if (which_eom == pcm_electrons) then
308 ! Here we consider the potential at any earlier time equal to the initial potential.
309 ! Therefore, we can suppose that the solvent is already in equilibrium with the initial solute potential.
310 ! The latter is valid when starting the propagation from the ground state but does not hold in general.
311 message(1) = 'EOM-PCM for solvent polarization due to solute electrons considers that you start from a ground state run.'
312 call messages_warning(1, namespace=namespace)
313
314 safe_allocate(pot_tp(1:nts_act))
315 pot_tp = pot_t
316
317 ! applying the static IEF-PCM response matrix (corresponging to epsilon_0) to the initial potential
318 q_t = matmul(matq0, pot_t)
319
320 safe_allocate(q_tp(1:nts_act))
321 q_tp = q_t
322
323 if (which_eps == pcm_drude_model) then
324 safe_allocate(dq_tp(1:nts_act))
325 safe_allocate(force_tp(1:nts_act))
326 dq_tp = m_zero
327 force_tp = m_zero
328 end if
329
330 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick) then
331 ! Here (instead) we consider zero the potential at any earlier time.
332 ! Therefore, the solvent is not initially in equilibrium with the external potential unless its initial value is zero.
333
334 safe_allocate(potext_tp(1:nts_act))
335 potext_tp = pot_t
336
337 ! applying the dynamic IEF-PCM response matrix (for epsilon_d) to the initial potential
338 q_t = matmul(matqd_lf, pot_t)
339
340 safe_allocate(qext_tp(1:nts_act))
341 qext_tp = q_t
342
343 if (which_eps == pcm_drude_model) then
344 safe_allocate(dqext_tp(1:nts_act))
345 safe_allocate(force_qext_tp(1:nts_act))
346 dqext_tp = m_zero
347 force_qext_tp = m_zero
348 end if
349
350 else if (which_eom == pcm_kick) then
351
352 if (which_eps == pcm_drude_model) then
353 safe_allocate(dqkick_tp(1:nts_act))
354 safe_allocate(force_qkick_tp(1:nts_act))
355 dqkick_tp = m_zero
356 force_qkick_tp = m_zero
357 end if
358
359 if (which_eps == pcm_drude_model) then
360 dqkick_tp = matmul(matqv_lf, pot_t)*dt
361 else
362 q_t = matmul(matqv_lf - matmul(matqq, matqd_lf), pot_t)
363 end if
364
365 safe_allocate(qkick_tp(1:nts_act))
366 qkick_tp = q_t
367
368 end if
369
370 ! initializing Velocity-Verlet algorithm for the integration of EOM-PCM for Drude-Lorentz
371 if (which_eps == pcm_drude_model) call init_vv_propagator
372
373 pop_sub(init_charges)
374 end subroutine init_charges
375
376 !------------------------------------------------------------------------------------------------------------------------------
379 subroutine pcm_ief_prop_deb(q_t, pot_t)
380 real(real64), intent(out) :: q_t(:)
381 real(real64), intent(in) :: pot_t(:)
382
383 push_sub(pcm_ief_prop_deb)
384
385 if (which_eom == pcm_electrons) then
386 ! Eq.(47) in S. Corni, S. Pipolo and R. Cammi, J.Phys.Chem.A 2015, 119, 5405-5416.
387 q_t(:) = q_tp(:) - dt*matmul(matqq, q_tp) + &
388 dt*matmul(matqv, pot_tp) + &
389 matmul(matqd, pot_t - pot_tp)
390
391 q_tp = q_t
392
393 pot_tp = pot_t
394
395 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick) then
396 ! analogous to Eq.(47) ibid. with different matrices
397 q_t(:) = qext_tp(:) - dt*matmul(matqq, qext_tp) + &
398 dt*matmul(matqv_lf, potext_tp) + &
399 matmul(matqd_lf, pot_t - potext_tp) ! N.B. matqq
400
401 qext_tp = q_t
402
403 potext_tp = pot_t
404
405 else if (which_eom == pcm_kick) then
406 ! simplifying for kick
407 q_t(:) = qkick_tp(:) - dt*matmul(matqq, qkick_tp) ! N.B. matqq
408
409 qkick_tp = q_t
410
411 end if
412
413 pop_sub(pcm_ief_prop_deb)
414 end subroutine pcm_ief_prop_deb
415
416 !------------------------------------------------------------------------------------------------------------------------------
422 subroutine init_vv_propagator
423 push_sub(init_vv_propagator)
424
425 f1 = dt*(m_one - dt*m_half*drl%gm)
426 f2 = dt*dt*m_half
427 f3 = m_one - dt*drl%gm*(m_one - dt*m_half*drl%gm)
428 f4 = m_half*dt
429 f5 = drl%gm*f2
430
431 pop_sub(init_vv_propagator)
432 end subroutine init_vv_propagator
433
434 !------------------------------------------------------------------------------------------------------------------------------
437 subroutine pcm_ief_prop_vv_ief_drl(q_t, pot_t)
438 real(real64), intent(out) :: q_t(:)
439 real(real64), intent(in) :: pot_t(:)
440
441 real(real64) :: force(nts_act)
442
444
445 if (which_eom == pcm_electrons) then
446 ! From Eq.(15) S. Pipolo and S. Corni, J.Phys.Chem.C 2016, 120, 28774-28781.
447 ! Using the scheme in Eq.(21) and (17) of E. Vanden-Eijnden, G. Ciccotti, Chem.Phys.Lett. 429 (2006) 310-316.
448 q_t = q_tp + f1*dq_tp + f2*force_tp
449 force = -matmul(matqq, q_t) + matmul(matqv, pot_t)
450 dq_tp = f3*dq_tp + f4*(force+force_tp) -f5*force_tp
451 force_tp = force
452 q_tp = q_t
453
454 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick) then
455 ! analagous to Eq.(15) ibid. with different matrices
456 q_t = qext_tp + f1*dqext_tp + f2*force_qext_tp
457 force = -matmul(matqq, q_t) + matmul(matqv_lf, pot_t) ! N.B. matqq
458 dqext_tp = f3*dqext_tp + f4*(force + force_qext_tp) -f5*force_qext_tp
459 force_qext_tp = force
460 q_tp = q_t
461
462 else if (which_eom == pcm_kick) then
463 ! simplifying for kick
464 q_t = qkick_tp + f1*dqkick_tp + f2*force_qkick_tp
465 force = -matmul(matqq, q_t) ! N.B. matqq
466 dqkick_tp = f3*dqkick_tp + f4*(force + force_qkick_tp) -f5*force_qkick_tp
467 force_qkick_tp = force
468 q_tp = q_t
469
470 end if
471
472 pot_tp = pot_t
473
475 end subroutine pcm_ief_prop_vv_ief_drl
476
477 !------------------------------------------------------------------------------------------------------------------------------
479 subroutine pcm_bem_init(namespace)
480 type(namespace_t), intent(in) :: namespace
481 integer :: itess, jtess
482 integer :: pcmmat0_unit, pcmmatd_unit
483
484 push_sub(pcm_bem_init)
485
486 if (which_eom == pcm_electrons) then
487 safe_allocate(matq0(1:nts_act, 1:nts_act))
488 safe_allocate(matqd(1:nts_act, 1:nts_act))
489 safe_allocate(matqv(1:nts_act, 1:nts_act))
490 if (.not. allocated(matqq)) then
491 safe_allocate(matqq(1:nts_act, 1:nts_act))
492 end if
493 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick .or. which_eom == pcm_kick) then
494 safe_allocate(matq0_lf(1:nts_act, 1:nts_act)) ! not used yet
495 safe_allocate(matqd_lf(1:nts_act, 1:nts_act))
496 safe_allocate(matqv_lf(1:nts_act, 1:nts_act))
497 if (.not. allocated(matqq)) then
498 safe_allocate(matqq(1:nts_act, 1:nts_act))
499 end if
500 end if
501 call do_pcm_propmat(namespace)
502
503 if (which_eom == pcm_electrons) then
504 pcmmat0_unit = io_open(pcm_dir//'pcm_matrix_static_from_eom.out', namespace, action='write')
505 pcmmatd_unit = io_open(pcm_dir//'pcm_matrix_dynamic_from_eom.out', namespace, action='write')
506 do jtess = 1, nts_act
507 do itess = 1, nts_act
508 write(pcmmat0_unit,*) matq0(itess, jtess)
509 write(pcmmatd_unit,*) matqd(itess, jtess)
510 end do
511 end do
512 call io_close(pcmmat0_unit)
513 call io_close(pcmmatd_unit)
514 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick) then
515 pcmmat0_unit = io_open(pcm_dir//'pcm_matrix_static_lf_from_eom.out', namespace, action='write')
516 pcmmatd_unit = io_open(pcm_dir//'pcm_matrix_dynamic_lf_from_eom.out', namespace, action='write')
517 do jtess = 1, nts_act
518 do itess = 1, nts_act
519 write(pcmmat0_unit,*) matq0_lf(itess, jtess)
520 write(pcmmatd_unit,*) matqd_lf(itess, jtess)
521 end do
522 end do
523 call io_close(pcmmat0_unit)
524 call io_close(pcmmatd_unit)
525 end if
526
527 pop_sub(pcm_bem_init)
528 end subroutine pcm_bem_init
529
530 !------------------------------------------------------------------------------------------------------------------------------
531
532 subroutine pcm_eom_end()
533 push_sub(pcm_eom_end)
534
535 ! pcm charges
536 safe_deallocate_a(q_tp)
537 safe_deallocate_a(qext_tp)
538 safe_deallocate_a(qkick_tp)
539
540 ! increment pcm charges
541 safe_deallocate_a(dq_tp)
542 safe_deallocate_a(dqext_tp)
543 safe_deallocate_a(dqkick_tp)
544
545 ! force-like term in pcm-eom equation
546 safe_deallocate_a(force_tp)
547 safe_deallocate_a(force_qext_tp)
548 safe_deallocate_a(force_qkick_tp)
549
550 ! pcm-eom bem matrices
551 safe_deallocate_a(matq0)
552 safe_deallocate_a(matqd)
553 safe_deallocate_a(matq0_lf)
554 safe_deallocate_a(matqd_lf)
555 safe_deallocate_a(matqv)
556 safe_deallocate_a(matqv_lf)
557 safe_deallocate_a(matqq)
558
559 safe_deallocate_a(pot_tp)
560 safe_deallocate_a(cts_act)
561
563
564 pop_sub(pcm_eom_end)
565 end subroutine pcm_eom_end
566
567 !------------------------------------------------------------------------------------------------------------------------------
574 subroutine do_pcm_propmat(namespace)
575 type(namespace_t), intent(in) :: namespace
576 save
577 integer :: i, j
578 real(real64), allocatable :: scr4(:,:), scr1(:,:)
579 real(real64), allocatable :: scr2(:,:), scr3(:,:)
580 real(real64), allocatable :: fact1(:), fact2(:)
583 real(real64), allocatable :: Kdiag0(:), Kdiagd(:)
588 real(real64) :: sgn,sgn_lf, fac_eps0, fac_epsd
589 real(real64) :: temp
590
591 logical :: firsttime = .true.
592
593 push_sub(do_pcm_propmat)
594
595 sgn = m_one ! In the case of NP this is -1 because the normal to the cavity is always pointing outward
596 ! and the field acreated by a positive unit charge outside the cavity is directed inward.
597
598 sgn_lf = m_one
599 ! ''local field'' differ from ''standard'' PCM response matrix in some sign changes
600 if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick .or. which_eom == pcm_kick) sgn_lf = -m_one
601
602 safe_allocate(cals(1:nts_act, 1:nts_act))
603 safe_allocate(cald(1:nts_act, 1:nts_act))
604 safe_allocate(kdiag0(1:nts_act))
605 safe_allocate(kdiagd(1:nts_act))
606 safe_allocate(fact1(1:nts_act))
607 safe_allocate(fact2(1:nts_act))
608
609 ! generate Calderon S and D matrices
610 do i = 1, nts_act
611 do j = 1, nts_act
612 call green_s(i, j, temp)
613 cals(i, j) = temp
614 call green_d(i, j, temp)
615 cald(i, j) = temp
616 end do
617 end do
618 if (firsttime) then
619 call allocate_ts_matrix()
620 call do_ts_matrix(namespace)
621 firsttime = .false.
622 end if
623 safe_deallocate_a(cals)
624 safe_deallocate_a(cald)
626 safe_allocate(scr4(1:nts_act, 1:nts_act))
627 safe_allocate(scr1(1:nts_act, 1:nts_act))
628 safe_allocate(scr2(1:nts_act, 1:nts_act))
629 safe_allocate(scr3(1:nts_act, 1:nts_act))
630
631 if (which_eps == pcm_debye_model) then
632 if (.not. is_close(deb%eps_0, m_one)) then
633 fac_eps0 = (deb%eps_0 + m_one)/(deb%eps_0 - m_one)
634 kdiag0(:) = sgn_lf*(m_two*m_pi - sgn*sgn_lf*eigv(:))/(m_two*m_pi*fac_eps0 - sgn*eigv(:)) ! Eq.(14) with eps_0 in Ref.1
635 else
636 kdiag0(:) = m_zero
637 end if
638 if (.not. is_close(deb%eps_d, m_one)) then
639 fac_epsd = (deb%eps_d + m_one)/(deb%eps_d - m_one)
640 kdiagd(:) = sgn_lf*(m_two*m_pi - sgn*sgn_lf*eigv(:))/(m_two*m_pi*fac_epsd - sgn*eigv(:)) ! Eq.(14) with eps_d, ibid.
641 else
642 kdiagd(:) = m_zero
643 end if
644 fact1(:) = ((m_two*m_pi - sgn*eigv(:))*deb%eps_0 + m_two*m_pi + eigv(:))/ & ! inverse of Eq.(32), ibid.
645 ((m_two*m_pi - sgn*eigv(:))*deb%eps_d + m_two*m_pi + eigv(:))/deb%tau
646 fact2(:) = kdiag0(:)*fact1(:) ! tau^{-1}K_0 in Eq.(38), ibid.
647
648 else if (which_eps == pcm_drude_model) then
649 kdiagd(:) = m_zero ! from Eq.(10) up in Ref.2
650 fact2(:) = (m_two*m_pi - sgn*eigv(:))*drl%aa/(m_four*m_pi) ! Eq.(10) down
651 do i = 1, nts_act
652 if (fact2(i) < m_zero)fact2(i) = m_zero ! check out
653 end do
654 if (abs(drl%w0) <= m_epsilon) drl%w0 = 1.0e-8_real64 ! check out
655 fact1(:) = fact2(:) + drl%w0*drl%w0 ! Eq.(19), ibid.
656 fact2(:) = sgn_lf*(m_two*m_pi - sgn*sgn_lf*eigv(:))*drl%aa/(m_four*m_pi) ! Eq.(10) down, local field analogous
657 kdiag0(:) = fact2(:)/fact1(:) ! from Eq.(10) up, ibid.
658 end if
659
660 scr3 = matmul(sm12, eigt)
661 scr2 = matmul(transpose(eigt), sp12)
662 scr4 = transpose(scr3)
663 do i = 1, nts_act
664 scr1(:,i) = scr3(:, i)*fact1(i)
665 end do
666 matqq = matmul(scr1, scr2) ! Eq.(39) in Ref.1 and Eq.(16) in Ref.2
667 do i = 1,nts_act
668 scr1(:,i) = scr3(:, i)*fact2(i)
669 end do
670 if (which_eom == pcm_electrons) then
671 matqv = -matmul(scr1, scr4) ! Eq.(38) in Ref.1 and Eq.(17) in Ref.2
672 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick .or. which_eom == pcm_kick) then
673 matqv_lf = -matmul(scr1, scr4) ! local field analogous
674 end if
675 do i = 1, nts_act
676 scr1(:,i) = scr3(:,i)*kdiag0(i)
677 end do
678 if (which_eom == pcm_electrons) then
679 matq0 = -matmul(scr1, scr4) ! from Eq.(14) and (18) for eps_0 in Ref.1
680 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick .or. which_eom == pcm_kick) then
681 matq0_lf = -matmul(scr1, scr4) ! local field analogous (not used yet)
682 end if
683 do i = 1, nts_act
684 scr1(:,i) = scr3(:, i)*kdiagd(i)
685 end do
686 if (which_eom == pcm_electrons) then
687 matqd = -matmul(scr1, scr4) ! from Eq.(14) and (18) for eps_d, ibid.
688 else if (which_eom == pcm_external_potential .or. which_eom == pcm_external_plus_kick .or. which_eom == pcm_kick) then
689 matqd_lf = -matmul(scr1, scr4) ! local field analogous
690 end if
691
692 safe_deallocate_a(scr4)
693 safe_deallocate_a(scr1)
694 safe_deallocate_a(scr2)
695 safe_deallocate_a(scr3)
696 safe_deallocate_a(fact1)
697 safe_deallocate_a(fact2)
698 safe_deallocate_a(kdiag0)
699 safe_deallocate_a(kdiagd)
700
701 if (enough_initial) then
703 end if
704
705 pop_sub(do_pcm_propmat)
706 end subroutine do_pcm_propmat
707
708 !------------------------------------------------------------------------------------------------------------------------------
713 subroutine green_d(i, j, value)
714 integer, intent(in) :: i, j
715 real(real64), intent(out) :: value
716
717 real(real64) :: dist,diff(3)
718
719 push_sub(green_d)
720
721 if (i /= j) then
722 diff = cts_act(i)%point - cts_act(j)%point
723 dist = norm2(diff)
724 value = dot_product(cts_act(j)%normal, diff)/dist**3 ! Eq.(5) in Refs.1-2
725 else
726 value = -1.0694_real64*sqrt(m_four*m_pi*cts_act(i)%area)
727 value = value/(m_two*cts_act(i)%r_sphere)/cts_act(i)%area ! diagonal part is a bit cumbersome
728 end if
729
730 pop_sub(green_d)
731 end subroutine green_d
732
733 !------------------------------------------------------------------------------------------------------------------------------
738 subroutine green_s(i, j, value)
739 integer, intent(in):: i,j
740 real(real64), intent(out) :: value
741
742 real(real64) :: dist,diff(3)
743
744 push_sub(green_s)
745
746 if (i /= j) then
747 diff = cts_act(i)%point - cts_act(j)%point
748 dist = norm2(diff)
749 value = m_one/dist ! Eq.(5) in Refs.1-2
750 else
751 value = 1.0694_real64*sqrt(m_four*m_pi/cts_act(i)%area) ! diagonal part is a bit cumbersome
752 end if
753
754 pop_sub(green_s)
755 end subroutine green_s
756
757 !------------------------------------------------------------------------------------------------------------------------------
758 subroutine allocate_ts_matrix()
759 push_sub(allocate_ts_matrix)
760
761 safe_allocate(eigv(1:nts_act))
762 safe_allocate(eigt(1:nts_act, 1:nts_act))
763 safe_allocate(sm12(1:nts_act, 1:nts_act))
764 safe_allocate(sp12(1:nts_act, 1:nts_act))
765
766 pop_sub(allocate_ts_matrix)
767 end subroutine allocate_ts_matrix
768
769 !------------------------------------------------------------------------------------------------------------------------------
770 subroutine deallocate_ts_matrix()
771 push_sub(deallocate_ts_matrix)
772
773 safe_deallocate_a(eigv)
774 safe_deallocate_a(eigt)
775 safe_deallocate_a(sm12)
776 safe_deallocate_a(sp12)
777
778 pop_sub(deallocate_ts_matrix)
779 end subroutine deallocate_ts_matrix
780
781 !------------------------------------------------------------------------------------------------------------------------------
783 subroutine do_ts_matrix(namespace)
784 type(namespace_t), intent(in) :: namespace
785 integer :: i, j
786 integer :: info, lwork, liwork
787 real(real64), allocatable :: scr1(:,:), scr2(:,:), eigt_t(:,:)
788 real(real64) :: sgn
789 character jobz, uplo
790 integer, allocatable :: iwork(:)
791 real(real64), allocatable :: work(:)
792
793 push_sub(do_ts_matrix)
794
795 safe_allocate(scr1(1:nts_act, 1:nts_act))
796 safe_allocate(scr2(1:nts_act, 1:nts_act))
797 safe_allocate(eigt_t(1:nts_act, 1:nts_act))
798 safe_allocate(work(1:1 + 6*nts_act + 2*nts_act*nts_act))
799 safe_allocate(iwork(1:3 + 5*nts_act))
800
801 sgn = m_one
802
803 jobz = 'V'
804 uplo = 'U'
805 lwork = 1 + 6*nts_act + 2*nts_act*nts_act
806 liwork = 3 + 5*nts_act
807 eigt = cals
808 call dsyevd(jobz, uplo, nts_act, eigt, nts_act, eigv, work, lwork, iwork, liwork, info)
809 do i = 1, nts_act
810 if (eigv(i) < m_zero) then
811 write(message(1),*) "Eigenvalue ", i, " of S when constructing the TS matrix is negative!"
812 write(message(2),*) "I put it to 1e-8"
813 call messages_warning(2, namespace=namespace)
814 eigv(i) = 1.0e-8_real64
815 end if
816 scr1(:,i) = eigt(:,i)*sqrt(eigv(i))
817 end do
818 eigt_t = transpose(eigt)
819 sp12 = matmul(scr1, eigt_t) ! building S^{1/2} to be used in R (Ref.1) and Q_{\omega} (Ref.2)
820 do i = 1, nts_act
821 scr1(:, i) = eigt(:, i)/sqrt(eigv(i))
822 end do
823 sm12 = matmul(scr1, eigt_t) ! building S^{-1/2} to be used in R and \tilde{Q} (Ref.1) and Q_{\omega} and Q_f (Ref.2)
824 do i = 1, nts_act
825 scr1(:,i) = cald(:, i)*cts_act(i)%area
826 end do
827 scr2 = matmul(matmul(sm12, scr1), sp12) ! Eq.(10) in Ref.1 (paragraph after Eq.(9), Ref.2)
828 do j = 1, nts_act
829 do i = 1, nts_act
830 eigt(i, j) = m_half*(scr2(i, j) + scr2(j, i)) ! re-symmetrizing for numerical reasons
831 end do
832 end do
833 call dsyevd(jobz,uplo,nts_act,eigt,nts_act,eigv,work,lwork, &
834 iwork,liwork,info) ! obtaining \Lambda (eigv) and T (eigt), Eq.(10), ibid.
835
836 safe_deallocate_a(work)
837 safe_deallocate_a(iwork)
838 safe_deallocate_a(scr1)
839 safe_deallocate_a(scr2)
840 safe_deallocate_a(eigt_t)
841
842 pop_sub(do_ts_matrix)
843 end subroutine do_ts_matrix
844
845 ! -----------------------------------------------------------------------------
846 subroutine pcm_eom_enough_initial(not_yet_called)
847 logical, intent(out) :: not_yet_called
848
849 push_sub(pcm_eom_enough_initial)
850
851 enough_initial = .true.
852 not_yet_called = .false.
853
855 end subroutine pcm_eom_enough_initial
856
857end module pcm_eom_oct_m
858
859!! Local Variables:
860!! mode: f90
861!! coding: utf-8
862!! End:
double sqrt(double __x) __attribute__((__nothrow__
real(real64), parameter, public m_two
Definition: global.F90:190
real(real64), parameter, public m_zero
Definition: global.F90:188
real(real64), parameter, public m_four
Definition: global.F90:192
real(real64), parameter, public m_pi
some mathematical constants
Definition: global.F90:186
character(len= *), parameter, public pcm_dir
Definition: global.F90:260
real(real64), parameter, public m_epsilon
Definition: global.F90:204
real(real64), parameter, public m_half
Definition: global.F90:194
real(real64), parameter, public m_one
Definition: global.F90:189
Definition: io.F90:114
subroutine, public io_close(iunit, grp)
Definition: io.F90:418
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
Definition: io.F90:352
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:537
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:414
integer, parameter, public pcm_external_plus_kick
Definition: pcm_eom.F90:172
subroutine pcm_bem_init(namespace)
Boundary Element Method (BEM) EOM-IEF-PCM matrices initialization.
Definition: pcm_eom.F90:573
integer, parameter, public pcm_electrons
Definition: pcm_eom.F90:172
integer, parameter, public pcm_kick
Definition: pcm_eom.F90:172
subroutine do_ts_matrix(namespace)
Subroutine to build matrices , , and (notation of Refs.1-2)
Definition: pcm_eom.F90:877
integer, parameter, public pcm_nuclei
Definition: pcm_eom.F90:172
subroutine do_pcm_propmat(namespace)
Subroutine to build the required BEM matrices for the EOM-IEF-PCM for Debye and Drude-Lorentz cases.
Definition: pcm_eom.F90:668
subroutine init_vv_propagator
Subroutine to initialize numerical constants required by the Velocity-Verlet (VV) algorithm.
Definition: pcm_eom.F90:516
subroutine, public pcm_charges_propagation(q_t, pot_t, this_dt, this_cts_act, input_asc, this_eom, this_eps, namespace, this_deb, this_drl)
Driving subroutine for the Equation of Motion (EOM) propagation of the polarization charges within th...
Definition: pcm_eom.F90:233
subroutine pcm_ief_prop_deb(q_t, pot_t)
Euler method for integrating first order EOM for the polarization charges within IEF-PCM in the case ...
Definition: pcm_eom.F90:473
subroutine green_d(i, j, value)
Subroutine to build BEM matrix corresponding to the Calderon operator D, using the Green function of ...
Definition: pcm_eom.F90:807
integer, parameter, public pcm_external_potential
Definition: pcm_eom.F90:172
subroutine deallocate_ts_matrix()
Definition: pcm_eom.F90:864
subroutine init_charges(q_t, pot_t, namespace)
Polarization charges initialization (in equilibrium with the initial potential for electrons)
Definition: pcm_eom.F90:394
integer, parameter, public pcm_drude_model
Definition: pcm_eom.F90:168
subroutine, public pcm_eom_end()
Definition: pcm_eom.F90:626
subroutine pcm_charges_from_input_file(q_t, pot_t, namespace)
Polarization charges initialization from input file.
Definition: pcm_eom.F90:348
subroutine allocate_ts_matrix()
Definition: pcm_eom.F90:852
subroutine green_s(i, j, value)
Subroutine to build BEM matrix corresponding to the Calderon operator S, using the Green function of ...
Definition: pcm_eom.F90:832
subroutine, public pcm_eom_enough_initial(not_yet_called)
Definition: pcm_eom.F90:940
subroutine pcm_ief_prop_vv_ief_drl(q_t, pot_t)
VV algorithm for integrating second order EOM for the polarization charges within IEF-PCM in the case...
Definition: pcm_eom.F90:531
integer, parameter, public pcm_debye_model
Definition: pcm_eom.F90:168
set of parameters for Debye dielectric model
Definition: pcm_eom.F90:153
set of parameters for Drude-Lorentz dielectric model
Definition: pcm_eom.F90:162
tesselation derived type
Definition: pcm_eom.F90:142
int true(void)