Skip to content

Commit 2c67e77

Browse files
committed
Merge branch 'master' into fortitude
2 parents eab6bc5 + a781b39 commit 2c67e77

File tree

41 files changed

+1659
-96
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

41 files changed

+1659
-96
lines changed

sample_inputs/input.in.sh

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,8 @@ inose=0, ! NVE ensemble (thermostat turned OFF)
2222
&sh
2323
istate_init=2, ! initial electronic state (1 is ground state)
2424
nstate=3, ! number of electronic states
25+
couplings='analytic', ! non-adiabatic coupling terms 'analytic', 'baeck-an', 'none'
26+
velocity_rescaling='nac_then_velocity' ! momentum adjustment along either 'nac_then_velocity' or 'velocity'
2527
deltaE=2.0, ! maximum energy difference (eV) between states for which we calculate NA coupling
2628
PopThr=0.001, ! minimum population of either state, for which we compute NA coupling
2729
EnergyDifThr=0.50, ! maximum energy difference between two consecutive steps

src/files.F90

Lines changed: 44 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -170,26 +170,7 @@ subroutine files_init(isbc, phase, ndist, nang, ndih)
170170
end if
171171

172172
if (ipimd == 2) then
173-
open (UPOP, file=chfiles(UPOP), access=chaccess, action='write')
174-
open (UPROB, file=chfiles(UPROB), access=chaccess, action='write')
175-
open (UPES, file=chfiles(UPES), access=chaccess, action='write')
176-
open (UNACME, file=chfiles(UNACME), access=chaccess, action='write')
177-
open (UDOTPROD, file=chfiles(UDOTPROD), access=chaccess, action='write')
178-
179-
if (idebug > 1) then
180-
open (UBKL, file=chfiles(UBKL), access=chaccess, action='write')
181-
open (UWFCOEF, file=chfiles(UWFCOEF), access=chaccess, action='write', recl=250)
182-
if (phase == 1) then
183-
open (UPHASE, file=chfiles(UPHASE), access=chaccess, action='write')
184-
end if
185-
end if
186-
187-
if (pot == '_tera_') then
188-
open (UCHARGES, file=chfiles(UCHARGES), access=chaccess, action='write')
189-
open (UDOTPRODCI, file=chfiles(UDOTPRODCI), access=chaccess, action='write')
190-
open (UDIP, file=chfiles(UDIP), access=chaccess, action='write')
191-
open (UTDIP, file=chfiles(UTDIP), access=chaccess, action='write')
192-
end if
173+
call sh_files_init(phase, chaccess)
193174
end if
194175

195176
if (ipimd /= 2 .and. pot == '_tera_') then
@@ -230,6 +211,49 @@ subroutine files_init(isbc, phase, ndist, nang, ndih)
230211

231212
end subroutine files_init
232213

214+
subroutine sh_files_init(phase, chaccess)
215+
use mod_general, only: idebug, pot
216+
integer, intent(in) :: phase
217+
character(len=10), intent(in) :: chaccess
218+
219+
open (UPOP, file=chfiles(UPOP), access=chaccess, action='write')
220+
open (UPROB, file=chfiles(UPROB), access=chaccess, action='write')
221+
open (UPES, file=chfiles(UPES), access=chaccess, action='write')
222+
open (UDOTPROD, file=chfiles(UDOTPROD), access=chaccess, action='write')
223+
224+
if (idebug > 1) then
225+
open (UBKL, file=chfiles(UBKL), access=chaccess, action='write')
226+
open (UWFCOEF, file=chfiles(UWFCOEF), access=chaccess, action='write', recl=250)
227+
if (phase == 1) then
228+
open (UPHASE, file=chfiles(UPHASE), access=chaccess, action='write')
229+
end if
230+
end if
231+
232+
if (pot == '_tera_') then
233+
open (UCHARGES, file=chfiles(UCHARGES), access=chaccess, action='write')
234+
open (UDOTPRODCI, file=chfiles(UDOTPRODCI), access=chaccess, action='write')
235+
open (UDIP, file=chfiles(UDIP), access=chaccess, action='write')
236+
open (UTDIP, file=chfiles(UTDIP), access=chaccess, action='write')
237+
end if
238+
239+
end subroutine sh_files_init
240+
241+
subroutine nacmefile_init()
242+
use mod_general, only: irest
243+
character(len=10) :: chaccess
244+
245+
! Here we ensure, that previous files are deleted
246+
if (irest == 0) then
247+
chaccess = 'SEQUENTIAL'
248+
else
249+
chaccess = 'APPEND'
250+
end if
251+
252+
! open file
253+
open (UNACME, file=chfiles(UNACME), access=chaccess, action='write')
254+
255+
end subroutine nacmefile_init
256+
233257
subroutine print_file_headers()
234258
use mod_general, only: ipimd, natom
235259
use mod_system, only: names

