New routine input_from_file called everywhere

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@1948 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2005-06-09 07:35:50 +00:00
parent acc9136f3c
commit e3bb8be1db
6 changed files with 11 additions and 155 deletions

View File

@ -25,11 +25,6 @@ SUBROUTINE cg_readin()
NAMELIST /inputph/ prefix, fildyn, trans, epsil, raman, nmodes, &
tr2_ph, niter_ph, amass, outdir, asr, deltatau, nderiv, &
first, last, recover
CHARACTER (LEN=256) :: input_file
INTEGER :: nargs, iiarg, ierr, ILEN
INTEGER, EXTERNAL :: iargc
!
CALL start_clock('cg_readin')
!
@ -51,27 +46,8 @@ SUBROUTINE cg_readin()
!
IF ( ionode ) THEN
!
! ... Input from file ?
CALL input_from_file ( )
!
nargs = iargc()
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
OPEN ( UNIT = 5, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
CALL errore( 'iosys', 'input file ' // TRIM( input_file ) // &
& ' not found' , ierr )
!
END IF
!
END DO
READ(iunit,'(a)') title_ph
READ(iunit,inputph)
!

View File

@ -87,37 +87,12 @@ SUBROUTINE phq_readin()
! eth_ns : threshold for non-scf wavefunction calculation (Raman)
! dek : delta_xk used for wavefunctions derivation (Raman)
!
! ... local variables
!
CHARACTER (LEN=256) :: input_file
INTEGER :: nargs, iiarg, ierr, ILEN
INTEGER, EXTERNAL :: iargc
!
!
IF ( .NOT. ionode ) GOTO 400
!
! ... Input from file ?
!
nargs = iargc()
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
!
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
!
OPEN ( UNIT = 5, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
CALL errore( 'iosys', 'input file ' // TRIM( input_file ) // &
& ' not found' , ierr )
!
END IF
!
END DO
CALL input_from_file ( )
!
! ... Read the first line of the input file
!

View File

@ -24,7 +24,7 @@ SUBROUTINE iosys()
USE constants, ONLY : AU, eV_to_kelvin
USE mp_global, ONLY : npool, nproc_pool
!
USE io_global, ONLY : stdout
USE io_global, ONLY : stdout, ionode
!
USE bp, ONLY : nppstr_ => nppstr, &
gdir_ => gdir, &
@ -245,9 +245,7 @@ SUBROUTINE iosys()
! ... local variables
!
INTEGER :: unit = 5, &
i, iiarg, nargs, ia, ios, ierr, ilen, is, image, nt
INTEGER, EXTERNAL :: iargc
CHARACTER (LEN=80) :: input_file
i, ia, ios, is, image, nt
LOGICAL :: ltest
REAL(kind=DP) :: theta, phi
!
@ -256,29 +254,9 @@ SUBROUTINE iosys()
!
pseudo_dir = TRIM( pseudo_dir ) // '/pw/pseudo/'
!
! ... Input from file ?
!
nargs = iargc()
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
!
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
!
OPEN ( UNIT = unit, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
!
CALL errore( 'iosys', 'input file ' // TRIM( input_file ) // &
& ' not found' , ierr )
!
END IF
!
END DO
IF (ionode) THEN
CALL input_from_file ( )
END IF
!
! ... all namelists are read
!

View File

@ -34,10 +34,6 @@ SUBROUTINE do_cond(nodenumber)
bdl, bds, bdr, nz1, energy0, denergy, ecut2d, &
ewind, epsproj, delgep, cutplot
CHARACTER (LEN=80) :: input_file
INTEGER :: nargs, iiarg, ierr, ILEN
INTEGER, EXTERNAL :: iargc
nd_nmbr=nodenumber
CALL init_clocks(.TRUE.)
CALL start_clock('PWCOND')
@ -78,28 +74,9 @@ SUBROUTINE do_cond(nodenumber)
IF ( ionode ) THEN
!
! ... Input from file ?
CALL input_from_file ( )
!
nargs = iargc()
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
OPEN ( UNIT = 5, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
CALL errore( 'iosys', 'input file ' // TRIM( input_file ) // &
& ' not found' , ierr )
!
END IF
!
END DO
!
! reading the namelist inputpp
! reading the namelist inputcond
!
READ (5, inputcond, err=200, iostat=ios )
200 CALL errore ('do_cond','reading inputcond namelist',ABS(ios))

View File

@ -126,10 +126,6 @@ PROGRAM matdyn
INTEGER :: n, i, j, it, nq, na, nb, ndos, iout
NAMELIST /input/ flfrc, amass, asr, flfrq, flvec, at, dos, deltaE, &
& fldos, nk1, nk2, nk3, l1, l2, l3, ntyp, readtau, fltau
CHARACTER (LEN=256) :: input_file
INTEGER :: nargs, iiarg, ierr, ILEN
INTEGER, EXTERNAL :: iargc
!
!
CALL mp_start()
@ -162,27 +158,7 @@ PROGRAM matdyn
l2=1
l3=1
!
! ... Input from file ?
!
nargs = iargc()
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
OPEN ( UNIT = 5, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
CALL errore( 'iosys', 'input file ' // TRIM( input_file ) // &
& ' not found' , ierr )
!
END IF
!
END DO
CALL input_from_file ( )
!
READ (5,input)
!

View File

@ -87,10 +87,6 @@ PROGRAM q2r
!
NAMELIST / input / nr1, nr2, nr3, fild, zasr
!
CHARACTER (LEN=256) :: input_file
INTEGER :: nargs, iiarg, ierr, ILEN
INTEGER, EXTERNAL :: iargc
!
!
CALL mp_start()
!
@ -104,29 +100,7 @@ PROGRAM q2r
nr2 = 0
nr3 = 0
!
! ... Input from file ?
!
nargs = iargc()
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
!
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
!
OPEN ( UNIT = 5, FILE = input_file, FORM = 'FORMATTED', &
STATUS = 'OLD', IOSTAT = ierr )
!
CALL errore( 'iosys', 'input file ' // TRIM( input_file ) // &
& ' not found' , ierr )
!
END IF
!
END DO
CALL input_from_file ( )
!
READ ( 5, input )
!