Fixed some bugs in the implementation of velocities from input.

C.S.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@1864 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
sbraccia 2005-05-16 19:00:07 +00:00
parent 8949481005
commit 7e7dd4b365
4 changed files with 38 additions and 45 deletions

View File

@ -442,7 +442,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
END IF
!
IF( tfor .OR. thdyn ) CALL phfac( tau0, ei1, ei2, ei3, eigr )
IF ( tfor .OR. thdyn ) CALL phfac( tau0, ei1, ei2, ei3, eigr )
!
! ... strucf calculates the structure factor sfac
!
@ -458,7 +458,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
tlast = ( nfi == nomore )
ttprint = ( MOD( nfi, iprint ) == 0 )
!
IF( ( tfor .OR. tfirst ) .AND. tefield ) CALL efield_update( eigr )
IF ( ( tfor .OR. tfirst ) .AND. tefield ) CALL efield_update( eigr )
!
!=======================================================================
!
@ -490,7 +490,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
hgamma(:,:) = 0.D0
!
IF(thdyn) THEN
IF ( thdyn ) THEN
!
CALL cell_force( fcell, ainv, stress, omega, press, wmass )
!
@ -501,13 +501,13 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
CALL cell_gamma( hgamma, ainv, h, velh )
!
ENDIF
END IF
!
!======================================================================
!
IF ( tfor ) THEN
!
IF( lwf ) CALL ef_force( fion, na, nsp, zv )
IF ( lwf ) CALL ef_force( fion, na, nsp, zv )
!
! ... constraints are imposed here
!
@ -528,10 +528,10 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
IF ( lconstrain ) THEN
!
CALL check_constrain( nat, taup, ityp, 1.D0 )
!
CALL r_to_s( taup, tausp, na, nsp, ainv )
!
CALL check_constrain( nat, taup, ityp, 1.D0 )
!
CALL r_to_s( taup, tausp, na, nsp, ainv )
!
END IF
!
END IF
@ -557,7 +557,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
hold = h
!
ENDIF
END IF
!
! ... phfac calculates eigr
!
@ -596,7 +596,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
IF ( .NOT. tcg ) THEN
!
IF( iprsta >= 3 ) CALL print_lambda( lambda, nbsp, 9, 1.D0 )
IF ( iprsta >= 3 ) CALL print_lambda( lambda, nbsp, 9, 1.D0 )
!
IF ( tortho ) CALL updatc( ccc, lambda, phi, bephi, becp, bec, cm )
!
@ -643,11 +643,11 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
! ... fake cell-parameters kinetic energy
!
ekinh=0.D0
ekinh = 0.D0
!
IF ( thdyn ) CALL cell_kinene( ekinh, temphh, velh )
!
IF( COUNT( iforceh == 1 ) > 0 ) THEN
IF ( COUNT( iforceh == 1 ) > 0 ) THEN
!
temphc = 2.D0 * factem * ekinh / DBLE( COUNT( iforceh == 1 ) )
!
@ -655,7 +655,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
temphc = 0.D0
!
ENDIF
END IF
!
! ... udating nose-hoover friction variables
!
@ -720,7 +720,7 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
!
ELSE
!
IF ( .NOT.tens ) THEN
IF ( .NOT. tens ) THEN
!
econs = ekinp + etot
atot = etot
@ -849,12 +849,12 @@ SUBROUTINE cprmain( tau, fion_out, etot_out )
! ... new variables for next step
!
CALL ions_shiftvar( tausp, taus, tausm ) ! scaled positions
CALL ions_shiftvar( taup, tau0, taum ) ! real positions
CALL ions_shiftvar( taup, tau0, taum ) ! real positions
CALL ions_shiftvar( velsp, vels, velsm ) ! scaled velocities
!
IF( tnosep ) CALL ions_nose_shiftvar( xnhpp, xnhp0, xnhpm )
IF( tnosee ) CALL electrons_nose_shiftvar( xnhep, xnhe0, xnhem )
IF( tnoseh ) CALL cell_nose_shiftvar( xnhhp, xnhh0, xnhhm )
IF ( tnosep ) CALL ions_nose_shiftvar( xnhpp, xnhp0, xnhpm )
IF ( tnosee ) CALL electrons_nose_shiftvar( xnhep, xnhe0, xnhem )
IF ( tnoseh ) CALL cell_nose_shiftvar( xnhhp, xnhh0, xnhhm )
!
END IF
!

