Cleanup of unused variables.

C.S.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2033 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
sbraccia 2005-07-18 02:56:45 +00:00
parent d92755e936
commit ba2edda164
5 changed files with 21 additions and 22 deletions

View File

@ -929,7 +929,7 @@ MODULE input
!
lconstrain = ( nconstr_inp > 0 )
!
IF ( lconstrain ) CALL init_constraint( nat, tau, 1.D0, ityp, if_pos )
IF ( lconstrain ) CALL init_constraint( nat, tau, 1.D0, ityp )
!
IF( program_name == 'FPMD' ) THEN

View File

@ -136,13 +136,13 @@ MODULE bfgs_module
! ... local variables
!
INTEGER :: dim, i, j
LOGICAL :: lwolfe, ltest
REAL(KIND=DP) :: dE0s, dEs, E_diff, num, den, ratio
LOGICAL :: lwolfe
REAL(KIND=DP) :: dE0s, den
!
REAL (KIND=DP), ALLOCATABLE :: res(:,:), overlap(:,:), work(:)
INTEGER, ALLOCATABLE :: iwork(:)
INTEGER :: k, k_m, info
REAL (KIND=DP) :: norm_g, gamma0
REAL(KIND=DP) :: gamma0
!
!
dim = SIZE( pos )

View File

@ -65,7 +65,7 @@ MODULE constraints_module
! ... public methods
!
!-----------------------------------------------------------------------
SUBROUTINE init_constraint( nat, tau, alat, ityp, if_pos )
SUBROUTINE init_constraint( nat, tau, alat, ityp )
!-----------------------------------------------------------------------
!
USE input_parameters, ONLY : nconstr_inp, constr_tol_inp, &
@ -78,10 +78,9 @@ MODULE constraints_module
REAL (KIND=DP), INTENT(IN) :: tau(3,nat)
REAL (KIND=DP), INTENT(IN) :: alat
INTEGER, INTENT(IN) :: ityp(nat)
INTEGER, INTENT(IN) :: if_pos(3,nat)
!
INTEGER :: ia, ia1, ia2, ia3
REAL(KIND=DP) :: r12(3), r23(3)
REAL(KIND=DP) :: r21(3), r23(3)
REAL(KIND=DP) :: k, r_c
INTEGER :: type_coord
REAL(KIND=DP) :: dtau(3), norm_dtau
@ -176,13 +175,13 @@ MODULE constraints_module
ia2 = ANINT( constr(2,ia) )
ia3 = ANINT( constr(3,ia) )
!
r12 = ( tau(:,ia2) - tau(:,ia1) ) * alat
r21 = ( tau(:,ia2) - tau(:,ia1) ) * alat
r23 = ( tau(:,ia2) - tau(:,ia3) ) * alat
!
r12 = r12 / norm( r12 )
r21 = r21 / norm( r21 )
r23 = r23 / norm( r23 )
!
target(ia) = DOT_PRODUCT( r12, r23 )
target(ia) = DOT_PRODUCT( r21, r23 )
!
CASE DEFAULT
!
@ -229,8 +228,8 @@ MODULE constraints_module
REAL(KIND=DP) :: x1, x2, y1, y2, z1, z2
REAL(KIND=DP) :: dist0
INTEGER :: ia, ia1, ia2, ia3
REAL(KIND=DP) :: r12(3), r23(3)
REAL(KIND=DP) :: norm_r12, norm_r23, cos123, sin123
REAL(KIND=DP) :: r21(3), r23(3)
REAL(KIND=DP) :: norm_r21, norm_r23, cos123, sin123
REAL(KIND=DP) :: k, r_c
INTEGER :: type_coord
REAL(KIND=DP) :: dtau(3), norm_dtau, expo
@ -317,22 +316,22 @@ MODULE constraints_module
ia2 = ANINT( constr(2,index) )
ia3 = ANINT( constr(3,index) )
!
r12 = ( tau(:,ia2) - tau(:,ia1) ) * alat
r21 = ( tau(:,ia2) - tau(:,ia1) ) * alat
r23 = ( tau(:,ia2) - tau(:,ia3) ) * alat
!
norm_r12 = norm( r12 )
norm_r21 = norm( r21 )
norm_r23 = norm( r23 )
!
r12 = r12 / norm_r12
r21 = r21 / norm_r21
r23 = r23 / norm_r23
!
cos123 = DOT_PRODUCT( r12, r23 )
cos123 = DOT_PRODUCT( r21, r23 )
sin123 = SQRT( 1.D0 - cos123**2 )
!
g = ( cos123 - target(index) )
!
dg(:,ia1) = ( cos123 * r12 - r23 ) / ( sin123 * norm_r12 )
dg(:,ia3) = ( cos123 * r23 - r12 ) / ( sin123 * norm_r23 )
dg(:,ia1) = ( cos123 * r21 - r23 ) / ( sin123 * norm_r21 )
dg(:,ia3) = ( cos123 * r23 - r21 ) / ( sin123 * norm_r23 )
dg(:,ia2) = - dg(:,ia1) - dg(:,ia3)
!
CASE DEFAULT

View File

@ -102,7 +102,7 @@ SUBROUTINE compute_fes_grads( N_in, N_fin, stat )
!
END IF
!
! ... only the tfirst cpu initializes the file needed by parallelization
! ... only the first cpu initializes the file needed by parallelization
! ... among images
!
IF ( meta_ionode ) CALL new_image_init()
@ -134,7 +134,7 @@ SUBROUTINE compute_fes_grads( N_in, N_fin, stat )
!
END IF
!
! ... self-consistency ( for non-frozen images only )
! ... free-energy gradient ( for non-frozen images only )
!
IF ( .NOT. frozen(image) ) THEN
!
@ -198,7 +198,7 @@ SUBROUTINE compute_fes_grads( N_in, N_fin, stat )
!
! ... the new value of the order-parameter is set here
!
CALL init_constraint( nat, tau, alat, ityp, if_pos )
CALL init_constraint( nat, tau, alat, ityp )
!
new_target(:) = pos(:,image)
!

View File

@ -1353,7 +1353,7 @@ SUBROUTINE iosys()
!
! ... set constraints
!
IF ( lconstrain ) CALL init_constraint( nat, tau, alat, ityp, if_pos )
IF ( lconstrain ) CALL init_constraint( nat, tau, alat, ityp )
!
! ... Renata's dynamics uses masses in atomic units
!