Wrappers for iargc, getarg, getenv used everywhere. Next step: replace them

with standard calls if accepted by all relevant compilers


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@11744 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2015-09-21 21:04:37 +00:00
parent 6e64c07d0f
commit 9592f95ef4
9 changed files with 64 additions and 91 deletions

View File

@ -48,19 +48,13 @@ MODULE command_line_options
CONTAINS
!
SUBROUTINE get_command_line ( input_command_line )
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
IMPLICIT NONE
CHARACTER(LEN=*), OPTIONAL :: input_command_line
INTEGER :: narg
#if !defined(__NAG)
INTEGER :: iargc
! Do not define iargc as external: gfortran doesn't like it
#endif
LOGICAL :: read_string
CHARACTER(LEN=256) :: arg
CHARACTER(LEN=6), EXTERNAL :: int_to_char
INTEGER, EXTERNAL :: i_argc
!
command_line = ' '
read_string = PRESENT ( input_command_line )
@ -71,7 +65,7 @@ CONTAINS
IF (read_string) THEN
nargs = my_iargc ( input_command_line )
ELSE
nargs = iargc()
nargs = i_argc()
ENDIF
CALL mp_bcast ( nargs, root, world_comm )
!
@ -85,7 +79,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL getarg ( narg, arg )
CALL get_arg ( narg, arg )
ENDIF
narg = narg + 1
SELECT CASE ( TRIM(arg) )
@ -93,7 +87,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, input_file_ )
ELSE
CALL getarg ( narg, input_file_ )
CALL get_arg ( narg, input_file_ )
ENDIF
IF ( TRIM (input_file_) == ' ' ) GO TO 15
narg = narg + 1
@ -101,7 +95,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL getarg ( narg, arg )
CALL get_arg ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) nimage_
narg = narg + 1
@ -109,7 +103,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL getarg ( narg, arg )
CALL get_arg ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) npool_
narg = narg + 1
@ -117,7 +111,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL getarg ( narg, arg )
CALL get_arg ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) ntg_
narg = narg + 1
@ -125,7 +119,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL getarg ( narg, arg )
CALL get_arg ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) nband_
narg = narg + 1
@ -133,7 +127,7 @@ CONTAINS
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL getarg ( narg, arg )
CALL get_arg ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) ndiag_
narg = narg + 1

View File

@ -19,27 +19,22 @@ SUBROUTINE plugin_arguments()
USE io_global, ONLY : stdout
!
USE plugin_flags
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
!
IMPLICIT NONE
!
#if !defined(__NAG)
INTEGER :: iargc
#endif
INTEGER, EXTERNAL :: i_argc
INTEGER :: iiarg, nargs, i, i0
CHARACTER (len=1), EXTERNAL :: lowercase
CHARACTER (len=256) :: arg
!
nargs = iargc()
nargs = i_argc()
! add here more plugins
use_plumed = .false.
use_pw2casino = .false.
use_environ = .false.
!
DO iiarg = 1, nargs
CALL getarg( iiarg, plugin_name)
CALL get_arg( iiarg, plugin_name)
IF ( plugin_name(1:1) == '-') THEN
i0 = 1
IF ( plugin_name(2:2) == '-') i0 = 2

View File

@ -13,30 +13,25 @@ FUNCTION input_images_getarg( ) RESULT(input_images)
! return N (0 if not found)
!
USE kinds, ONLY : DP
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
!
IMPLICIT NONE
!
INTEGER :: input_images
CHARACTER(len=256) :: myname
#if !defined(__NAG)
INTEGER :: iargc
#endif
INTEGER, EXTERNAL :: i_argc
INTEGER :: iiarg, nargs, i, i0
!
nargs = iargc()
nargs = i_argc()
input_images = 0
!
DO iiarg = 1, nargs
!
CALL getarg( iiarg, myname)
CALL get_arg( iiarg, myname)
!
IF ( TRIM( myname ) == '-input_images' .OR. &
TRIM( myname ) == '--input_images' ) THEN
!
CALL getarg( ( iiarg + 1 ) , myname )
CALL get_arg( ( iiarg + 1 ) , myname )
!
READ(myname,*) input_images
RETURN

View File

