Fixes for NAG Fortran compiler -- courtesy of Samuel Poncé and Henry Lambert (Oxford)

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@11748 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
spigafi 2015-09-22 20:24:28 +00:00
parent 0b0b4ff51f
commit bb0761a565
7 changed files with 24 additions and 25 deletions

View File

@ -473,8 +473,8 @@ CONTAINS
INTEGER, INTENT(IN) :: nproc ! number of procs in the communicator
INTEGER, INTENT(IN) :: comm ! communicator
INTEGER, INTENT(IN) :: ig_l2g1(ngwl1),ig_l2g2(ngwl2)
INTEGER, INTENT(IN) :: ngwl1,ngwl2
INTEGER, INTENT(IN) :: ig_l2g1(ngwl1),ig_l2g2(ngwl2)
! Global maximum number of G vectors for both grids
INTEGER, INTENT(in) :: n_g

View File

@ -18,7 +18,7 @@ program fqha
character(len=256) :: filename
!
!
write (*,"('File containing the dos >>> ',$)")
write (*,"('File containing the dos >>> ')",advance="no")
read(*,'(a)') filename
open(unit=1,file=filename,status='old')
!
@ -50,8 +50,8 @@ program fqha
F0 = F0 / 8065.5d0 / 13.6058d0
! normalization check: \sum g(omega) d\omega = 3*Nat
norm = sum (dos(1:ndiv)) * de
write(*,"('Check: 3*Nat = ',f8.4,5x'zero-point energy (Ry)=',f15.8)") norm,F0
write (*,"('Output file for the Free energy >>> ',$)")
write(*,"('Check: 3*Nat = ',f8.4,5x,'zero-point energy (Ry)=',f15.8)") norm,F0
write (*,"('Output file for the Free energy >>> ')",advance="no")
read(*,'(a)') filename
if ( filename == ' ') then
filename = 'fqha.out'
@ -60,7 +60,7 @@ program fqha
open(unit=1,file=filename,status='unknown')
!
1 continue
write (*,"('Temperature (K) >>> ',$)")
write (*,"('Temperature (K) >>> ')",advance="no")
read (*,*,end=20,err=20) T
if ( T < 0d0 ) then
write(*,"('Incorrect T < 0, stopping')")

View File

@ -25,10 +25,9 @@ USE spin_orb, ONLY : fcoef, domag
!
IMPLICIT NONE
INTEGER :: na, modes
COMPLEX(DP) :: dbecsum_nc( nhm, nhm, nat, nspin, modes)
COMPLEX(DP) :: dbecsum( nhm*(nhm+1)/2, nat, nspin_mag, modes)
INTEGER :: na, modes
!
! ... local variables
!

View File

@ -41,9 +41,9 @@ MODULE us_exx
! w(i) if i==imax
! iw(i+1) if i==imin-1
! 0 otherwise
INTEGER,INTENT(in) :: m, n, imin, imax, i
COMPLEX(DP) :: bexg_merge(m)
!
INTEGER,INTENT(in) :: m,n, imin, imax, i
REAL(DP),INTENT(in) :: w(m,n)
!
bexg_merge = (0._dp, 0._dp)

View File

@ -78,12 +78,12 @@ PROGRAM ev
!
IF ( ionode ) THEN
PRINT '(5x,"Lattice parameter or Volume are in (au, Ang) > ",$)'
PRINT '(5x,"Lattice parameter or Volume are in (au, Ang) > "), advance="NO"'
READ '(a)', au_unit
in_angstrom = au_unit=='Ang' .or. au_unit=='ANG' .or. &
au_unit=='ang'
IF (in_angstrom) PRINT '(5x,"Assuming Angstrom")'
PRINT '(5x,"Enter type of bravais lattice (fcc, bcc, sc, noncubic) > ",$)'
PRINT '(5x,"Enter type of bravais lattice (fcc, bcc, sc, noncubic) > "), advance="NO"'
READ '(a)',bravais
!
IF(trim(bravais)=='fcc'.or.trim(bravais)=='FCC') THEN
@ -102,7 +102,7 @@ PROGRAM ev
ENDIF
!
PRINT '(5x,"Enter type of equation of state :"/&
&5x,"1=birch1, 2=birch2, 3=keane, 4=murnaghan > ",$)'
&5x,"1=birch1, 2=birch2, 3=keane, 4=murnaghan > "), advance="NO"'
READ *,istat
IF(istat==1 .or. istat==4) THEN
npar=3
@ -112,7 +112,7 @@ PROGRAM ev
PRINT '(5x,"Unexpected eq. of state ",i2)', istat
STOP
ENDIF
PRINT '(5x,"Input file > ",$)'
PRINT '(5x,"Input file > "), advance="NO"'
READ '(a)',filin
OPEN(unit=2,file=filin,status='old',form='formatted',iostat=ierr)
IF (ierr/=0) THEN
@ -272,7 +272,7 @@ PROGRAM ev
INTEGER :: i, iun
LOGICAL :: exst
PRINT '(5x,"Output file > ",$)'
PRINT '(5x,"Output file > "), advance="NO"'
READ '(a)',filout
IF(filout/=' ') THEN
iun=8

