More tweaking with post-processing

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2175 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2005-09-14 12:48:59 +00:00
parent ee9644ff8f
commit 7cf398eeec
3 changed files with 35 additions and 23 deletions

View File

@ -7,7 +7,7 @@
! !
! !
!----------------------------------------------------------------------- !-----------------------------------------------------------------------
SUBROUTINE chdens SUBROUTINE chdens (filplot)
!----------------------------------------------------------------------- !-----------------------------------------------------------------------
! Writes the charge density (or potential, or polarisation) ! Writes the charge density (or potential, or polarisation)
! into a file format suitable for plotting ! into a file format suitable for plotting
@ -30,6 +30,8 @@ SUBROUTINE chdens
USE io_files, ONLY: nd_nmbr USE io_files, ONLY: nd_nmbr
implicit none implicit none
character (len=256), INTENT(in) :: filplot
!
integer, parameter :: nfilemax = 7 integer, parameter :: nfilemax = 7
! maximum number of files with charge ! maximum number of files with charge
@ -39,7 +41,13 @@ SUBROUTINE chdens
real(DP) :: e1(3), e2(3), e3(3), x0 (3), radius, m1, m2, m3, & real(DP) :: e1(3), e2(3), e3(3), x0 (3), radius, m1, m2, m3, &
weight (nfilemax), epsilon weight (nfilemax), epsilon
character (len=256) :: fileout, filepol, filename (nfilemax) character (len=256) :: fileout, filename (nfilemax)
character (len=15), dimension(0:6) :: formatname = &
(/ 'gnuplot', 'contour.x', 'plotrho.x', 'XCrySDen', 'gOpenMol', &
& 'XCrySDen', 'Gaussian cube' /)
character (len=20), dimension(0:4) :: plotname = &
(/ '1D spherical average', '1D along a line', '2D contour', &
& '3D', '2D polar on a sphere'/)
real(DP) :: celldms (6), gcutmsa, duals, ecuts, zvs(ntypx), ats(3,3) real(DP) :: celldms (6), gcutmsa, duals, ecuts, zvs(ntypx), ats(3,3)
real(DP), allocatable :: taus (:,:), rhor(:) real(DP), allocatable :: taus (:,:), rhor(:)
@ -55,20 +63,18 @@ SUBROUTINE chdens
namelist /plot/ & namelist /plot/ &
nfile, filepp, weight, iflag, e1, e2, e3, nx, ny, nz, x0, & nfile, filepp, weight, iflag, e1, e2, e3, nx, ny, nz, x0, &
output_format, fileout, epsilon, filepol output_format, fileout
! !
! set the DEFAULT values ! set the DEFAULT values
! !
nfile = 1 nfile = 1
filepp(1) = 'tmp.pp' filepp(1) = filplot
weight(1) = 1.0d0 weight(1) = 1.0d0
iflag = 1 iflag = 1
radius = 1.0d0 radius = 1.0d0
output_format = 0 output_format = 0
fileout = ' ' fileout = ' '
epsilon = 1.0d0
filepol = ' '
e1(:) = 0.d0 e1(:) = 0.d0
e2(:) = 0.d0 e2(:) = 0.d0
e3(:) = 0.d0 e3(:) = 0.d0
@ -218,7 +224,8 @@ SUBROUTINE chdens
if (fileout /= ' ') then if (fileout /= ' ') then
ounit = 1 ounit = 1
open (unit=ounit, file=fileout, form='formatted', status='unknown') open (unit=ounit, file=fileout, form='formatted', status='unknown')
WRITE( stdout, '(5x,"Writing data on file ",a)') fileout WRITE( stdout, '(/5x,"Writing data to be plotted to file ",a)') &
TRIM(fileout)
else else
ounit = 6 ounit = 6
endif endif
@ -254,10 +261,10 @@ SUBROUTINE chdens
! !
call ggen call ggen
! !
! here we compute the fourier component of the quantity to plot ! here we compute the fourier components of the quantity to plot
! !
psic(:) = CMPLX (rhor(:), 0.d0) psic(:) = CMPLX (rhor(:), 0.d0)
call cft3 (psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, - 1) call cft3 (psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, -1)
! !
! we store the fourier components in the array rhog ! we store the fourier components in the array rhog
! !
@ -293,12 +300,12 @@ SUBROUTINE chdens
if (fileout /= ' ') then if (fileout /= ' ') then
open (unit = ounit+1, file = trim(fileout)//'.xyz', & open (unit = ounit+1, file = trim(fileout)//'.xyz', &
form = 'formatted', status = 'unknown') form = 'formatted', status = 'unknown')
WRITE( stdout, '(5x,"Writing coordinates on file ",a)') & WRITE( stdout, '(5x,"Writing coordinates to file ",a)') &
trim(fileout)//'.xyz' trim(fileout)//'.xyz'
else else
open (unit = ounit+1, file = 'coord.xyz', & open (unit = ounit+1, file = 'coord.xyz', &
form = 'formatted', status = 'unknown') form = 'formatted', status = 'unknown')
WRITE( stdout, '("Writing coordinates on file coord.xyz")') WRITE( stdout, '("Writing coordinates to file coord.xyz")')
end if end if
endif endif
@ -357,7 +364,10 @@ SUBROUTINE chdens
call errore ('chdens', 'wrong iflag', 1) call errore ('chdens', 'wrong iflag', 1)
endif endif
!
print '(5x,"Plot Type: ",a," Output format: ",a)', &
plotname(iflag), formatname(output_format)
!
deallocate(rhor) deallocate(rhor)
deallocate(rhog) deallocate(rhog)
deallocate(tau) deallocate(tau)
@ -566,7 +576,6 @@ subroutine plot_2d (nx, ny, m1, m2, x0, e1, e2, ngm, g, rhog, alat, &
rhoim = rhoim / nx / ny rhoim = rhoim / nx / ny
print '(5x,"Min, Max, imaginary charge: ",3f12.6)', rhomin, rhomax, rhoim print '(5x,"Min, Max, imaginary charge: ",3f12.6)', rhomin, rhomax, rhoim
print '(5x,"Output format: ",i3)', output_format
! !
! and we print the charge on output ! and we print the charge on output

View File

@ -36,16 +36,16 @@ subroutine plot_io (filplot, title, nrx1, nrx2, nrx3, nr1, nr2, &
if (iflag == 0 ) call errore('plot_io',& if (iflag == 0 ) call errore('plot_io',&
' iflag==0 not allowed, use read_io_header ',1) ' iflag==0 not allowed, use read_io_header ',1)
if (iflag > 0) then if (iflag > 0) then
WRITE( stdout, '(5x,"Writing data on file ",a)') filplot WRITE( stdout, '(5x,"Writing data to file ",a)') TRIM(filplot)
open (unit = iunplot, file = filplot, form = 'formatted', & open (unit = iunplot, file = filplot, form = 'formatted', &
status = 'unknown', err = 100, iostat = ios) status = 'unknown', err = 100, iostat = ios)
else else
WRITE( stdout, '(5x,"Reading data from file ",a)') filplot WRITE( stdout, '(5x,"Reading data from file ",a)') TRIM(filplot)
open (unit = iunplot, file = filplot, form = 'formatted', & open (unit = iunplot, file = filplot, form = 'formatted', &
status = 'old', err = 100, iostat = ios) status = 'old', err = 100, iostat = ios)
endif endif
100 call errore ('plot_io', 'opening file '//filplot, abs (ios) ) 100 call errore ('plot_io', 'opening file '//TRIM(filplot), abs (ios) )
rewind (iunplot) rewind (iunplot)
if (iflag > 0) then if (iflag > 0) then
@ -106,10 +106,10 @@ subroutine read_io_header(filplot, title, nrx1, nrx2, nrx3, nr1, nr2, nr3, &
if (filplot == ' ') call errore ('read_io_h', 'filename missing', 1) if (filplot == ' ') call errore ('read_io_h', 'filename missing', 1)
! !
iunplot = 4 iunplot = 4
WRITE( stdout, '(5x,"Reading header from file ",a)') filplot WRITE( stdout, '(5x,"Reading header from file ",a)') TRIM(filplot)
open (unit = iunplot, file = filplot, form = 'formatted', & open (unit = iunplot, file = filplot, form = 'formatted', &
status = 'old', err = 100, iostat = ios) status = 'old', err = 100, iostat = ios)
100 call errore ('plot_io', 'opening file '//filplot, abs (ios) ) 100 call errore ('plot_io', 'opening file '//TRIM(filplot), abs (ios) )
rewind (iunplot) rewind (iunplot)
read (iunplot, '(a)') title read (iunplot, '(a)') title

View File

@ -24,25 +24,28 @@ PROGRAM postproc
USE io_files, ONLY : nd_nmbr USE io_files, ONLY : nd_nmbr
USE io_global, ONLY : ionode USE io_global, ONLY : ionode
! !
IMPLICIT NONE
CHARACTER(len=256) :: filplot
!
! initialise parallel environment ! initialise parallel environment
! !
CALL start_postproc (nd_nmbr) CALL start_postproc (nd_nmbr)
IF ( ionode ) CALL input_from_file ( ) IF ( ionode ) CALL input_from_file ( )
! !
call extract () call extract (filplot)
! !
call clean_pw () call clean_pw ()
! !
! chdens should be called on just one processor ! chdens should be called on just one processor
! !
IF ( ionode ) call chdens () IF ( ionode ) call chdens (filplot)
! !
call stop_pp () call stop_pp ()
! !
END PROGRAM postproc END PROGRAM postproc
! !
!----------------------------------------------------------------------- !-----------------------------------------------------------------------
SUBROUTINE extract SUBROUTINE extract (filplot)
!----------------------------------------------------------------------- !-----------------------------------------------------------------------
! !
! This subroutine reads the data for the output file produced by pw.x ! This subroutine reads the data for the output file produced by pw.x
@ -62,7 +65,7 @@ SUBROUTINE extract
USE mp, ONLY : mp_bcast USE mp, ONLY : mp_bcast
IMPLICIT NONE IMPLICIT NONE
CHARACTER(len=256) :: filplot CHARACTER(len=256), INTENT(out) :: filplot
INTEGER :: plot_num, kpoint, kband, spin_component, ios INTEGER :: plot_num, kpoint, kband, spin_component, ios
LOGICAL :: stm_wfc_matching, lsign LOGICAL :: stm_wfc_matching, lsign