aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / whole_file_23.f90
blob3fd1051fe30c5c8ffbe0b956f938eed029e991e4
1 ! { dg-do compile }
2 !
3 ! PR fortran/40873
5 ! Failed to compile (segfault) with -fwhole-file.
6 ! Cf. PR 40873 comment 24; test case taken from
7 ! PR fortran/31867 comment 6.
10 pure integer function lensum (words, sep)
11 character (len=*), intent(in) :: words(:), sep
12 lensum = (size (words)-1) * len (sep) + sum (len_trim (words))
13 end function
15 module util_mod
16 implicit none
17 interface
18 pure integer function lensum (words, sep)
19 character (len=*), intent(in) :: words(:), sep
20 end function
21 end interface
22 contains
23 function join (words, sep) result(str)
24 ! trim and concatenate a vector of character variables,
25 ! inserting sep between them
26 character (len=*), intent(in) :: words(:), sep
27 character (len=lensum (words, sep)) :: str
28 integer :: i, nw
29 nw = size (words)
30 str = ""
31 if (nw < 1) then
32 return
33 else
34 str = words(1)
35 end if
36 do i=2,nw
37 str = trim (str) // sep // words(i)
38 end do
39 end function join
40 end module util_mod
42 program xjoin
43 use util_mod, only: join
44 implicit none
45 character (len=5) :: words(2) = (/"two ","three"/)
46 write (*,"(1x,'words = ',a)") "'"//join (words, "&")//"'"
47 end program xjoin