Skip to content

Commit 6ca32ee

Browse files
author
giannozz
committed
Misc changes to dynamics:
1) in my opinion, the Andersen thermostat was not doing what it was supposed to do. Not sre now it does it, though. 2) the code now performs as many dynamics steps as required in input, even when restarting from a previous run. 3) Random number generator further randomized to prevent repeating the same "random" configuration
1 parent 2bd832e commit 6ca32ee

File tree

2 files changed

+47
-22
lines changed

2 files changed

+47
-22
lines changed

Modules/random_numbers.f90

+17
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,23 @@ FUNCTION randy ( irand )
7070
!
7171
END FUNCTION randy
7272
!
73+
!------------------------------------------------------------------------
74+
SUBROUTINE set_random_seed ( )
75+
!------------------------------------------------------------------------
76+
!
77+
! poor-man random seed for randy
78+
!
79+
INTEGER, DIMENSION (8) :: itime
80+
INTEGER :: iseed, irand
81+
!
82+
CALL date_and_time ( values = itime )
83+
! itime contains: year, month, day, time difference in minutes, hours,
84+
! minutes, seconds and milliseconds.
85+
iseed = ( itime(8) + itime(6) ) * ( itime(7) + itime(4) )
86+
irand = randy ( iseed )
87+
!
88+
END SUBROUTINE set_random_seed
89+
!
7390
!-----------------------------------------------------------------------
7491
FUNCTION gauss_dist_scal( mu, sigma )
7592
!-----------------------------------------------------------------------

PW/dynamics_module.f90

