Fixed some bugs in the definition of coordination numbers, IO formats, and metadynamics.

C.S.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2213 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
sbraccia 2005-09-24 02:49:16 +00:00
parent c81ff3deba
commit fb1a49e5e2
4 changed files with 69 additions and 24 deletions

View File

@ -64,7 +64,7 @@ SUBROUTINE compute_fes_grads( N_in, N_fin, stat )
& TRIM( int_to_char( istep_path + 1 ) ) // ".axsf", &
STATUS = "UNKNOWN", ACTION = "WRITE" )
!
WRITE( UNIT = iunaxsf, FMT = '(" ANIMSTEPS ",I3)' ) num_of_images
WRITE( UNIT = iunaxsf, FMT = '(" ANIMSTEPS ",I5)' ) num_of_images
WRITE( UNIT = iunaxsf, FMT = '(" CRYSTAL ")' )
WRITE( UNIT = iunaxsf, FMT = '(" PRIMVEC ")' )
WRITE( UNIT = iunaxsf, FMT = '(3F14.10)' ) &
@ -311,6 +311,7 @@ SUBROUTINE metadyn()
!------------------------------------------------------------------------
!
USE kinds, ONLY : DP
USE constants, ONLY : eps8
USE constraints_module, ONLY : nconstr, target, lagrange
USE cp_main_variables, ONLY : nfi
USE control_flags, ONLY : program_name, nomore, ldamped, tconvthrs, &
@ -331,10 +332,12 @@ SUBROUTINE metadyn()
!
IMPLICIT NONE
!
INTEGER :: iter
INTEGER :: iter, i
REAL(DP), ALLOCATABLE :: tau(:,:)
REAL(DP), ALLOCATABLE :: fion(:,:)
REAL(DP) :: etot
REAL(DP) :: etot, norm_fe_grad
!
REAL(DP), EXTERNAL :: rndm
!
!
ALLOCATE( tau( 3, nat ), fion( 3, nat ) )
@ -377,6 +380,24 @@ SUBROUTINE metadyn()
!
CALL add_gaussians( iter )
!
norm_fe_grad = norm( fe_grad )
!
IF ( norm_fe_grad < eps8 ) THEN
!
! ... use a random perturbation
!
WRITE( iunmeta, '("random step")' )
!
DO i = 1, nconstr
!
fe_grad(:) = rndm()
!
END DO
!
norm_fe_grad = norm( fe_grad )
!
END IF
!
! ... the system is "adiabatically" moved to the new target
!
new_target(:) = target(:) - fe_step * fe_grad(:) / norm( fe_grad )
@ -471,7 +492,7 @@ SUBROUTINE write_config( image )
INTEGER :: atom
!
!
WRITE( UNIT = iunaxsf, FMT = '(" PRIMCOORD ",I3)' ) image
WRITE( UNIT = iunaxsf, FMT = '(" PRIMCOORD ",I5)' ) image
WRITE( UNIT = iunaxsf, FMT = '(I5," 1")' ) nat
!
DO atom = 1, nat

View File

@ -160,7 +160,7 @@ MODULE coarsegrained_base
FILE = TRIM( prefix ) // ".axsf", STATUS = 'UNKNOWN' )
!
WRITE( UNIT = iunaxsf, &
FMT = '(" ANIMSTEPS ",I3)' ) max_metadyn_iter + 1
FMT = '(" ANIMSTEPS ",I5)' ) max_metadyn_iter
!
WRITE( UNIT = iunaxsf, FMT = '(" CRYSTAL ")' )
WRITE( UNIT = iunaxsf, FMT = '(" PRIMVEC ")' )

View File