View File

@ -23,11 +23,10 @@ MODULE ions_positions
CONTAINS
!
!--------------------------------------------------------------------------
SUBROUTINE ions_hmove( taus, tausm, vels, &
iforce, pmass, fion, ainv, delt, na, nsp )
SUBROUTINE ions_hmove( taus, tausm, iforce, pmass, fion, ainv, delt, na, nsp )
!--------------------------------------------------------------------------
!
REAL(KIND=dbl), INTENT(IN) :: tausm(:,:), vels(:,:), pmass(:), fion(:,:)
REAL(KIND=dbl), INTENT(IN) :: tausm(:,:), pmass(:), fion(:,:)
INTEGER, INTENT(IN) :: iforce(:,:)
REAL(KIND=dbl), INTENT(IN) :: ainv(3,3), delt
REAL(KIND=dbl), INTENT(OUT) :: taus(:,:)
@ -56,8 +55,7 @@ MODULE ions_positions
!
END DO
!
taus(:,isa) = tausm(:,isa) + &
delt * vels(:,isa) + iforce(:,isa) * fac * fions(:)
taus(:,isa) = tausm(:,isa) + iforce(:,isa) * fac * fions(:)
!
END DO

View File

@ -265,14 +265,11 @@ MODULE from_restart_module
!
CALL r_to_s( vel, vels, na, nsp, h )
!
CALL ions_hmove( taus, tausm, vels, iforce, &
pmass, fion, ainv, delt, na, nsp )
taus(:,:) = tausm(:,:) + delt * vels(:,:)
!
ELSE
!
vels = 0.D0
!
CALL ions_hmove( taus, tausm, vels, iforce, &
CALL ions_hmove( taus, tausm, iforce, &
pmass, fion, ainv, delt, na, nsp )
!
END IF

View File

@ -159,13 +159,13 @@ MODULE read_cards_module
!
CALL card_setnfi( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'OPTICAL' ) THEN
!
CALL card_optical( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'CONSTRAINTS' ) THEN
!
@ -175,43 +175,41 @@ MODULE read_cards_module
!
CALL card_vhmean( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'DIPOLE' ) THEN
!
CALL card_dipole( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'ESR' ) THEN
!
CALL card_esr( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'K_POINTS' ) THEN
!
CALL card_kpoints( input_line )
IF ( prog == 'CP' .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'NEIGHBOURS' ) THEN
!
CALL card_neighbours( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'OCCUPATIONS' ) THEN
!
CALL card_occupations( input_line )
! IF ( prog == 'PW' .AND. ionode ) &
! WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'PSTAB' ) THEN
!
CALL card_pstab( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'CELL_PARAMETERS' ) THEN
!
@ -221,31 +219,31 @@ MODULE read_cards_module
!
CALL card_turbo( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'ION_VELOCITIES' ) THEN
!
CALL card_ion_velocities( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
IF ( ( prog == 'PW' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'KSOUT' ) THEN
!
CALL card_ksout( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(a)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(a)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'KSOUT_EMPTY' ) THEN
!
CALL card_ksout_empty( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'RHOOUT' ) THEN
!
CALL card_rhoout( input_line )
IF ( ( prog == 'PW' .OR. prog == 'CP' ) .AND. ionode ) &
WRITE( stdout,'(A)') 'Warning: card '//trim(input_line)//' ignored'
WRITE( stdout,'(A)') 'Warning: card '//TRIM(input_line)//' ignored'
!
ELSE IF ( TRIM(card) == 'CLIMBING_IMAGES' ) THEN
!