@ -47,9 +47,6 @@ PROGRAM Q2QSTAR
USE io_dyn_mat, ONLY : read_dyn_mat_param, read_dyn_mat_header, &
read_dyn_mat, read_dyn_mat_tail, &
write_dyn_mat_header
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
!
IMPLICIT NONE
!
@ -65,19 +62,17 @@ PROGRAM Q2QSTAR
!
COMPLEX(DP),ALLOCATABLE :: phi(:,:,:,:), d2(:,:)
INTEGER :: i,j, icar,jcar, na,nb
#if !defined(__NAG)
INTEGER :: iargc ! intrinsic function
#endif
INTEGER, EXTERNAL :: i_argc ! wrapper for iargc
!
NAMELIST / input / fildyn
!
CALL mp_startup()
CALL environment_start(CODE)
!
nargs = iargc()
nargs = i_argc()
IF(nargs < 1) CALL errore(CODE, 'Argument is missing! Syntax: "q2qstar dynfile [outfile]"', 1)
!
CALL getarg(1, fildyn)
CALL get_arg(1, fildyn)
CALL mp_bcast(fildyn, ionode_id,world_comm)
!
! check input
@ -86,7 +81,7 @@ PROGRAM Q2QSTAR
!
! set up output
IF (nargs > 1) THEN
CALL getarg(2, filout)
CALL get_arg(2, filout)
ELSE
filout = TRIM(fildyn)//".rot"
ENDIF

View File

@ -169,7 +169,7 @@ pw_export.x : pw_export.o libpp.a $(MODULES) $(LIBOBJS)
- ( cd ../../bin ; ln -fs ../PP/src/$@ . )
sumpdos.x : sumpdos.o
$(LD) $(LDFLAGS) -o $@ sumpdos.o
$(LD) $(LDFLAGS) -o $@ sumpdos.o $(MODULES) $(LIBOBJS) $(LIBS)
- ( cd ../../bin ; ln -fs ../PP/src/$@ . )
epsilon.x : epsilon.o libpp.a $(MODULES) $(LIBOBJS)

View File

@ -7,10 +7,6 @@
!
PROGRAM sumpdos
!
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
!
IMPLICIT NONE
!
! AUTHOR: Andrea Ferretti
@ -21,9 +17,7 @@ PROGRAM sumpdos
! file names are read from stdin
! USAGE: sumpdos <file1> ... <fileN>
!
#if !defined(__NAG)
INTEGER :: iargc ! function giving no of arguments
#endif
INTEGER, EXTERNAL :: i_argc ! function giving no of arguments
INTEGER :: ngrid ! dimension of the energy grid
INTEGER :: nfile ! number of files to sum
INTEGER :: nspin ! number of spin_component
@ -52,13 +46,13 @@ efermi = 0.0d0
!
! get the number of arguments (i.e. the number of files)
!
nfile = iargc ()
nfile = i_argc ()
IF ( nfile == 0 ) THEN
WRITE(0,"( 'No file to sum' )")
STOP
ENDIF
CALL getarg ( 1, str1 )
CALL get_arg ( 1, str1 )
!
SELECT CASE ( trim(str1) )
CASE ( "-h" )
@ -79,7 +73,7 @@ efermi = 0.0d0
!
! read file names from file
!
CALL getarg ( 2, filein )
CALL get_arg ( 2, filein )
IF ( len_trim(filein) == 0 ) CALL errore('sumpdos','provide filein name',2)
INQUIRE( FILE=trim(filein), EXIST=exist )
@ -126,7 +120,7 @@ efermi = 0.0d0
ALLOCATE( file(nfile), STAT=ierr )
IF (ierr/=0) CALL errore('sumpdos','allocating FILE',abs(ierr))
DO iarg = 1, nfile
CALL getarg ( iarg, file(iarg) )
CALL get_arg ( iarg, file(iarg) )
ENDDO
END SELECT

View File

@ -24,15 +24,10 @@ subroutine read_input_and_bcast(filerecon, r_paw)
USE parameters, ONLY : ntypx,lmaxx,lqmax
USE control_flags, ONLY : twfcollect
USE klist, ONLY : nelup, neldw, nelec
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
IMPLICIT NONE
#if !defined(__NAG)
INTEGER :: iargc
#endif
INTEGER, EXTERNAL :: i_argc
INTEGER :: nargs, iiarg, ierr, ios, i
LOGICAL :: found ! input_file found or not ?
REAL(DP) :: norm, xeps_dot_xk
@ -105,19 +100,19 @@ subroutine read_input_and_bcast(filerecon, r_paw)
! This part is similar to subroutine input_from_file (in flib/inpfile.f90)
nargs = iargc()
nargs = i_argc()
found = .FALSE.
input_file = ' '
DO iiarg = 1, (nargs-1)
!
CALL getarg( iiarg, input_file )
CALL get_arg( iiarg, input_file )
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' .OR. &
TRIM( input_file ) == '-i' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
CALL get_arg( ( iiarg + 1 ) , input_file )
found = .TRUE.
EXIT
ENDIF

