Removed conflicting calls to "errore"

Low-level routines and simple programs should not call "errore"


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2774 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2006-02-07 08:52:56 +00:00
parent b05a42b971
commit e06832f549
10 changed files with 56 additions and 43 deletions

View File

@ -39,8 +39,9 @@ SUBROUTINE input_from_file( )
OPEN ( UNIT = unit, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
!
CALL errore( 'input_from_file', 'input file ' // TRIM( input_file ) &
& // ' not found' , ierr )
! TODO: return error code instead
!CALL errore( 'input_from_file', 'input file ' // TRIM( input_file ) &
! & // ' not found' , ierr )
!
END IF
!
@ -53,6 +54,7 @@ SUBROUTINE get_file( input_file )
!
! This subroutine reads, either from command line or from terminal,
! the name of a file to be opened
! TODO: return error code if an error occurs
!
IMPLICIT NONE
!
@ -78,9 +80,9 @@ SUBROUTINE get_file( input_file )
ELSE IF ( nargs == 1 ) then
CALL getarg (1,input_file)
ELSE
CALL errore( TRIM(prgname), 'too many arguments' , nargs )
PRINT '(A,": too many arguments ",i4)', TRIM(prgname), nargs
END IF
RETURN
20 CALL errore( TRIM(prgname), 'reading file name' , 1 )
20 PRINT '(A,": reading file name ",A)', TRIM(prgname), TRIM(input_file)
!
END SUBROUTINE get_file

View File

@ -2,7 +2,7 @@
include ../make.sys
OBJS = write_upf.o errore.o
OBJS = write_upf.o
MODS = ../Modules/kind.o ../Modules/parameters.o ../Modules/pseudo_types.o \
../Modules/parser.o ../Modules/io_global.o ../Modules/mp_global.o \
../Modules/mp.o ../Modules/parallel_include.o ../Modules/constants.o

View File

@ -36,8 +36,8 @@ program mypp2upf
close (unit=2)
stop
20 call errore ('mypp2upf', 'Reading pseudo file name ', 1)
20 write (6,'("mypp2upf: error reading pseudopotential file name")')
stop
end program mypp2upf
module mypp
@ -60,8 +60,8 @@ subroutine read_mypp(iunps)
! ----------------------------------------------------------
!
return
100 call errore ('read_mypp', 'Reading pseudo file', 100 )
100 write (6,'("read_mypp: error reading pseudopotential file")')
stop
end subroutine read_mypp
! ----------------------------------------------------------

View File

@ -1,9 +0,0 @@
subroutine errore(a,b,n)
character(len=*) :: a,b
if (n.ne.0) then
write(6,'(//'' program '',a,'':'',a,''.'',8x,i8,8x,''stop'')') a,b,n
stop
end if
end subroutine errore

View File

@ -39,8 +39,8 @@ program fhi2upf
close (unit=2)
stop
20 call errore ('fhi2upf', 'Reading pseudo file name ', 1)
20 write (6,'("fhi2upf: error reading pseudopotential file name")')
stop
end program fhi2upf
module fhi
@ -90,7 +90,8 @@ subroutine read_fhi(iunps)
lmax_ = lmax_ - 1
if (lmax_+1 > Nl) then
call errore('read_fhi','too many l-components',1)
write (6,'("read_fhi: too many l-components...stopping")')
stop
end if
do i=1,10
@ -105,7 +106,8 @@ subroutine read_fhi(iunps)
if ( l > 0) then
if (comp(l)%nmesh /= comp(0)%nmesh .or. &
comp(l)%amesh /= comp(0)%amesh ) then
call errore('read_fhi','different radial grids not allowed',i)
write(6,'("read_fhi: different radial grids not allowed...stopping")')
stop
end if
end if
mesh = comp(l)%nmesh
@ -126,7 +128,8 @@ subroutine read_fhi(iunps)
do i=1,mesh
read(iunps,*,end=10, err=20) r, rho_atc_(i), drhoc, d2rhoc
if ( abs( r - comp(0)%grid(i) ) > 1.d-6 ) then
call errore('read_fhi','radial grid for core charge?',i)
write(6,'("read_fhi: radial grid for core charge? stopping")')
stop
end if
end do
nlcc_ = .true.
@ -140,9 +143,11 @@ subroutine read_fhi(iunps)
! ----------------------------------------------------------
return
!
20 call errore('read_fhi','error reading core charge',i)
20 write(6,'("read_fhi: error reading core charge")')
stop
!
100 call errore ('read_fhi', 'Reading pseudo file', 100 )
100 write(6,'("read_fhi: error reading pseudopotential file")')
stop
end subroutine read_fhi

View File

@ -37,7 +37,8 @@ program rrkj2upf
close (unit=2)
stop
20 call errore ('rrkj2upf', 'Reading pseudo file name ', 1)
20 write (6,'("rrkj2upf: error reading pseudopotential file name")')
stop
end program rrkj2upf
@ -149,7 +150,8 @@ subroutine read_rrkj(iunps)
! ----------------------------------------------------------
!
return
100 call errore ('read_rrkj', 'Reading pseudo file', 100 )
100 write (6,'("read_rrkj: error reading pseudopotential file")')
stop
end subroutine read_rrkj

View File

@ -36,6 +36,7 @@ program uspp2upf
close (unit=2)
stop
20 call errore ('uspp2upf', 'Reading pseudo file name ', 1)
20write (6,'("uspp2upf: error reading pseudopotential file name")')
stop
end program uspp2upf

View File

@ -303,7 +303,8 @@ subroutine convert_uspp
else if (exfact.eq. 5) then
iexch=1; icorr=4; igcx=3; igcc=4 ! Perdew-Becke-Erkerhof
else
call errore('convert','Wrong xc in pseudopotential',1)
write (6,'("convert: wrong xc in pseudopotential ",f12.6)') exfact
stop
end if
allocate (r(mesh), rab(mesh))

View File

@ -36,5 +36,6 @@ program vdb2upf
close (unit=2)
stop
20 call errore ('vdb2upf', 'Reading pseudo file name ', 1)
20 write (6,'("vdb2upf: error reading pseudopotential file name")')
stop
end program vdb2upf

View File

@ -123,8 +123,9 @@ end subroutine write_upf
write (ounps, '(a10)', err = 100, iostat = ios) "</PP_INFO>"
return
100 call errore ('write_pseudo_comment', 'Writing pseudo file', abs ( &
ios))
100 write(6,'("write_pseudo_comment: error writing pseudopotential file")')
stop
end subroutine write_pseudo_comment
!
@ -157,8 +158,8 @@ end subroutine write_upf
write (ounps, '(a5,t24,a)', err = 100, iostat = ios) "US", &
"Ultrasoft pseudopotential"
else
call errore ('write_pseudo_header',&
'Unknown PP type: '//pseudotype, 1)
write(6,'("write_pseudo_header: unknown PP type ",A)') pseudotype
stop
endif
write (ounps, '(l5,t24,a)', err = 100, iostat = ios) nlcc , &
"Nonlinear Core Correction"
@ -182,8 +183,9 @@ end subroutine write_upf
!---> End header writing
write (ounps, '(a12)', err = 100, iostat = ios) "</PP_HEADER>"
return
100 call errore ('write_pseudo_header','Writing pseudo file', abs(ios) )
return
100 write(6,'("write_pseudo_header: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_header
@ -214,7 +216,8 @@ end subroutine write_upf
return
100 call errore ('write_pseudo_rhoatom','Writing pseudo file',abs(ios))
100 write(6,'("write_pseudo_mesh: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_mesh
@ -240,7 +243,8 @@ end subroutine write_upf
write (ounps, '(a10)', err = 100, iostat = ios) "</PP_NLCC>"
return
100 call errore ('write_pseudo_nlcc', 'Writing pseudo file', abs (ios))
100 write(6,'("write_pseudo_nlcc: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_nlcc
!
@ -262,9 +266,10 @@ end subroutine write_upf
( vloc0(ir), ir = 1, mesh )
write (ounps, '(a11)', err = 100, iostat = ios) "</PP_LOCAL>"
return
100 call errore ('write_pseudo_local', 'Writing pseudo file', abs(ios) )
end subroutine write_pseudo_local
100 write(6,'("write_pseudo_local: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_local
!
!---------------------------------------------------------------------
subroutine write_pseudo_nl (ounps)
@ -342,7 +347,8 @@ end subroutine write_upf
write (ounps, '(a14)', err = 100, iostat = ios) "</PP_NONLOCAL>"
return
100 call errore ('write_pseudo_nl', 'Writing pseudo file', abs (ios) )
100 write(6,'("write_pseudo_nl: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_nl
@ -371,7 +377,9 @@ end subroutine write_upf
write (ounps, '(a11)', err = 100, iostat = ios) "</PP_PSWFC>"
return
100 call errore ('write_pseudo_pswfc', 'Writing pseudo file', abs(ios) )
100 write(6,'("write_pseudo_pswfc: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_pswfc
!
!---------------------------------------------------------------------
@ -393,7 +401,9 @@ end subroutine write_upf
write (ounps, '(a13)', err = 100, iostat = ios) "</PP_RHOATOM>"
return
100 call errore('write_pseudo_rhoatom','Writing pseudo file',abs(ios))
100 write(6,'("write_pseudo_rhoatom: errore writing pseudopotential file")')
stop
end subroutine write_pseudo_rhoatom
!---------------------------------------------------------------------