src/potentials_sh.F90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -125,7 +125,6 @@ subroutine force_nai(x, y, z, fx, fy, fz, eclas)
125125
E2 = (VA + VX) / 2.0D0 + dsqrt((VA - VX)**2.0D0 + 4.0D0 * VXA**2.0D0) / 2.0D0
126126
! nonadiabatic coupling vector in the reduced system
127127
d12 = -(VXA * (dVA - dVX) + (-VA + VX) * dVXA) / (VA**2.0D0 - 2.0D0 * VA * VX + VX**2.0D0 + 4.0D0 * VXA**2.0D0)
128-
d12 = d12 / ANG ! one more conversion necessary
129128
! derivatives of energies
130129
dE1 = (dVA + dVX) / 2.0D0 - (2.0D0 * (VA - VX) * (dVA - dVX) + 8.0D0 * VXA * dVXA) / &
131130
(4.0D0 * dsqrt((VA - VX)**2.0D0 + 4.0D0 * VXA**2.0D0))

src/surfacehop.F90

Lines changed: 167 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -33,20 +33,23 @@ module mod_sh
3333
integer :: substep = 100
3434

3535
! Controls calculations of Non-adiabatic Couplings (NAC)
36-
! 0 - Analytical NAC
37-
! 1 - Numerical Hammers-Schffer-Tully model (currently not implemented)
38-
! 2 - Do not compute couplings
39-
integer :: inac = 0
36+
! couplings = 'analytic' (inac=0) - Analytical NAC (default)
37+
! couplings = 'baeck-an' (inac=1) - Baeck-An couplings
38+
! couplings = 'none' (inac=2) - Do not compute couplings
39+
integer :: inac = 0 ! for working within the code
40+
character(len=50) :: couplings = 'analytic' ! for reading the input file
41+
! energy history array and time-derivate couplings (sigma_ba) necessary for Beack-An couplings
42+
real(DP), allocatable :: en_hist_array(:, :), sigma_ba(:, :) ! sigma_ba is actually the dotproduct
4043

4144
! 1 - Turn OFF hopping
4245
integer :: nohop = 0
4346

4447
! How to adjust velocity after hop:
45-
! 0 - Adjust velocity along the NAC vector (default)
46-
! 1 - Simple velocity rescale
47-
! NOTE: Simple v-rescale is invoked as a fallback
48-
! if there is not enough momentum along the NAC vector.
49-
integer :: adjmom = 0
48+
! velocity_rescaling = 'nac_then_velocity' (adjmom=0) - Adjust velocity along the NAC vector, if not possible,
49+
! try the velocity vector (default)
50+
! velocity_rescaling = 'velocity' (adjmom=1) - Rescale along the velocity vector
51+
integer :: adjmom = 0 ! for working within the code
52+
character(len=50) :: velocity_rescaling = 'nac_then_velocity' ! for reading the input file
5053
! 1 - Reverse momentum direction after frustrated hop
5154
integer :: revmom = 0
5255

