- few more useful print out for CP/FPMD

partial temperatures and mean square displacement


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2452 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
cavazzon 2005-11-09 17:57:05 +00:00
parent fd7576704c
commit 6c0386e76b
3 changed files with 90 additions and 22 deletions

View File

@ -52,7 +52,8 @@
USE printout_base, ONLY : printout_base_open, printout_base_close, &
printout_pos, printout_cell, printout_stress
USE constants, ONLY : factem, au_gpa, au, amu_si, bohr_radius_cm, scmass
USE ions_base, ONLY : na, nsp, nat, ind_bck, atm, ityp, pmass
USE ions_base, ONLY : na, nsp, nat, ind_bck, atm, ityp, pmass, &
cdm_displacement, ions_displacement
USE cell_base, ONLY : s_to_r
USE efield_module, ONLY : tefield, pberryel, pberryion
USE cg_module, ONLY : tcg, itercg
@ -77,6 +78,7 @@
!
REAL(DP) :: stress_gpa( 3, 3 )
REAL(DP) :: hinv( 3, 3 )
REAL(DP) :: dis( nsp )
REAL(DP) :: out_press, volume
REAL(DP) :: totalmass
INTEGER :: isa, is, ia
@ -115,9 +117,11 @@
totalmass = totalmass + pmass(is) * na(is) / scmass
END DO
totalmass = totalmass / volume * 11.2061 ! AMU_SI * 1000.0 / BOHR_RADIUS_CM**3
WRITE( stdout, fmt='(/,3X,"System Density [g/cm^3] : ",F10.4)' ) totalmass
WRITE( stdout, fmt='(/,3X,"System Density [g/cm^3] : ",F10.4,/)' ) totalmass
WRITE( stdout, * )
WRITE( stdout,1000) cdm_displacement( tau0 )
!
CALL ions_displacement( dis, tau0 )
!
stress_gpa = stress * au_gpa
!
@ -170,6 +174,13 @@
!
DEALLOCATE( tauw )
!
! ... Write partial temperature and MSD for each atomic specie tu stdout
!
WRITE( stdout, 1944 )
DO is = 1, nsp
WRITE( stdout, 1945 ) is, temps(is), dis(is)
END DO
!
IF( tfile ) WRITE( 33, 2948 ) nfi, ekinc, temphc, tempp, etot, enthal, &
econs, econt, volume, out_press, tps
IF( tfile ) WRITE( 39, 2949 ) nfi, vnhh(3,3), xnhh0(3,3), vnhp(1), &
@ -217,6 +228,10 @@
!
255 FORMAT( ' ',A5,A8,3(1X,A12),A6 )
256 FORMAT( 'Step ',I5,1X,I7,1X,F12.5,1X,F12.5,1X,F12.5,1X,I5 )
1000 FORMAT(/,3X,'Center of mass square displacement (a.u.): ',F10.6,/)
1944 FORMAT(//' Partial temperatures (for each ionic specie) ', &
/,' Species Temp (K) Mean Square Displacement (a.u.)')
1945 FORMAT(3X,I6,1X,F10.2,1X,F10.4)
1947 FORMAT( 2X,'nfi',4X,'ekinc',2X,'temph',2X,'tempp',8X,'etot',6X,'enthal', &
& 7X,'econs',7X,'econt',4X,'vnhh',3X,'xnhh0',4X,'vnhp',3X,'xnhp0' )
1948 FORMAT( I5,1X,F8.5,1X,F6.1,1X,F6.1,4(1X,F11.5),4(1X,F7.4) )

View File