View File

@ -48,47 +48,47 @@ program special_points
nshift(i)=0
enddo
!
write(*,'(5x,a,$)') 'bravais lattice >> '
write(*,'(5x,a)', advance="no") 'bravais lattice >> '
read(*,*) ibrav
!
write(*,'(5x,a,$)') 'filout [mesh_k] >> '
write(*,'(5x,a)',advance="no") 'filout [mesh_k] >> '
read(*,'(a)') filout
if (filout.eq.' ') filout='mesh_k'
open(unit=1,file=filout,status='unknown')
open(unit=2,file='info',status='unknown')
!
if(ibrav.eq.4 .or. ibrav.gt.5) then
write(*,'(5x,a,$)') 'enter celldm(3) >> '
write(*,'(5x,a)',advance="no") 'enter celldm(3) >> '
read(*,*) celldm(3)
end if
if(ibrav.ge.8) then
write(*,'(5x,a,$)') 'enter celldm(2) >> '
write(*,'(5x,a)',advance="no") 'enter celldm(2) >> '
read(*,*) celldm(2)
end if
if(ibrav.eq.5 .or. ibrav.ge.12) then
write(*,'(5x,a,$)') 'enter celldm(4) >> '
write(*,'(5x,a)',advance="no") 'enter celldm(4) >> '
read(*,*) celldm(4)
end if
if(ibrav.eq.14) then
write(*,'(5x,a)') 'enter celldm(5) >> cos(ac)'
write(*,'(5x,a,$)') 'enter celldm(5) >> '
write(*,'(5x,a)',advance="no") 'enter celldm(5) >> '
read(*,*) celldm(5)
write(*,'(5x,a)') 'enter celldm(6) >> cos(ab)'
write(*,'(5x,a,$)') 'enter celldm(6) >> '
write(*,'(5x,a)',advance="no") 'enter celldm(6) >> '
read(*,*) celldm(6)
end if
!
write(*,'(5x,a,$)') 'mesh: n1 n2 n3 >> '
write(*,'(5x,a)',advance="no") 'mesh: n1 n2 n3 >> '
read(*,*) nmax
nptot=nmax(1)*nmax(2)*nmax(3)
if(nptot.gt.nptx) then
write(*,'(5x,i6)') nptx
call errore('kpoints','nptx too small for this mesh',1)
endif
write(*,'(5x,a,$)') 'mesh: k1 k2 k3 (0 no shift, 1 shifted) >> '
write(*,'(5x,a)',advance="no") 'mesh: k1 k2 k3 (0 no shift, 1 shifted) >> '
read(*,*) nshift(1), nshift(2), nshift(3)
!
write(*,'(5x,a,$)') 'write all k? [f] >> '
write(*,'(5x,a)',advance="no") 'write all k? [f] >> '
read(*,'(a1)') answer
aflag= answer.eq.'t'.or.answer.eq.'T' .or. &
answer.eq.'y'.or.answer.eq.'Y' .or. &
@ -173,7 +173,7 @@ program special_points
endif
enddo
!
write(*,'(/5x,a,$)') '# of k-points == '
write(*,'(/5x,a)',advance="no") '# of k-points == '
write(*,'(i5,a5,i5)') nk,' of ',n
write(*,'(2x)')
!

View File

@ -111,7 +111,7 @@ SUBROUTINE get_file( input_file )
CALL get_arg (0,prgname)
!
IF ( nargs == 0 ) THEN
10 PRINT '("Input file > ",$)'
10 PRINT '("Input file > "), advance="NO"'
READ (5,'(a)', end = 20, err=20) input_file
IF ( input_file == ' ') GO TO 10
INQUIRE ( FILE = input_file, EXIST = exst )