@@ -95,8 +98,8 @@ module mod_sh
9598
! of states that are calculated but ignored.
9699
integer :: ignore_state = 0
97100

98-
namelist /sh/ istate_init, nstate, substep, deltae, integ, inac, nohop, phase, decoh_alpha, popthr, ignore_state, &
99-
nac_accu1, nac_accu2, popsumthr, energydifthr, energydriftthr, adjmom, revmom, &
101+
namelist /sh/ istate_init, nstate, substep, deltae, integ, couplings, nohop, phase, decoh_alpha, popthr, ignore_state, &
102+
nac_accu1, nac_accu2, popsumthr, energydifthr, energydriftthr, velocity_rescaling, revmom, &
100103
dE_S0S1_thr, correct_decoherence
101104
save
102105

@@ -108,6 +111,7 @@ subroutine sh_init(x, y, z, vx, vy, vz)
108111
use mod_general, only: irest, natom, pot
109112
use mod_interfaces, only: force_clas
110113
use mod_kinetic, only: ekin_v
114+
use mod_files, only: nacmefile_init
111115
real(DP), intent(inout) :: x(:, :), y(:, :), z(:, :)
112116
real(DP), intent(in) :: vx(:, :), vy(:, :), vz(:, :)
113117
real(DP) :: dum_fx(size(x, 1), size(x, 2))
@@ -153,6 +157,14 @@ subroutine sh_init(x, y, z, vx, vy, vz)
153157
en_array = 0.0D0
154158
en_array_old = en_array
155159

160+
! Initialize the history array we use to calculate the Baeck-An couplings
161+
if (inac == 1) then
162+
allocate (en_hist_array(nstate, 4)) !last 3 energies (1: current, 2: n-1, 3: n-2, 4: n-3)
163+
en_hist_array = 0.0D0
164+
allocate (sigma_ba(nstate, nstate)) !this is equivalent to dotproduct, but I will need to store old and new values
165+
sigma_ba = 0.0D0
166+
end if
167+
156168
allocate (tocalc(nstate, nstate))
157169
tocalc = 0
158170
tocalc(istate, istate) = 1
@@ -165,6 +177,9 @@ subroutine sh_init(x, y, z, vx, vy, vz)
165177
dum_fx = 0.0D0; dum_fy = 0.0D0; dum_fz = 0.0D0
166178
call force_clas(dum_fx, dum_fy, dum_fz, x, y, z, dum_eclas, pot)
167179

180+
! open nacme_all.dat if NACME is calculated
181+
if (inac == 0) call nacmefile_init()
182+
168183
! When restarting, initial SH WF was already read from the restart file
169184
if (irest == 0) then
170185
call sh_set_initialwf(istate)
@@ -227,18 +242,45 @@ subroutine check_sh_parameters()
227242
error = .true.
228243
end if
229244