@ -7,6 +7,8 @@
!
#include "f_defs.h"
!
!#define __DEBUG_CONSTRAINTS
!
!----------------------------------------------------------------------------
MODULE constraints_module
!----------------------------------------------------------------------------
@ -140,7 +142,7 @@ MODULE constraints_module
norm_dtau = norm( dtau )
!
target(ia) = target(ia) + &
2.D0 / ( EXP( k * ( norm_dtau - r_c ) ) + 1.D0 )
1.D0 / ( EXP( k * ( norm_dtau - r_c ) ) + 1.D0 )
!
END DO
!
@ -162,12 +164,11 @@ MODULE constraints_module
!
END IF
!
ia1 = ANINT( constr(1,ia) )
ia1 = ANINT( constr(1,ia) )
type_coord1 = ANINT( constr(2,ia) )
!
r_c = constr(2,ia)
k = constr(3,ia)
!
type_coord1 = ANINT( constr(4,ia) )
r_c = constr(3,ia)
k = constr(4,ia)
!
target(ia) = 0.D0
!
@ -182,7 +183,7 @@ MODULE constraints_module
norm_dtau = norm( dtau )
!
target(ia) = target(ia) + &
2.D0 / ( EXP( k * ( norm_dtau - r_c ) ) + 1.D0 )
1.D0 / ( EXP( k * ( norm_dtau - r_c ) ) + 1.D0 )
!
END DO
!
@ -321,9 +322,9 @@ MODULE constraints_module
!
expo = EXP( k * ( norm_dtau - r_c ) )
!
g = g + 2.D0 / ( expo + 1.D0 )
g = g + 1.D0 / ( expo + 1.D0 )
!
dtau(:) = 2.D0 * dtau(:) * k * expo / ( expo + 1.D0 )**2
dtau(:) = dtau(:) * k * expo / ( expo + 1.D0 )**2
!
dg(:,ia2) = dg(:,ia2) + dtau(:)
dg(:,ia1) = dg(:,ia1) - dtau(:)
@ -343,12 +344,11 @@ MODULE constraints_module
!
! ... constraint on local coordination
!
ia = ANINT( constr(1,index) )
ia = ANINT( constr(1,index) )
type_coord1 = ANINT( constr(2,index) )
!
r_c = constr(2,index)
k = constr(3,index)
!
type_coord1 = ANINT( constr(4,index) )
r_c = constr(3,index)
k = constr(4,index)
!
g = 0.D0
!
@ -366,9 +366,9 @@ MODULE constraints_module
!
expo = EXP( k * ( norm_dtau - r_c ) )
!
g = g + 2.D0 / ( expo + 1.D0 )
g = g + 1.D0 / ( expo + 1.D0 )
!
dtau(:) = 2.D0 * dtau(:) * k * expo / ( expo + 1.D0 )**2
dtau(:) = dtau(:) * k * expo / ( expo + 1.D0 )**2
!
dg(:,ia1) = dg(:,ia1) + dtau(:)
dg(:,ia) = dg(:,ia) - dtau(:)

View File

@ -69,7 +69,7 @@ SUBROUTINE compute_fes_grads( N_in, N_fin, stat )
& TRIM( int_to_char( istep_path + 1 ) ) // ".axsf", &
STATUS = "UNKNOWN", ACTION = "WRITE" )
!
WRITE( UNIT = iunaxsf, FMT = '(" ANIMSTEPS ",I3)' ) num_of_images
WRITE( UNIT = iunaxsf, FMT = '(" ANIMSTEPS ",I5)' ) num_of_images
WRITE( UNIT = iunaxsf, FMT = '(" CRYSTAL ")' )
WRITE( UNIT = iunaxsf, FMT = '(" PRIMVEC ")' )
WRITE( UNIT = iunaxsf, FMT = '(3F14.10)' ) &
@ -405,6 +405,7 @@ SUBROUTINE metadyn()
!------------------------------------------------------------------------
!
USE kinds, ONLY : DP
USE constants, ONLY : eps8
USE constraints_module, ONLY : nconstr, target
USE ener, ONLY : etot
USE io_files, ONLY : iunaxsf, iunmeta
@ -417,7 +418,10 @@ SUBROUTINE metadyn()
!
IMPLICIT NONE
!
INTEGER :: iter
INTEGER :: iter, i
REAL(DP) :: norm_fe_grad
!
REAL(DP), EXTERNAL :: rndm
!
!
iter = starting_metadyn_iter
@ -428,11 +432,31 @@ SUBROUTINE metadyn()
!
CALL add_gaussians( iter )
!
norm_fe_grad = norm( fe_grad )
!
IF ( norm_fe_grad < eps8 ) THEN
!
! ... use a random perturbation
!
WRITE( iunmeta, '("random step")' )
!
DO i = 1, nconstr
!
fe_grad(:) = rndm()
!
END DO
!
norm_fe_grad = norm( fe_grad )
!
END IF
!
new_target(:) = target(:) - fe_step * fe_grad(:) / norm( fe_grad )
!
WRITE( stdout, '(/,5X,"adiabatic switch of the system ", &
& "to the new coarse-grained positions",/)' )
!
! ... the system is "adiabatically" moved to the new target
!
CALL move_to_target()
!
END IF
@ -587,7 +611,7 @@ SUBROUTINE write_config( image )
INTEGER :: atom
!
!
WRITE( UNIT = iunaxsf, FMT = '(" PRIMCOORD ",I3)' ) image
WRITE( UNIT = iunaxsf, FMT = '(" PRIMCOORD ",I5)' ) image
WRITE( UNIT = iunaxsf, FMT = '(I5," 1")' ) nat
!
DO atom = 1, nat