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