230-
if (inac > 2 .or. inac < 0) then
231-
write (stderr, '(A)') 'Parameter "inac" must be 0, 1 or 2.'
245+
! converting input 'couplings' into inac which is used in the code
246+
select case (couplings)
247+
case ('analytic')
248+
inac = 0
249+
write (stdout, '(A)') 'Using analytic ab initio couplings.'
250+
case ('baeck-an')
251+
inac = 1
252+
write (stdout, '(A)') 'Using approximate Baeck-An couplings.'
253+
case ('none')
254+
inac = 2
255+
write (stdout, '(A)') 'Ignoring nonadaiabatic couplings.'
256+
case default
257+
write (stderr, '(A)') 'Parameter "couplings" must be "analytic", "baeck-an" or "none".'
232258
error = .true.
233-
end if
259+
end select
260+
261+
! converting input 'velocity_rescaling' into inac which is used in the code
262+
select case (velocity_rescaling)
263+
case ('nac_then_velocity')
264+
adjmom = 0
265+
write (stdout, '(A)') 'Rescaling velocity along the NAC vector after hop.'
266+
write (stdout, '(A)') 'If there is not enough energy, try rescaling along the velocity vector.'
267+
case ('velocity')
268+
adjmom = 1
269+
write (stdout, '(A)') 'Rescaling velocity along the momentum vector after hop.'
270+
case default
271+
write (stderr, '(A)') 'Parameter "velocity_rescaling" must be "nac_then_velocity" or "velocity".'
272+
error = .true.
273+
end select
274+
234275
if (adjmom == 0 .and. inac == 1) then
235-
write (stderr, '(A)') 'Combination of adjmom=0 and inac=1 is not possible.'
236-
write (stderr, '(A)') 'NAC vectors are not computed if inac=1.'
276+
write (stderr, '(A)') 'Combination of velocity_rescaling="nac_then_velocity" and couplings="baeck-an" is not possible.'
277+
write (stderr, '(A)') 'Velocity cannot be rescaled along NAC when using Baeck-An.'
278+
write (stderr, '(A)') 'Change velocity_rescaling="velocity" to rescale along the velocity vector.'
237279
error = .true.
238280
end if
239281

240282
if (inac == 2 .and. nohop == 0) then
241-
write (stdout, '(A)') 'WARNING: For simulations without couplings, inac=2, hopping probability cannot be determined.'
283+
write (stdout, '(A)') 'WARNING: For simulations without couplings(="none") hopping probability cannot be determined.'
242284
nohop = 1
243285
end if
244286

@@ -549,6 +591,39 @@ subroutine calc_nacm(pot, nac_accu)
549591
end if
550592
end subroutine calc_nacm
551593

594+
! Calculate Baeck-An couplings
595+
! Implementation was based on these two articles:
596+
! original by Barbatti: https://doi.org/10.12688/openreseurope.13624.2
597+
! another implementation by Truhlar: https://doi.org/10.1021/acs.jctc.1c01080
598+
! In the numeric implementation, we follow Barbatti and use a higher order formula.
599+
subroutine calc_baeckan(dt)
600+
use mod_general, only: it
601+
integer :: ist1, ist2
602+
real(DP), intent(in) :: dt
603+
real(DP) :: de(4), de2dt2, argument
604+
605+
sigma_ba = 0.0D0
606+
607+
! we don't have sufficient history until step 4
608+
if (it < 4) return
609+
610+
do ist1 = 1, nstate
611+
do ist2 = ist1 + 1, nstate
612+
! If ignore_state is set, we do not calculate sigma (dotproduct) for this state
613+
if (ignore_state == ist1 .or. ignore_state == ist2) cycle
614+
de = en_hist_array(ist2, :) - en_hist_array(ist1, :)
615+
! Second derivative (de2dt2) comes from Eq. 16 from https://doi.org/10.12688/openreseurope.13624.2
616+
de2dt2 = (2.0D0 * de(1) - 5.0D0 * de(2) + 4.0D0 * de(3) - de(4)) / dt**2
617+
argument = de2dt2 / de(1)
618+
if (argument > 0.0D0) then
619+
sigma_ba(ist2, ist1) = dsqrt(argument) / 2.0D0
620+
end if
621+
sigma_ba(ist1, ist2) = -sigma_ba(ist2, ist1)
622+
end do
623+
end do
624+
625+
end subroutine calc_baeckan
626+
552627
! move arrays from new step to old step
553628
subroutine move_vars(vx, vy, vz, vx_old, vy_old, vz_old)
554629
use mod_general, only: natom
@@ -568,9 +643,21 @@ subroutine move_vars(vx, vy, vz, vx_old, vy_old, vz_old)
568643
end do
569644
end do
570645
end if
571-
572646
end do
573647

