Identifying Commandline Arguments

I have the following commandline options I am trying to define within my code…

dummymain 0 > dummymain.lst
dummymain 1 > dummymain.lst
dummymain > dummymain.lst

The last line are the default (the system should assume the first argument is 0, if not given) and I might type the output details connected (so, > dummymain.lst might also be typed as >dummymain.lst)

The internal code states this…

      if (command_argument_count() .EQ. 2) then
        call get_command_argument(1, temp1)
        read(temp1, *)massonly
      else
        massonly = 0
      endif

When I run this, it appears to ignore the massonly = 0, regardless.

If I do not put in an argument value, does Fortran see the output definition as an argument as well?

Oh, I should state, I set the command_argument_count() .EQ. 2 purely to see if this resolved the issue (it did not). I had originally set it to simply identify if it were greater than 0.

According the code snippet massonly is set when TWO arguments are given. For example:

dummymain 1 0 > dummymain.lst

Change the 2 to 1 in the if sentence for use only one argument.

1 Like

The redirect is not one of the command arguments.

2 Likes

Well, it looks like the replies so far highlight what the problem was and how to resolve it; but I was taking a little example program and whittling it down as an example for this thread and got hung up on
the original example failing with gfortran, but I know it works with two other compilers.

If you see the line starting with !x! when it is uncommented gfortran seems to think the CHARACTER declaration applies to all the remaining variables instead of the first one.

The other compilers treat only the first variable being type CHARACTER and the rest INTEGER and allocate all three arrays as I was intending.

Since I have not used the relatively new type declaration in an allocate all that many times, does anyone thing gfortran(1) is correct in the way it treats the “!x!” line?

Since the issue came up while starting to compose an example for this thread and the example does demonstrate how to generically read an arbitrary command line into a CHARACTER array, this issue could possibly come up for someone trying to do what the original post related too …

program demo_get_command_argument
! showing how to make an **array** to hold any argument list
implicit none
integer                      :: count, i, ival1, ios
integer,allocatable          :: istat(:), ilen(:)
character(len=:),allocatable :: arguments(:)
character(len=255)           :: message
   ! allocate the arrays with information about the command line
   call getargs()
   ! show the result -- arrays that have
   ! the strings, status returned and lengths and values
   write (*,'("ARG STAT LENGTH VALUE")')
   write (*,'(i3.3,1x,i0.5,1x,i0.6,1x,"[",a,"]")') &
   & (i,istat(i),ilen(i),arguments(i)(:ilen(i)),i=0,count)
   ! convert first value to an integer
   ival1=-9999 ! default value
   if(count.ge.1)then
      ! convert string to number
      read(arguments(1)(:ilen(1)),*,iostat=ios,iomsg=message)ival1
      if(ios.ne.0)then
         write(*,'(a)')trim(message)
         write(*,*)'could not read integer from',arguments(1)(:ilen(1))
         stop
      else
         write(*,*)'ival1=',ival1
      endif
   else
      write(*,*)'no parameter supplied'
   endif
contains
subroutine getargs()
integer   :: longest, argument_length, stat
   ! get number of arguments
   count = command_argument_count()
   write(*,'(a,i0)')'The number of arguments is ',count
   ! find longest argument
   longest=0
   do i=0,count
      call get_command_argument(number=i,length=argument_length)
      longest=max(longest,argument_length)
   enddo
   ! allocate string array big enough to hold command line argument strings
   ! and related information
   !x!allocate(character(len=longest) :: arguments(0:count),istat(0:count),ilen(0:count))
   allocate(character(len=longest) :: arguments(0:count))
   allocate(istat(0:count),ilen(0:count))
   ! read the arguments into the array
   do i=0,count
     call get_command_argument(i, arguments(i),status=istat(i),length=ilen(i))
   enddo
end subroutine getargs
end program demo_get_command_argument
1 Like

Well, that is a bit of a surprise, and I totally missed it. Looks like I need two other bug reports instead though :face_with_raised_eyebrow:. Thanks for finding that so quickly. nvfortran and ifort and ifx compiled and ran with that line with no trouble. Curious if anyone can try it with something else.

nvfortran consistently allows different types after a type-spec so that might be an extension, but interestingly, if instead of CHARACTER I try something like

allocate(integer :: ii(10),rr(10))

the Intel compiler gives a rather clear error message:

!    error #8235: If type specification appears, the type and kind type
!                 parameters of each object being allocated
!                 must be the same as type and kind type parameters of the
!                 type specification.   [RR]

so I don’t suspect an extension there.

As for typing more about the type-spec spec-ing type statement, I think I heard that before about a woodchuck chucking wood :>

I have not tried them all, but so far I found no switch on either compiler that gives a warning about the statement with a type-spec that is then following by other types. So if it IS supposed to be an extension neither compiler reports it when asked to flag non-standard usage.

For whatever it’s worth, my take is as follows.

Any processor that fails to detect and report a violation of a numbered constraint in the standard, “C934 (R927) If type-spec appears, it shall specify a type with which each allocate-object is type compatible,” as in the code below, does not conform:

   character(len=:), allocatable :: s
   integer, allocatable :: i
   allocate( character :: s, i )
end

Intel Fortran can thus be seen to have a bug:

C:\Temp>ifort /c /standard-semantics a.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

C:\Temp>

gfortran conforms:

C:\Temp>gfortran -c a.f90
a.f90:3:29:

3 |    allocate( character :: s, i )
  |                             1

Error: Type of entity at (1) is type incompatible with typespec

C:\Temp>

Might have been misunderstood. I think you have clearly made the case gfortran is producing the standard-specified behavior. I think that behavior other than this either needs to be flagged by any switch purporting to identify non-standard behavior and/or be corrected. I am submitting bug reports for ifort/ifx and nvfortran.

Note that for ifort(1) the problem looks like it may be specific to CHARACTER types (have not tried with user-defined types yet, etc… though). If the same type of thing is done with an INTEGER and REAL it produces an error

#!/bin/bash
cat >testit.F90 <<\EOF
program testit
real,allocatable :: r
integer,allocatable :: i
#ifdef A
allocate(r,i)
#endif
#ifdef B
allocate(real::r,i)
#endif
#ifdef C
allocate(integer::i,r)
#endif
end program testit
EOF
(
exec 2>&1
trap '' err
for TEST in A B C
do
(
set -x 
: TEST $TEST
ifort -D$TEST testit.F90 -warn all 
)
done
)|tee -a $0
exit


+ : TEST A
+ ifort -DA testit.F90 -warn all
+ : TEST B
+ ifort -DB testit.F90 -warn all
testit.F90(8): error #8235: If type specification appears, the type and kind type parameters of each object being allocated must be the same as type and kind type parameters of the type specification.   [I]
allocate(real::r,i)
-----------------^
compilation aborted for testit.F90 (code 1)
+ : TEST C
+ ifort -DC testit.F90 -warn all
testit.F90(11): error #8235: If type specification appears, the type and kind type parameters of each object being allocated must be the same as type and kind type parameters of the type specification.   [R]
allocate(integer::i,r)
--------------------^
compilation aborted for testit.F90 (code 1)
message:

Yes. There was an informal proposal to introduce a “select compiler” statement that was somewhat like a “select case” statement that would be required to encapsulate non-standard code into fortran, in lieu of preprocessor directives like “#ifdef -ifort_” that I liked, but I was in the minority.

Trying to create bug reports for some of the compilers actually makes me like gfortran bugzilla.
It can take a ridiculous amount of effort to just find a place to submit the reports.