+30-22
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,12 @@
11
!
2-
! Copyright (C) 2001-2009 Quantum ESPRESSO group
2+
! Copyright (C) 2001-2011 Quantum ESPRESSO group
33
! This file is distributed under the terms of the
44
! GNU General Public License. See the file `License'
55
! in the root directory of the present distribution,
66
! or http://www.gnu.org/copyleft/gpl.txt .
77
!
88
!
9-
#define __BFGS
10-
!#define __NPT
11-
!
9+
#undef __NPT
1210
#if defined (__NPT)
1311
#define RELAXTIME 2000.D0
1412
#define TARGPRESS 2.39D0
@@ -133,14 +131,15 @@ SUBROUTINE verlet()
133131
REAL(DP) :: total_mass, temp_new, temp_av, elapsed_time
134132
REAL(DP) :: delta(3), ml(3), mlt
135133
INTEGER :: na
134+
! istep0 counts MD steps done during this run
135+
! (istep counts instead all MD steps, including those of previous runs)
136+
INTEGER, SAVE :: istep0 = 0
136137
#if defined (__NPT)
137138
REAL(DP) :: chi, press_new
138139
#endif
139140
LOGICAL :: file_exists, leof
140-
!
141141
REAL(DP), EXTERNAL :: dnrm2
142142
!
143-
!
144143
! ... the number of degrees of freedom
145144
!
146145
IF ( any( if_pos(:,:) == 0 ) ) THEN
@@ -198,7 +197,7 @@ SUBROUTINE verlet()
198197
!
199198
ENDIF
200199
!
201-
IF ( istep >= nstep ) THEN
200+
IF ( istep0 >= nstep ) THEN
202201
!
203202
conv_ions = .true.
204203
!
@@ -215,6 +214,7 @@ SUBROUTINE verlet()
215214
!
216215
elapsed_time = elapsed_time + dt*2.D0*au_ps
217216
!
217+
istep0= istep0+ 1
218218
istep = istep + 1
219219
!
220220
WRITE( UNIT = stdout, &
@@ -434,8 +434,17 @@ SUBROUTINE md_init()
434434
CASE( 'andersen', 'Andersen' )
435435
!
436436
WRITE( UNIT = stdout, &
437-
FMT = '(/,5X,"temperature is ", &
438-
& "controlled by Andersen thermostat"/)' )
437+
FMT = '(/,5X,"temperature is controlled by Andersen ", &
438+
& "thermostat",/,5x,"Collision frequency =",&
439+
& f7.4,"/timestep")' ) 1.0_dp/nraise
440+
!
441+
CASE( 'berendsen', 'Berendsen' )
442+
!
443+
WRITE( UNIT = stdout, &
444+
FMT = '(/,5X,"temperature is controlled by soft ", &
445+
& "(Berendsen) velocity rescaling",/,5x,&
446+
& "Characteristic time =",i3,"*timestep")') &
447+
nraise
439448
!
440449
CASE( 'initial', 'Initial' )
441450
!
@@ -514,6 +523,7 @@ SUBROUTINE apply_thermostat()
514523
!
515524
IMPLICIT NONE
516525
!
526+
INTEGER :: nat_moved
517527
REAL(DP) :: sigma, kt
518528
!
519529
IF(.not.vel_defined)THEN
@@ -574,25 +584,20 @@ SUBROUTINE apply_thermostat()
574584
CASE( 'berendsen', 'Berendsen' )
575585
!
576586
WRITE( UNIT = stdout, &
577-
FMT = '(/,5X,"Soft velocity rescaling with tau=",i3, &
578-
& "*time step: T_new = ",F6.1,"K ")' ) nraise,temp_new
587+
FMT = '(/,5X,"Soft (Berendsen) velocity rescaling")' )
579588
!
580589
CALL thermalize( nraise, temp_new, temperature )
581590
!
582591
CASE( 'andersen', 'Andersen' )
583592
!
584593
kt = temperature / ry_to_kelvin
585-
!
586-
WRITE( UNIT = stdout, &
587-
FMT = '(/,5X,"Andersen thermostat with acceptance rate ",&
588-
& f6.3,": T_new = ",F6.1,"K ")' ) temp_new
589-
!
590-
CALL thermalize( nraise, temp_new, temperature )
594+
nat_moved = 0
591595
!
592596
DO na = 1, nat
593597
!
594598
IF ( randy() < 1.D0 / dble( nraise ) ) THEN
595599
!
600+
nat_moved = nat_moved + 1
596601
sigma = sqrt( kt / mass(na) )
597602
!
598603
! ... N.B. velocities must in a.u. units of alat and are zero
@@ -605,6 +610,10 @@ SUBROUTINE apply_thermostat()
605610
!
606611
ENDDO
607612
!
613+
IF ( nat_moved > 0) WRITE( UNIT = stdout, &
614+
FMT = '(/,5X,"Andersen thermostat: ",I4," collisions")' ) &
615+
nat_moved
616+
!
608617
CASE( 'initial', 'Initial' )
609618
!
610619
CONTINUE
@@ -629,14 +638,17 @@ SUBROUTINE start_therm()
629638
USE control_flags, ONLY : lfixatom
630639
USE cell_base, ONLY : alat
631640
USE ions_base, ONLY : nat, if_pos
632-
USE random_numbers, ONLY : gauss_dist
641+
USE random_numbers, ONLY : gauss_dist, set_random_seed
633642
!
634643
IMPLICIT NONE
635644
!
636645
INTEGER :: na, nb
637646
REAL(DP) :: total_mass, kt, sigma, ek, ml(3), system_temp
638647
!
648+
! ... next command prevents different MD runs to start
649+
! ... with exactly the same "random" velocities
639650
!
651+
call set_random_seed ( )
640652
kt = temperature / ry_to_kelvin
641653
!
642654
! ... starting velocities have a Maxwell-Boltzmann distribution
@@ -1290,8 +1302,6 @@ SUBROUTINE force_precond( istep, force, etotold )
12901302
REAL(DP), INTENT(inout) :: force(:,:)
12911303
REAL(DP), INTENT(in) :: etotold
12921304
!
1293-
#if defined (__BFGS)
1294-
!
12951305
REAL(DP), ALLOCATABLE :: pos(:), pos_p(:)
12961306
REAL(DP), ALLOCATABLE :: grad(:), grad_p(:), precond_grad(:)
12971307
REAL(DP), ALLOCATABLE :: inv_hess(:,:)
@@ -1403,8 +1413,6 @@ SUBROUTINE force_precond( istep, force, etotold )
14031413
DEALLOCATE( y, s )
14041414
DEALLOCATE( Hy, yH )
14051415
!
1406-
#endif
1407-
!
14081416
END SUBROUTINE force_precond
14091417
!
14101418
!-----------------------------------------------------------------------

0 commit comments

Comments
 (0)