Reverted to previous behavior upon suggestion by Alberto Otero de la Roza

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@10537 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2013-10-17 18:58:39 +00:00
parent afc437db9a
commit 5a888d4ef2
1 changed files with 12 additions and 16 deletions

View File

@ -11,8 +11,9 @@
! updated by PG on Sep. 15, 2005 to account for the case in which
! nr1x,nr2x,nr3x (the physical dimensions of array rho) differ from
! nr1, nr2, nr3 (the true dimensions)
! updated by PG on Feb, 2013 upon suggestion by Thomas Gruber
! updated by PG on Feb, 2013 upon suggestion by Thomas Gruber:
! workaround for VESTA - reverted to previous behavior in Oct 2013
! since workaround is no longer needed
! -------------------------------------------------------------------
! this routine writes a gaussian 98 like formatted cubefile.
! atoms outside the supercell are wrapped back according to PBC.
@ -29,9 +30,9 @@ SUBROUTINE write_cubefile ( alat, at, bg, nat, tau, atm, ityp, rho, &
CHARACTER(len=3), INTENT(IN) :: atm(*)
REAL(DP), INTENT(IN) :: alat, tau(3,nat), at(3,3),bg(3,3), rho(nr1x,nr2x,nr3x)
! --
INTEGER :: i, nt, i1, i2, i3, im1, im2, im3, at_num
INTEGER :: i, nt, i1, i2, i3, at_num
INTEGER, EXTERNAL:: atomic_number
real(DP) :: at_chrg, tpos(3), inpos(3), rhoaux(nr3+1)
real(DP) :: at_chrg, tpos(3), inpos(3)
!C WRITE A FORMATTED 'DENSITY-STYLE' CUBEFILE VERY SIMILAR
!C TO THOSE CREATED BY THE GAUSSIAN PROGRAM OR THE CUBEGEN UTILITY.
@ -53,9 +54,9 @@ SUBROUTINE write_cubefile ( alat, at, bg, nat, tau, atm, ityp, rho, &
WRITE(ounit,*) ' Total SCF Density'
! origin is forced to (0.0,0.0,0.0)
WRITE(ounit,'(I5,3F12.6)') nat, 0.0d0, 0.0d0, 0.0d0
WRITE(ounit,'(I5,3F12.6)') nr1+1, (alat*at(i,1)/dble(nr1),i=1,3)
WRITE(ounit,'(I5,3F12.6)') nr2+1, (alat*at(i,2)/dble(nr2),i=1,3)
WRITE(ounit,'(I5,3F12.6)') nr3+1, (alat*at(i,3)/dble(nr3),i=1,3)
WRITE(ounit,'(I5,3F12.6)') nr1, (alat*at(i,1)/dble(nr1),i=1,3)
WRITE(ounit,'(I5,3F12.6)') nr2, (alat*at(i,2)/dble(nr2),i=1,3)
WRITE(ounit,'(I5,3F12.6)') nr3, (alat*at(i,3)/dble(nr3),i=1,3)
DO i=1,nat
nt = ityp(i)
@ -72,17 +73,12 @@ SUBROUTINE write_cubefile ( alat, at, bg, nat, tau, atm, ityp, rho, &
WRITE(ounit,'(I5,5F12.6)') at_num, at_chrg, inpos
ENDDO
DO i1=1,nr1+1
im1=mod(i1-1,nr1)+1
DO i2=1,nr2+1
im2=mod(i2-1,nr2)+1
DO i3=1,nr3+1
im3=mod(i3-1,nr3)+1
rhoaux(i3) = rho(im1,im2,im3)
END DO
WRITE(ounit,'(6E13.5)') (rhoaux(i3),i3=1,nr3+1)
DO i1=1,nr1
DO i2=1,nr2
WRITE(ounit,'(6E13.5)') (rho(i1,i2,i3),i3=1,nr3)
ENDDO
ENDDO
RETURN
END SUBROUTINE write_cubefile