648+
! Shift the energy history for Baeck-An couplings
649+
if (inac == 1) then
650+
! Move old energies by 1
651+
en_hist_array(:, 4) = en_hist_array(:, 3)
652+
en_hist_array(:, 3) = en_hist_array(:, 2)
653+
en_hist_array(:, 2) = en_hist_array(:, 1)
654+
! new energy is stored before the couplings are calculated
655+
! I avoided doing the same as with LZSH energy history tracking because then I need to modify force_abin, force_terash and
656+
! every potential in potentials_sh (and all possible future ones). This way it is kept private and does not depend on the
657+
! way energies are calculated.
658+
! See commit: https://github.com/PHOTOX/ABIN/pull/186/commits/918f6837a76ec0f41b575d3ca948253eed2f30cc
659+
end if
660+
574661
vx_old = vx
575662
vy_old = vy
576663
vz_old = vz
@@ -594,7 +681,7 @@ subroutine surfacehop(x, y, z, vx, vy, vz, vx_old, vy_old, vz_old, dt, eclas)
594681
real(DP), dimension(nstate) :: en_array_int, en_array_newint
595682
real(DP), dimension(natom, nstate, nstate) :: nacx_int, nacy_int, nacz_int
596683
real(DP), dimension(natom, nstate, nstate) :: nacx_newint, nacy_newint, nacz_newint
597-
real(DP), dimension(nstate, nstate) :: dotproduct_int, dotproduct_newint
684+
real(DP), dimension(nstate, nstate) :: dotproduct_int, dotproduct_newint, sigma_ba_old
598685
! Switching probabilities
599686
real(DP) :: t(nstate, nstate)
600687
! Cumulative switching probabilities
@@ -618,7 +705,7 @@ subroutine surfacehop(x, y, z, vx, vy, vz, vx_old, vy_old, vz_old, dt, eclas)
618705
t_tot = 1.0D0
619706

620707
! First, calculate NACME
621-
if (inac == 0) then
708+
if (inac == 0) then ! Analytic ab initio couplings
622709
! For TeraChem MPI / FMS interface, NAC are already computed!
623710
if (pot /= '_tera_' .and. pot /= '_nai_') then
624711
nacx = 0.0D0
@@ -630,6 +717,11 @@ subroutine surfacehop(x, y, z, vx, vy, vz, vx_old, vy_old, vz_old, dt, eclas)
630717
! TODO: Should we call this with TeraChem?
631718
! I think TC already phases the couplings internally.
632719
call phase_nacme(nacx_old, nacy_old, nacz_old, nacx, nacy, nacz)
720+
else if (inac == 1) then ! Baeck-An couplings
721+
! saving the current energy to the energy history (shifting was already done in previous step in move_vars)
722+
en_hist_array(:, 1) = en_array(:)
723+
sigma_ba_old = sigma_ba ! saving old sigma_ba
724+
call calc_baeckan(dt)
633725
end if
634726

635727
! smaller time step
@@ -645,15 +737,26 @@ subroutine surfacehop(x, y, z, vx, vy, vz, vx_old, vy_old, vz_old, dt, eclas)
645737
pop0 = get_elpop(ist)
646738

647739
! INTERPOLATION
648-
fr = real(itp, DP) / real(substep, DP)
649-
call interpolate(vx, vy, vz, vx_old, vy_old, vz_old, vx_newint, vy_newint, vz_newint, &
650-
nacx_newint, nacy_newint, nacz_newint, en_array_newint, &
651-
dotproduct_newint, fr)
740+
if ((inac == 0) .or. (inac == 2)) then
741+
fr = real(itp, DP) / real(substep, DP)
742+
call interpolate(vx, vy, vz, vx_old, vy_old, vz_old, vx_newint, vy_newint, vz_newint, &
743+
nacx_newint, nacy_newint, nacz_newint, en_array_newint, &
744+
dotproduct_newint, fr)
745+
746+
fr = real(itp - 1, DP) / real(substep, DP)
747+
call interpolate(vx, vy, vz, vx_old, vy_old, vz_old, vx_int, vy_int, vz_int, &
748+
nacx_int, nacy_int, nacz_int, en_array_int, &
749+
dotproduct_int, fr)
750+
else if (inac == 1) then
751+
fr = real(itp, DP) / real(substep, DP)
752+
call interpolate_ba(vx, vy, vz, vx_old, vy_old, vz_old, vx_newint, vy_newint, vz_newint, &
753+
en_array_newint, dotproduct_newint, sigma_ba, sigma_ba_old, fr)
754+
755+
fr = real(itp - 1, DP) / real(substep, DP)
756+
call interpolate_ba(vx, vy, vz, vx_old, vy_old, vz_old, vx_int, vy_int, vz_int, &
757+
en_array_int, dotproduct_int, sigma_ba, sigma_ba_old, fr)
652758

