Skip to content

Commit 1459f2a

Browse files
tarunprabhuTarun Prabhu
andauthored
[Fortran/gfortran] Sync gfortran tests with upstream
These are synced with a9e9f772c7488 [https://gcc.gnu.org/git/?p=gcc.git;a=commit;h=a9e9f772c7488ac0c09dd92f28890bdab939771a] The static test configuration files, and denylists have been updated. A quick fix is also included that prevents ninja builds from being serialized. --------- Co-authored-by: Tarun Prabhu <[email protected]>
1 parent e93f828 commit 1459f2a

File tree

554 files changed

+22302
-485
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

554 files changed

+22302
-485
lines changed

Fortran/gfortran/CMakeLists.txt

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -109,6 +109,7 @@ set(FLANG_ERRORING_FFLAGS
109109
-fbounds-check
110110
-fcheck-array-temporaries
111111
-fcheck=all
112+
-fcheck=array-temps
112113
-fcheck=bits
113114
-fcheck=bounds
114115
-fcheck=do
@@ -131,6 +132,7 @@ set(FLANG_ERRORING_FFLAGS
131132
-fcheck-bounds
132133
-fcheck=all
133134
-fcheck=bits
135+
-fcheck=no-bounds
134136
# Not sure if the -fdefault-* options will be supported. Maybe in a different
135137
# form in which case, this will have to be modified to accommodate those.
136138
-fdefault-real-10
@@ -666,9 +668,7 @@ function(gfortran_add_compile_test expect_error main others fflags ldflags)
666668
-DALWAYS_SAVE_DIAGS=OFF
667669
-DWORKING_DIRECTORY=${working_dir}
668670
-DOUTPUT_FILE=${out}
669-
-P ${COMPILE_SCRIPT_BIN}
670-
USES_TERMINAL
671-
COMMENT "Compiling ${main}")
671+
-P ${COMPILE_SCRIPT_BIN})
672672

673673
add_custom_target(${target}
674674
ALL
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! { dg-do compile }
2+
! { dg-options "-Ofast" }
3+
SUBROUTINE sedi_1D(QX1d, DZ1d,kdir,BX1d,kbot,ktop)
4+
real, dimension(:) :: QX1d,DZ1d
5+
real, dimension(size(QX1d)) :: VVQ
6+
logical BX_present
7+
do k= kbot,ktop,kdir
8+
VVQ= VV_Q0
9+
enddo
10+
Vxmaxx= min0
11+
if (kdir==1) then
12+
dzMIN = minval(DZ1d)
13+
endif
14+
npassx= Vxmaxx/dzMIN
15+
DO nnn= 1,npassx
16+
if (BX_present) then
17+
do k= ktop,kdir
18+
BX1d= iDZ1d0
19+
enddo
20+
endif
21+
ENDDO
22+
END
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! { dg-do compile }
2+
! { dg-options "-Ofast" }
3+
subroutine shr_map_checkFldStrshr_map_mapSet_dest(ndst,max0,eps,sum0,maxval0,min0,nidnjd,renorm)
4+
allocatable sum(:)
5+
logical renorm
6+
allocate(sum(ndst))
7+
do n=1,ndst
8+
if (sum0 > eps) then
9+
rmax = max0
10+
endif
11+
enddo
12+
if (renorm) then
13+
rmin = maxval0
14+
rmax = minval(sum)
15+
do n=1,nidnjd
16+
if (sum0 > eps) then
17+
rmin = min0
18+
endif
19+
enddo
20+
write(*,*) rmin,rmax
21+
endif
22+
end

Fortran/gfortran/regression/DisabledFiles.cmake

Lines changed: 91 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -165,6 +165,13 @@ file(GLOB UNIMPLEMENTED_FILES CONFIGURE_DEPENDS
165165
unlimited_polymorphic_1.f03
166166
unlimited_polymorphic_32.f90
167167

168+
# unimplemented: assumed-rank variable in procedure implemented in Fortran
169+
associate_66.f90
170+
bind_c_optional-2.f90
171+
intent_out_19.f90
172+
intent_out_20.f90
173+
shape_12.f90
174+
168175
# unimplemented: ASYNCHRONOUS in procedure interface
169176
assumed_rank_13.f90
170177
asynchronous_3.f03
@@ -351,6 +358,7 @@ file(GLOB UNIMPLEMENTED_FILES CONFIGURE_DEPENDS
351358
pdt_25.f03
352359
pdt_27.f03
353360
pdt_28.f03
361+
pdt_36.f03
354362
pdt_7.f03
355363
pdt_9.f03
356364
pr95826.f90
@@ -541,6 +549,7 @@ file(GLOB SKIPPED_FILES CONFIGURE_DEPENDS
541549

542550
# error: No intrinsic or user-defined ASSIGNMENT(=) matches operand types
543551
# 'TYPE 1' and 'TYPE 2'
552+
assumed_type_18.f90
544553
dec-comparison-complex_1.f90
545554
dec-comparison-complex_2.f90
546555
dec-comparison-int_1.f90
@@ -853,6 +862,37 @@ file(GLOB SKIPPED_FILES CONFIGURE_DEPENDS
853862
include_19.f90
854863
include_20.f90
855864
include_8.f90
865+
866+
# ----------------------------------------------------------------------------
867+
#
868+
# These tests require 128-bit integer support. Since we do not process
869+
# DejaGNU directives to conditionally disable such tests, they are always
870+
# disabled until we can conditionally run such tests
871+
selected_logical_kind_3.f90
872+
873+
# error: conflicting debug info for argument
874+
entry_6.f90
875+
876+
# error: Only -std=f2018 is allowed currently.
877+
continuation_19.f
878+
879+
# error: Must be a constant value
880+
pdt_33.f03
881+
882+
# error: 'foo_size' is not a procedure
883+
pr103312.f90
884+
885+
# error: Actual argument type '__builtin_c_ptr' is not compatible with dummy
886+
# argument type 'c_ptr'
887+
pr108961.f90
888+
889+
# error: Procedure pointer 'op' with implicit interface may not be associated
890+
# with procedure designator 'new_t' with explicit interface that cannot be
891+
# called via an implicit interface
892+
pr112407a.f90
893+
894+
# This causes a segmentation fault at run-time.
895+
ishftc_optional_size_1.f90
856896
)
857897

858898
# These tests are disabled because they fail when they are expected to pass.
@@ -973,6 +1013,7 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
9731013
# anyway so the test-suite passes by default on AArch64.
9741014
entry_23.f
9751015
findloc_8.f90
1016+
pr99210.f90
9761017

9771018
# These tests fail on Ubuntu because of a bug in the not utility. At least
9781019
# some of these should work once the issue with not has been fixed.
@@ -1438,6 +1479,9 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
14381479
# error: No explicit type declared for 'arg4'
14391480
unused_artificial_dummies_1.f90
14401481

1482+
# Invalid specification expression: reference to OPTIONAL dummy argument
1483+
allocatable_length_2.f90
1484+
14411485
# Valid errors
14421486
# Valid out-of-bounds subscript errors, are warnings in gfortran
14431487
bounds_check_3.f90
@@ -1730,7 +1774,7 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
17301774
bounds_check_17.f90
17311775
pr48958.f90
17321776

1733-
# These files require the __truncsfbf2 intrinsic that is not available in
1777+
# These files require the __truncsfbf2 intrinsic that is not available
17341778
# before GCC 13. Alternatively, it requires compiler-rt to be built and a
17351779
# command line option provided to instruct the compiler to use it. Currently,
17361780
# we do not support either a version check on GCC or require that compiler-rt
@@ -1751,4 +1795,50 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
17511795

17521796
# These are flaky tests, which may fail sometimes.
17531797
random_init_2.f90
1798+
1799+
# The causes of failure of these tests need to be investigated
1800+
PR113061.f90
1801+
allocate_with_source_29.f90
1802+
boz_8.f90
1803+
continuation_18.f90
1804+
data_initialized_4.f90
1805+
data_pointer_3.f90
1806+
date_and_time_2.f90
1807+
interface_50.f90
1808+
interface_procedure_1.f90
1809+
iso_fortran_env_9.f90
1810+
line_length_12.f90
1811+
oldstyle_5.f
1812+
pdt_34.f03
1813+
pdt_35.f03
1814+
pr104555.f90
1815+
pr112407b.f90
1816+
pr114883.f90
1817+
pr25623-2.f90
1818+
pr25623.f90
1819+
pr43984.f90
1820+
pr88624.f90
1821+
pr99139.f90
1822+
pr99368.f90
1823+
reshape_10.f90
1824+
selected_logical_kind_2.f90
1825+
submodule_3.f08
1826+
submodule_33.f08
1827+
achar_2.f90
1828+
allocate_with_source_30.f90
1829+
allocate_with_source_31.f90
1830+
backslash_1.f90
1831+
bound_11.f90
1832+
bounds_check_fail_6.f90
1833+
bounds_check_fail_7.f90
1834+
finalize_56.f90
1835+
internal_dummy_2.f08
1836+
iso_fortran_env_8.f90
1837+
optional_absent_12.f90
1838+
pr103389.f90
1839+
pr105456-nmlr.f90
1840+
pr105473.f90
1841+
pr111022.f90
1842+
pr114304.f90
1843+
zero_sized_15.f90
17541844
)
Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
! { dg-do compile }
2+
! { dg-options "-Warray-temporaries" }
3+
! Test fix for incorrectly passing array component to unlimited polymorphic procedure
4+
5+
module test_PR105658_mod
6+
implicit none
7+
type :: foo
8+
integer :: member1
9+
integer :: member2
10+
end type foo
11+
contains
12+
subroutine print_poly(array)
13+
class(*), dimension(:), intent(in) :: array
14+
select type(array)
15+
type is (integer)
16+
print*, array
17+
type is (character(*))
18+
print *, array
19+
end select
20+
end subroutine print_poly
21+
22+
subroutine do_print(thing)
23+
type(foo), dimension(3), intent(in) :: thing
24+
type(foo), parameter :: y(3) = [foo(1,2),foo(3,4),foo(5,6)]
25+
integer :: i, j, uu(5,6)
26+
27+
call print_poly(thing%member1) ! { dg-warning "array temporary" }
28+
call print_poly(y%member2) ! { dg-warning "array temporary" }
29+
call print_poly(y(1::2)%member2) ! { dg-warning "array temporary" }
30+
31+
! The following array sections work without temporaries
32+
uu = reshape([(((10*i+j),i=1,5),j=1,6)],[5,6])
33+
print *, uu(2,2::2)
34+
call print_poly (uu(2,2::2)) ! no temp needed!
35+
print *, uu(1::2,6)
36+
call print_poly (uu(1::2,6)) ! no temp needed!
37+
end subroutine do_print
38+
39+
subroutine do_print2(thing2)
40+
class(foo), dimension(:), intent(in) :: thing2
41+
call print_poly (thing2% member2) ! { dg-warning "array temporary" }
42+
end subroutine do_print2
43+
44+
subroutine do_print3 ()
45+
character(3) :: c(3) = ["abc","def","ghi"]
46+
call print_poly (c(1::2)) ! no temp needed!
47+
call print_poly (c(1::2)(2:3)) ! { dg-warning "array temporary" }
48+
end subroutine do_print3
49+
50+
end module test_PR105658_mod
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
! { dg-do compile }
2+
! { dg-options "-fno-move-loop-invariants -Oz" }
3+
module module_foo
4+
use iso_c_binding
5+
contains
6+
subroutine foo(a) bind(c)
7+
type(c_ptr) a(..)
8+
select rank(a)
9+
end select
10+
call bar
11+
end
12+
end

Fortran/gfortran/regression/allocatable_function_1.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -107,4 +107,4 @@ function bar (n) result(b)
107107
end function bar
108108

109109
end program alloc_fun
110-
! { dg-final { scan-tree-dump-times "free" 10 "original" } }
110+
! { dg-final { scan-tree-dump-times "__builtin_free " 10 "original" } }
Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
! { dg-do compile }
2+
! PR fortran/109500 - check F2018:8.5.3 Note 1
3+
!
4+
! The result of referencing a function whose result variable has the
5+
! ALLOCATABLE attribute is a value that does not itself have the
6+
! ALLOCATABLE attribute.
7+
8+
program main
9+
implicit none
10+
integer, allocatable :: p
11+
procedure(f), pointer :: pp
12+
pp => f
13+
p = f()
14+
print *, allocated (p)
15+
print *, is_allocated (p)
16+
print *, is_allocated (f()) ! { dg-error "is a function result" }
17+
print *, is_allocated (pp()) ! { dg-error "is a function result" }
18+
call s (p)
19+
call s (f()) ! { dg-error "is a function result" }
20+
call s (pp()) ! { dg-error "is a function result" }
21+
22+
contains
23+
subroutine s(p)
24+
integer, allocatable :: p
25+
end subroutine s
26+
27+
function f()
28+
integer, allocatable :: f
29+
allocate (f, source=42)
30+
end function
31+
32+
logical function is_allocated(p)
33+
integer, allocatable :: p
34+
is_allocated = allocated(p)
35+
end function
36+
end program
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
! { dg-do compile }
2+
! { dg-options "-Werror -Wall" }
3+
module foo
4+
contains
5+
subroutine bar
6+
character(len=:), allocatable :: s(:)
7+
call bah(s)
8+
end subroutine bar
9+
end module foo

0 commit comments

Comments
 (0)