Small change: stdout used everywhere in pwcond.

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@3121 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
dalcorso 2006-05-15 07:57:15 +00:00
parent 19b55af239
commit 269425ee76
5 changed files with 63 additions and 50 deletions

View File

@ -134,7 +134,7 @@ subroutine compbs_2(nocros, norb, n2d, ntot, amat, bmat, &
!
! Forming (2*n2d+norb, ntot) matrix of eigenvectors
! cooficients, storing them in vec
! coeficients, storing them in vec
!
vec=(0.d0,0.d0)

View File

@ -5,13 +5,13 @@
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
subroutine cond_out ()
use io_global, only : stdout
SUBROUTINE cond_out ()
USE io_global, ONLY : stdout
USE ions_base, ONLY: atm
use lsda_mod, only: nspin
USE lsda_mod, ONLY: nspin
USE noncollin_module, ONLY : noncolin, npol
use spin_orb, only : lspinorb
use cond
USE spin_orb, ONLY : lspinorb
USE cond
!---------------------------
! Some output
@ -32,21 +32,21 @@ subroutine cond_out ()
endif
if(nspin.eq.2) then
write(6,'(/,9x, ''LSDA calculations, spin index ='',i6)') iofspin
write(stdout,'(/,9x, ''LSDA calculations, spin index ='',i6)') iofspin
endif
if(nspin.eq.4) then
write(6,'(/,9x, ''Noncollinear calculations'')')
write(stdout,'(/,9x, ''Noncollinear calculations'')')
if(lspinorb) &
write(6,'(/,9x, ''Noncollinear calculations with spin-orbit'')')
write(stdout,'(/,9x, ''Noncollinear calculations with spin-orbit'')')
endif
write (6, 300) nrx, nry, nz1
write (stdout, 300) nrx, nry, nz1
300 format (/,5x, &
& 'nrx = ',i12,/,5x, &
& 'nry = ',i12,/,5x, &
& 'nz1 = ',i12,/,5x)
write (6, 301) energy0, denergy, nenergy, ecut2d, ewind, epsproj
write (stdout, 301) energy0, denergy, nenergy, ecut2d, ewind, epsproj
301 format (/,5x, &
& 'energy0 = ',1pe15.1,/,5x, &
& 'denergy = ',1pe15.1,/,5x, &
@ -55,6 +55,18 @@ subroutine cond_out ()
& 'ewind = ',1pe15.1,/,5x, &
& 'epsproj = ',1pe15.1,/,5x)
!
! Information about the k points
!
WRITE( stdout, '(/5x,"number of k_|| points=",i5)') nkpts
WRITE( stdout, '(23x,"cart. coord. in units 2pi/a_0")')
DO k = 1, nkpts
WRITE( stdout, '(8x,"k(",i5,") = (",2f12.7,"), wk =",f12.7)') k, &
(xyk (ipol, k) , ipol = 1, 2) , wkpt (k)
ENDDO
if(ikind.eq.1) then
write(stdout,'(''----- Information about left/right lead -----'')')
@ -62,69 +74,69 @@ subroutine cond_out ()
write(stdout,'(''----- Information about left lead ----- '')')
endif
write (6, 200) nocrosl, noinsl, norbl, norbf, nrzl
write (stdout, 200) nocrosl, noinsl, norbl, norbf, nrzl
200 format (/,5x, &
& 'nocros = ',i12,/,5x, &
& 'noins = ',i12,/,5x, &
& 'norb = ',i12,/,5x, &
& 'norbf = ',i12,/,5x, &
& 'nrz = ',i12,/,5x)
write(6, '(6x,''iorb type ibeta ang. mom.'',3x, &
write(stdout, '(6x,''iorb type ibeta ang. mom.'',3x, &
& ''m position (a_0)'')')
write(6,'(5x,i4,4x,i5,5x,i3,6x,i3,6x,i3,'' taunew('', &
write(stdout,'(5x,i4,4x,i5,5x,i3,6x,i3,6x,i3,'' taunew('', &
& i4,'')=('',3f8.4,'')'')') &
& ( iorb,tblml(1,iorb), tblml(2,iorb), tblml(3,iorb),&
& tblml(4,iorb), iorb, &
& (taunewl(ipol,iorb),ipol=1,3), iorb=1, norbl )
if(norbl.le.80) then
write(6,'(4x,''k slab'',3x,'' z(k) z(k+1)'', &
write(stdout,'(4x,''k slab'',3x,'' z(k) z(k+1)'', &
& 5x,''crossing(iorb=1,norb)'')')
do k=1, nrzl
write(6,'(2x,i3,2x,3f7.4,3x,80i1)') &
write(stdout,'(2x,i3,2x,3f7.4,3x,80i1)') &
k,zl(k),zl(k+1),zl(k+1)-zl(k),(crosl(iorb,k),iorb=1,norbl)
enddo
endif
if(ikind.eq.2) then
write(stdout,'(''----- Information about right lead -----'')')
write (6, 200) nocrosr, noinsr, norbr, norbf, nrzr
write(6, '(6x,''iorb type ibeta ang. mom.'',3x, &
write (stdout, 200) nocrosr, noinsr, norbr, norbf, nrzr
write(stdout, '(6x,''iorb type ibeta ang. mom.'',3x, &
& ''m position (a_0)'')')
write(6,'(5x,i4,4x,i5,5x,i3,6x,i3,6x,i3,'' taunew('', &
write(stdout,'(5x,i4,4x,i5,5x,i3,6x,i3,6x,i3,'' taunew('', &
& i4,'')=('',3f8.4,'')'')') &
& ( iorb,tblmr(1,iorb), tblmr(2,iorb), tblmr(3,iorb),&
& tblmr(4,iorb), iorb, &
& (taunewr(ipol,iorb),ipol=1,3), iorb=1, norbr )
if(norbr.le.80) then
write(6,'(4x,''k slab'',3x,'' z(k) z(k+1)'', &
write(stdout,'(4x,''k slab'',3x,'' z(k) z(k+1)'', &
& 5x,''crossing(iorb=1,norb)'')')
do k=1, nrzr
write(6,'(2x,i3,2x,3f7.4,3x,80i1)') &
write(stdout,'(2x,i3,2x,3f7.4,3x,80i1)') &
k,zr(k),zr(k+1),zr(k+1)-zr(k),(crosr(iorb,k),iorb=1,norbr)
enddo
endif
endif
if(ikind.gt.0) then
write(6,'(''----- Information about scattering region -----'')')
write (6, 201) noinss, norbs, norbf, nrzs
write(stdout,'(''----- Information about scattering region -----'')')
write (stdout, 201) noinss, norbs, norbf, nrzs
201 format (/,5x, &
& 'noins = ',i12,/,5x, &
& 'norb = ',i12,/,5x, &
& 'norbf = ',i12,/,5x, &
& 'nrz = ',i12,/,5x)
write(6, '(6x,''iorb type ibeta ang. mom.'',3x, &
write(stdout, '(6x,''iorb type ibeta ang. mom.'',3x, &
& ''m position (a_0)'')')
write(6,'(5x,i4,4x,i5,5x,i3,6x,i3,6x,i3,'' taunew('', &
write(stdout,'(5x,i4,4x,i5,5x,i3,6x,i3,6x,i3,'' taunew('', &
& i4,'')=('',3f8.4,'')'')') &
& ( iorb,tblms(1,iorb), tblms(2,iorb), tblms(3,iorb),&
& tblms(4,iorb), iorb, &
& (taunews(ipol,iorb),ipol=1,3), iorb=1, norbs )
if(norbs.le.80) then
write(6,'(4x,''k slab'',3x,'' z(k) z(k+1)'', &
write(stdout,'(4x,''k slab'',3x,'' z(k) z(k+1)'', &
& 5x,''crossing(iorb=1,norb)'')')
do k=1, nrzs
write(6,'(2x,i3,2x,3f7.4,3x,80i1)') &
write(stdout,'(2x,i3,2x,3f7.4,3x,80i1)') &
k,zs(k),zs(k+1),zs(k+1)-zs(k),(cross(iorb,k),iorb=1,norbs)
enddo
endif

View File

@ -16,13 +16,14 @@ subroutine init_cond (nregion, flag)
! flag - 'l'/'s'/'r'/'t' if the unit cell containes
! the left lead/scat. reg./right lead/all of them
!
use pwcom
use io_files, only : save_file
USE io_global, ONLY : stdout
USE pwcom
USE io_files, ONLY : save_file
USE noncollin_module, ONLY : noncolin, npol
USE uspp_param, ONLY : nbrx, nbeta, lll, betar, tvanp
use atom, only: mesh, r
USE atom, ONLY: mesh, r
USE ions_base, ONLY : atm, nat, ityp, ntyp => nsp, tau
use cond
USE cond
implicit none
@ -149,19 +150,19 @@ subroutine init_cond (nregion, flag)
!----------------
! Some output
write(6,*)
write(stdout,*)
if(flag.eq.'l') then
write(6,'(''===== INPUT FILE containing the left lead ====='')')
write(stdout,'(''===== INPUT FILE containing the left lead ====='')')
elseif(flag.eq.'s') then
write(6,'(''===== INPUT FILE containing the scat. region ====='')')
write(stdout,'(''===== INPUT FILE containing the scat. region ====='')')
elseif(flag.eq.'r') then
write(6,'(''===== INPUT FILE containing the right lead ====='')')
write(stdout,'(''===== INPUT FILE containing the right lead ====='')')
elseif(flag.eq.'t') then
write(6,'(''===== INPUT FILE containing all the regions ====='')')
write(stdout,'(''===== INPUT FILE containing all the regions ====='')')
endif
write(6,'(/,5x,''GEOMETRY:'')')
write (6, 100) alat, omega, sarea, zlen, nat, ntyp
write(stdout,'(/,5x,''GEOMETRY:'')')
write (stdout, 100) alat, omega, sarea, zlen, nat, ntyp
100 format (/,5x, &
& 'lattice parameter (a_0) = ',f12.4,' a.u.',/,5x, &
& 'the volume = ',f12.4,' (a.u.)^3',/,5x, &
@ -170,17 +171,17 @@ subroutine init_cond (nregion, flag)
& 'number of atoms/cell = ',i12,/,5x, &
& 'number of atomic types = ',i12,/,5x)
write(6,'(5x,''crystal axes: (cart. coord. in units of a_0)'',/, &
write(stdout,'(5x,''crystal axes: (cart. coord. in units of a_0)'',/, &
& 3(15x,''a('',i1,'') = ('',3f8.4,'' ) '',/ ) )') &
& ( na, (at(nt,na), nt=1,3), na=1,3)
write(6,'(/,3x,''Cartesian axes'')')
write(6, '(/,5x,''site n. atom '', &
write(stdout,'(/,3x,''Cartesian axes'')')
write(stdout, '(/,5x,''site n. atom '', &
& '' positions (a_0 units)'')')
write(6, '(7x,i4,8x,a6,'' tau('',i3,'')=('',3f8.4,'' )'')') &
write(stdout, '(7x,i4,8x,a6,'' tau('',i3,'')=('',3f8.4,'' )'')') &
& ( na,atm(ityp(na)),na, &
& ( tau(nt,na),nt=1,3),na=1,nat )
write (6, 300) nr1s, nr2s, nr3s, nrx1s, nrx2s, nrx3s, &
write (stdout, 300) nr1s, nr2s, nr3s, nrx1s, nrx2s, nrx3s, &
nr1, nr2, nr3, nrx1, nrx2, nrx3
300 format (/,5x, &
& 'nr1s = ',i12,/,5x, &
@ -196,11 +197,11 @@ subroutine init_cond (nregion, flag)
& 'nrx2 = ',i12,/,5x, &
& 'nrx3 = ',i12,/,5x)
write(6,*) '_______________________________'
write(6,*) ' Radii of nonlocal spheres: '
write(6, '(/,5x,''type ibeta ang. mom.'', &
write(stdout,*) '_______________________________'
write(stdout,*) ' Radii of nonlocal spheres: '
write(stdout, '(/,5x,''type ibeta ang. mom.'', &
& '' radius (a_0 units)'')')
write(6, '(7x,a6,3x,i3,7x,i3,14x,f12.4)') &
write(stdout, '(7x,a6,3x,i3,7x,i3,14x,f12.4)') &
& ( ( atm(nt), ib, lll(ib,nt), rsph(ib,nt), &
& ib=1,nbeta(nt) ), nt=1,ntyp)

View File

@ -174,7 +174,7 @@ IF (noncolin) THEN
ENDIF
! do p = 1, nrz
! write(6,'(i5,2f12.6)') p, real(vppot(p,1,1,1)), imag(vppot(p,1,1,1))
! write(stdout,'(i5,2f12.6)') p, real(vppot(p,1,1,1)), imag(vppot(p,1,1,1))
! enddo
! stop

View File

@ -282,7 +282,7 @@ implicit none
x2 = (0.d0,0.d0)
call ZGEMM('n', 'n', ntran, nchanl, nchanl, x1, vec1, ntran, &
veceig, nchanl, x2, vec2, ntran)
write(6,*) 'Nchannel, Norbital, projection'
write(stdout,*) 'Nchannel, Norbital, projection'
!---------------------------
! Angular momentum projection of eigenchannels
!
@ -299,7 +299,7 @@ implicit none
xi1(ipol) = xi1(ipol)+intw2(iorba, ig)*vec2(2*n2d+ig, n)
enddo
enddo
write(6,'(2i5,2f20.12)') n, iorb-orbj_in+1, &
write(stdout,'(2i5,2f20.12)') n, iorb-orbj_in+1, &
( DBLE(xi1(ipol))**2+AIMAG(xi1(ipol))**2,ipol=1,npol)
enddo
endif