653-
fr = real(itp - 1, DP) / real(substep, DP)
654-
call interpolate(vx, vy, vz, vx_old, vy_old, vz_old, vx_int, vy_int, vz_int, &
655-
nacx_int, nacy_int, nacz_int, en_array_int, &
656-
dotproduct_int, fr)
759+
end if
657760

658761
! Integrate electronic wavefunction for one dtp time step
659762
call sh_integrate_wf(en_array_int, en_array_newint, dotproduct_int, dotproduct_newint, dtp)
@@ -1012,6 +1115,42 @@ subroutine interpolate(vx, vy, vz, vx_old, vy_old, vz_old, vx_int, vy_int, vz_in
10121115

10131116
end subroutine interpolate
10141117

1118+
! interpolation of time-derivative coupling calculated via Baeck-An approximation
1119+
! this routine interpolates sigma_ba between integration steps
1120+
subroutine interpolate_ba(vx, vy, vz, vx_old, vy_old, vz_old, vx_int, vy_int, vz_int, &
1121+
en_array_int, dotproduct_int, sigma_ba, sigma_ba_old, fr)
1122+
use mod_general, only: natom
1123+
real(DP), intent(in) :: sigma_ba(:, :), sigma_ba_old(:, :)
1124+
real(DP), intent(in) :: vx(:, :), vy(:, :), vz(:, :) ! for velocity interpolation
1125+
real(DP), intent(in) :: vx_old(:, :), vy_old(:, :), vz_old(:, :)
1126+
real(DP), intent(out) :: dotproduct_int(:, :)
1127+
real(DP), intent(out) :: en_array_int(:)
1128+
real(DP), intent(out) :: vx_int(:, :), vy_int(:, :), vz_int(:, :) ! interpolated velocities
1129+
! How far are we interpolating?
1130+
real(DP), intent(in) :: fr
1131+
real(DP) :: frd
1132+
integer :: ist1, ist2, iw, iat !iteration counters
1133+
1134+
frd = 1.0D0 - fr
1135+
1136+
do ist1 = 1, nstate
1137+
en_array_int(ist1) = en_array(ist1) * fr + en_array_old(ist1) * frd
1138+
do ist2 = 1, nstate
1139+
! interpolating dot product
1140+
dotproduct_int(ist1, ist2) = sigma_ba(ist1, ist2) * fr + sigma_ba_old(ist1, ist2) * frd
1141+
end do
1142+
end do
1143+
1144+
! interpolating velocity which is necessary for Ekin in the decoherence correction
1145+
iw = 1
1146+
do iat = 1, natom
1147+
vx_int(iat, iw) = vx(iat, iw) * fr + vx_old(iat, iw) * frd
1148+
vy_int(iat, iw) = vy(iat, iw) * fr + vy_old(iat, iw) * frd
1149+
vz_int(iat, iw) = vz(iat, iw) * fr + vz_old(iat, iw) * frd
1150+
end do
1151+
1152+
end subroutine interpolate_ba
1153+
10151154
subroutine try_hop_simple_rescale(vx, vy, vz, instate, outstate, eclas)
10161155
use mod_general, only: pot
10171156
use mod_kinetic, only: ekin_v

0 commit comments

Comments
 (0)