@ -44,7 +44,7 @@
!
! read from file and distribute data calculated in preceding iterations
!
USE ions_base, ONLY: nsp, na
USE ions_base, ONLY: nsp, na, cdmi, taui
USE cell_base, ONLY: s_to_r
USE cp_restart, ONLY: cp_writefile
USE electrons_base, ONLY: nspin, nbnd, nbsp, iupdwn, nupdwn
@ -75,8 +75,6 @@
REAL(DP) :: ht(3,3), htm(3,3), htvel(3,3), gvel(3,3)
integer :: nk = 1, ispin, i, ib
REAL(DP) :: xk(3,1) = 0.0d0, wk(1) = 1.0d0
REAL(DP) :: cdmi_ (3) = 0.0d0
REAL(DP), ALLOCATABLE :: taui_ (:,:)
REAL(DP), ALLOCATABLE :: occ_ ( :, :, : )
REAL(DP) :: htm1(3,3), omega
@ -96,11 +94,6 @@
gvel = 0.0d0
ALLOCATE( taui_ ( 3, SIZE( taus, 2 ) ) )
CALL s_to_r( taus, taui_ , na, nsp, h )
cdmi_ = 0.0d0
ALLOCATE( occ_ ( nbnd, 1, nspin ) )
occ_ = 0.0d0
do ispin = 1, nspin
@ -111,19 +104,18 @@
IF( tens ) THEN
CALL cp_writefile( ndw, scradir, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui_ , cdmi_ , taus, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi , taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim, occ_ , &
occ_ , lambda, lambdam, xnhe0, xnhem, vnhe, ekincm, ei, &
rho, c02 = c0, cm2 = cm, mat_z = mat_z )
ELSE
CALL cp_writefile( ndw, scradir, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui_ , cdmi_ , taus, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi , taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim, occ_ , &
occ_ , lambda, lambdam, xnhe0, xnhem, vnhe, ekincm, ei, &
rho, c02 = c0, cm2 = cm )
END IF
DEALLOCATE( taui_ )
DEALLOCATE( occ_ )
return
@ -142,7 +134,7 @@
USE io_files, ONLY : scradir
USE electrons_base, ONLY : nbnd, nbsp, nspin, nupdwn, iupdwn
USE gvecw, ONLY : ngw, ngwt
USE ions_base, ONLY : nsp, na
USE ions_base, ONLY : nsp, na, cdmi, taui
USE cp_restart, ONLY : cp_readfile, cp_read_cell, cp_read_wfc
USE ensemble_dft, ONLY : tens
USE io_files, ONLY : scradir
@ -171,8 +163,6 @@
REAL(DP) :: ht(3,3), htm(3,3), htvel(3,3), gvel(3,3)
integer :: nk = 1, ispin, i, ib
REAL(DP) :: xk(3,1) = 0.0d0, wk(1) = 1.0d0
REAL(DP) :: cdmi_ (3) = 0.0d0
REAL(DP), ALLOCATABLE :: taui_ (:,:)
REAL(DP), ALLOCATABLE :: occ_ ( :, :, : )
REAL(DP) :: htm1(3,3), b1(3) , b2(3), b3(3), omega
@ -191,18 +181,17 @@
RETURN
END IF
ALLOCATE( taui_ ( 3, SIZE( taus, 2 ) ) )
ALLOCATE( occ_ ( nbnd, 1, nspin ) )
IF( tens ) THEN
CALL cp_readfile( ndr, scradir, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui_ , cdmi_ , taus, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi, taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim,occ_ , &
occ_ , lambda, lambdam, b1, b2, b3, &
xnhe0, xnhem, vnhe, ekincm, c02 = c0, cm2 = cm, mat_z = mat_z )
ELSE
CALL cp_readfile( ndr, scradir, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui_ , cdmi_ , taus, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi, taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim,occ_ , &
occ_ , lambda, lambdam, b1, b2, b3, &
xnhe0, xnhem, vnhe, ekincm, c02 = c0, cm2 = cm )
@ -222,8 +211,6 @@
endif
enddo
DEALLOCATE( taui_ )
do ispin = 1, nspin
do i = iupdwn ( ispin ), iupdwn ( ispin ) - 1 + nupdwn ( ispin )
occ_f( i ) = occ_ ( i - iupdwn ( ispin ) + 1, 1, ispin )

View File

@ -748,6 +748,72 @@
end subroutine ions_shiftvar
!------------------------------------------------------------------------------!
FUNCTION cdm_displacement( tau )
! Calculate the quadratic displacements of the cdm at the current time step
! with respect to the initial position
! cdmi: initial center of mass (real space)
IMPLICIT NONE
REAL(DP) :: cdm_displacement
REAL(DP) :: tau( :, : ) ! position in real space
REAL(DP) :: cdm(3)
CALL ions_cofmass(tau, pmass, na, nsp, cdm)
cdm_displacement = SUM( (cdm(:)-cdmi(:))**2 )
END FUNCTION cdm_displacement
!------------------------------------------------------------------------------!
SUBROUTINE ions_displacement( dis, tau )
! Calculate the sum of the quadratic displacements of the atoms in the ref.
! of cdm respect to the initial positions.
! taui: initial positions in real units in the ref. of cdm
! ----------------------------------------------
! att! tau_ref: starting position in center-of-mass ref. in real units
! ----------------------------------------------
IMPLICIT NONE
REAL (DP), INTENT(OUT) :: dis(:)
REAL (DP), INTENT(IN) :: tau(:,:)
REAL(DP) :: rdist(3), r2, cdm(3)
INTEGER :: i, j, k, isa
! ... Compute the current value of cdm "Centro Di Massa"
!
CALL ions_cofmass(tau, pmass, na, nsp, cdm )
!
IF( SIZE( dis ) < nsp ) &
CALL errore(' displacement ',' size of dis too small ', 1)
isa = 0
DO k = 1, nsp
dis(k) = 0.0_DP
r2 = 0.0_DP
DO j = 1, na(k)
isa = isa + 1
rdist = tau(:,isa) - cdm
r2 = r2 + SUM( ( rdist(:) - taui(:,isa) )**2 )
END DO
dis(k) = dis(k) + r2 / DBLE(na(k))
END DO
RETURN
END SUBROUTINE ions_displacement
!------------------------------------------------------------------------------!
END MODULE ions_base
!------------------------------------------------------------------------------!