Joining strings -- problem with gfortran?

Compiling and running the code

module util_mod
implicit none
contains
function join(words,sep) result(str)
! trim and concatenate a vector of character variables,
! inserting sep between them
character (len=*), intent(in)                                   :: words(:),sep
character (len=(size(words)-1)*len(sep) + sum(len_trim(words))) :: str
integer                                                         :: i,nw
nw  = size(words)
str = ""
if (nw < 1) then
   return
else
   str = words(1)
end if
do i=2,nw
   str = trim(str) // sep // words(i) 
end do
end function join
!
function c(x1,x2) result(vec)
! return character array containing present arguments
character (len=*)  , intent(in), optional    :: x1,x2
character (len=100)            , allocatable :: vec(:)
character (len=100)            , allocatable :: vec_(:)
integer                                      :: n
allocate (vec_(2))
if (present(x1))  vec_(1)  = x1
if (present(x2))  vec_(2)  = x2
n = count([present(x1),present(x2)])
allocate (vec(n))
if (n > 0) vec = vec_(:n)
end function c
end module util_mod

program main
use util_mod, only: join,c
implicit none
write (*,"(a)") "'" // trim(join(c("two"),sep=",")) // "'"
write (*,"(a)") "'" // trim(join(c("two","three"),sep=",")) // "'"
end program main

with g95 and Intel Fortran on Windows 10, I get the expected output,

'two'
'two,three'

but GNU Fortran (GCC) 11.0.0 20200927 (experimental) from equation.com gives

'twoNďż˝                                                                                    '
'two,threeďż˝                                                                                    three'

Gfortran 9.3.0 or 10.2.0 on Windows Subsystem for Linux gives something similar to gfortran on Windows. Is the problem with my code or gfortran?

For some reason, most likely a compiler bug, the return value from join comes back in a wrong length. That is, instead of length 9 for the second example it comes back in length 109. While the joined values sitting at the start there is some nonsense in the remaining 100 byte which trim cannot get past.
you can check this by changing your main program to

character(:), allocatable :: x
.............
x=trim(join(c("two","three"),sep=","))
write(*,*) len(x)

if you change to your join function to:

character(:), allocatable :: str
allocate(character((size(words)-1)*len(sep) +sum(len_trim(words)))::str)

it will work with gfortran as well (tested in linux 5.9.14, gfortran 10.2).
cheers

With the original:

$ gfortran essai.f90 && ./a.out
'two'
'two,three''
$ gfortran --version
GNU Fortran (Ubuntu 10.2.0-13ubuntu1) 10.2.0
Copyright (C) 2020 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

Is there a spurious quotation mark?

That’s what I found and that’s exactly the point where gfortran goes astray.

1 Like

Yes, there is two quotation marks at the end. Same thing with gfortran 9, 8, 7, 6, 5 under Linux Ubuntu.

But it’s OK with gfortran 4.8:

$ gfortran-4.8 essai.f90 && ./a.out
'two'
'two,three'

The login in this section of code seems questionable:

allocate (vec_(2))
if (present(x1))  vec_(1)  = x1
if (present(x2))  vec_(2)  = x2
n = count([present(x1),present(x2)])
allocate (vec(n))
if (n > 0) vec = vec_(:n)

Suppose x1 is not present and x2 is present, then vec_(2) has the value of x2 and vec_(1) is undefined.  But n =1  and vec = vec_(1:1), which is not conforming. (Also the allocate(vec(n) is not necessary, though not itself an error.)

I think you meant “logic”, not “login”.

The purpose of the c() function (modeled after the c function in R) is to provide an alternate syntax to

vec = [character (len=5) :: "two","three"]

I posted a short version of the function. The full version handles up to 10 arguments. It is anticipated that the user will just use positional arguments and not write something like

c(x2="foo",x3="bar")

I have a function

stats(stat_names,xvec)

where stat_names is a vector of characters and xvec is a real vector, and I want to be able to write simply

write (*,"(3f10.4)") stats(c("median","mean","sd"),x(:))

The function stats uses SELECT CASE to emulate function pointers.