View File

@ -110,9 +110,6 @@ Program manip_spectra
USE kinds, ONLY : DP
USE constants, ONLY : pi
USE edge_energy, ONLY: getE
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
! Input
LOGICAL :: shift_spectrum
REAL(kind=dp) :: xe0
@ -123,9 +120,7 @@ Program manip_spectra
LOGICAL :: found
INTEGER :: i, j
#if !defined(__NAG)
INTEGER :: iargc
#endif
INTEGER, EXTERNAL :: i_argc
INTEGER :: nargs, iiarg, ierr, ios
INTEGER :: nenergy, istart, i0_l2, nenergy_conv
REAL(kind=dp) :: el2, el3, so_splitting, emin_conv, emax_conv, de
@ -168,19 +163,19 @@ Program manip_spectra
! Read namelist
!
nargs = iargc()
nargs = i_argc()
found = .FALSE.
input_file = ' '
DO iiarg = 1, (nargs-1)
!
CALL getarg( iiarg, input_file )
CALL get_arg( iiarg, input_file )
IF ( TRIM( input_file ) == '-input' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-in' .OR. &
TRIM( input_file ) == '-i' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
CALL get_arg( ( iiarg + 1 ) , input_file )
found = .TRUE.
EXIT
ENDIF

View File

@ -5,54 +5,64 @@
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
! Wrappers for intrinsic iargc, getarg, getenv - machine-dependent stuff here
!
INTEGER FUNCTION i_argc ( )
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc
#else
! do not declare it external: gfortran doesn't like it
INTEGER :: iargc
#endif
i_argc = iargc ( )
END FUNCTION i_argc
!
SUBROUTINE get_env ( variable_name, variable_value )
!
! Wrapper for intrinsic getenv - all machine-dependent stuff here
!
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : getenv
#endif
CHARACTER (LEN=*) :: variable_name, variable_value
!
CALL getenv ( variable_name, variable_value)
!
END SUBROUTINE get_env
!
SUBROUTINE get_arg ( iarg, arg )
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : getarg
#endif
INTEGER, INTENT(IN) :: iarg
CHARACTER (LEN=*), INTENT(OUT) :: arg
CALL getarg ( iarg, arg )
END SUBROUTINE get_arg
!
!----------------------------------------------------------------------------
SUBROUTINE input_from_file( )
!
! This subroutine checks command-line arguments for -i[nput] "file name"
! if "file name" is present, attach input unit 5 to the specified file
!
#if defined(__NAG)
USE F90_UNIX_ENV, ONLY : iargc, getarg
#endif
!
IMPLICIT NONE
!
INTEGER :: stdin = 5, stderr = 6, ierr = 0
CHARACTER (LEN=256) :: input_file
LOGICAL :: found
!
#if !defined(__NAG)
INTEGER :: iargc
! Do not define iargc as external: gfortran doesn't like it
#endif
INTEGER, EXTERNAL :: i_argc
INTEGER :: iiarg, nargs
!
nargs = iargc()
nargs = i_argc()
found = .FALSE.
input_file = ' '
!
DO iiarg = 1, ( nargs - 1 )
!
CALL getarg( iiarg, input_file )
CALL get_arg( iiarg, input_file )
!
IF ( TRIM( input_file ) == '-i' .OR. &
TRIM( input_file ) == '-in' .OR. &
TRIM( input_file ) == '-inp' .OR. &
TRIM( input_file ) == '-input' ) THEN
!
CALL getarg( ( iiarg + 1 ) , input_file )
CALL get_arg( ( iiarg + 1 ) , input_file )
found =.TRUE.
EXIT
!
@ -94,11 +104,11 @@ SUBROUTINE get_file( input_file )
!
CHARACTER (LEN=256) :: prgname
INTEGER :: nargs
INTEGER :: iargc
LOGICAL :: exst
INTEGER, EXTERNAL :: i_argc
!
nargs = iargc()
CALL getarg (0,prgname)
nargs = i_argc()
CALL get_arg (0,prgname)
!
IF ( nargs == 0 ) THEN
10 PRINT '("Input file > ",$)'
@ -110,7 +120,7 @@ SUBROUTINE get_file( input_file )
GO TO 10
END IF
ELSE IF ( nargs == 1 ) then
CALL getarg (1,input_file)
CALL get_arg (1,input_file)
ELSE
PRINT '(A,": too many arguments ",i4)', TRIM(prgname), nargs
END IF