Skip to content

Commit

Permalink
Merge remote-tracking branch 'upstream/main'
Browse files Browse the repository at this point in the history
  • Loading branch information
mysterymath committed Sep 10, 2024
2 parents f1df29a + d6a91b8 commit bd3728b
Show file tree
Hide file tree
Showing 554 changed files with 22,324 additions and 502 deletions.
6 changes: 3 additions & 3 deletions Fortran/gfortran/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -109,6 +109,7 @@ set(FLANG_ERRORING_FFLAGS
-fbounds-check
-fcheck-array-temporaries
-fcheck=all
-fcheck=array-temps
-fcheck=bits
-fcheck=bounds
-fcheck=do
Expand All @@ -131,6 +132,7 @@ set(FLANG_ERRORING_FFLAGS
-fcheck-bounds
-fcheck=all
-fcheck=bits
-fcheck=no-bounds
# Not sure if the -fdefault-* options will be supported. Maybe in a different
# form in which case, this will have to be modified to accommodate those.
-fdefault-real-10
Expand Down Expand Up @@ -666,9 +668,7 @@ function(gfortran_add_compile_test expect_error main others fflags ldflags)
-DALWAYS_SAVE_DIAGS=OFF
-DWORKING_DIRECTORY=${working_dir}
-DOUTPUT_FILE=${out}
-P ${COMPILE_SCRIPT_BIN}
USES_TERMINAL
COMMENT "Compiling ${main}")
-P ${COMPILE_SCRIPT_BIN})

add_custom_target(${target}
ALL
Expand Down
22 changes: 22 additions & 0 deletions Fortran/gfortran/regression/20231103-1.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
! { dg-do compile }
! { dg-options "-Ofast" }
SUBROUTINE sedi_1D(QX1d, DZ1d,kdir,BX1d,kbot,ktop)
real, dimension(:) :: QX1d,DZ1d
real, dimension(size(QX1d)) :: VVQ
logical BX_present
do k= kbot,ktop,kdir
VVQ= VV_Q0
enddo
Vxmaxx= min0
if (kdir==1) then
dzMIN = minval(DZ1d)
endif
npassx= Vxmaxx/dzMIN
DO nnn= 1,npassx
if (BX_present) then
do k= ktop,kdir
BX1d= iDZ1d0
enddo
endif
ENDDO
END
22 changes: 22 additions & 0 deletions Fortran/gfortran/regression/20231103-2.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
! { dg-do compile }
! { dg-options "-Ofast" }
subroutine shr_map_checkFldStrshr_map_mapSet_dest(ndst,max0,eps,sum0,maxval0,min0,nidnjd,renorm)
allocatable sum(:)
logical renorm
allocate(sum(ndst))
do n=1,ndst
if (sum0 > eps) then
rmax = max0
endif
enddo
if (renorm) then
rmin = maxval0
rmax = minval(sum)
do n=1,nidnjd
if (sum0 > eps) then
rmin = min0
endif
enddo
write(*,*) rmin,rmax
endif
end
131 changes: 113 additions & 18 deletions Fortran/gfortran/regression/DisabledFiles.cmake
Original file line number Diff line number Diff line change
Expand Up @@ -119,6 +119,21 @@ file(GLOB UNSUPPORTED_FILES CONFIGURE_DEPENDS
unlimited_polymorphic_14.f90
# Unsupported predefined macro: __TIMESTAMP__
wdate-time.F90

# This test checks that two arrays, initialized with random real numbers that
# are converted to integers, are not identical. It is possible, though
# unlikely for such "randomly initialized" arrays to be identical. Because of
# this inherent flakiness, this test will remain unsupported.
random_init_2.f90

# Test is not conformant as it writes to a constant argument
# Similar test, that is conformant, added to UnitTests/assign-goto
assign_5.f90

# Test is not conformant as it expects different value of cmdstat and cmdmsg
# Similar test added: UnitTests/execute_command_line
execute_command_line_1.f90
execute_command_line_3.f90
)

# These tests are skipped because they hit a 'not yet implemented' assertion
Expand Down Expand Up @@ -165,6 +180,13 @@ file(GLOB UNIMPLEMENTED_FILES CONFIGURE_DEPENDS
unlimited_polymorphic_1.f03
unlimited_polymorphic_32.f90

# unimplemented: assumed-rank variable in procedure implemented in Fortran
associate_66.f90
bind_c_optional-2.f90
intent_out_19.f90
intent_out_20.f90
shape_12.f90

# unimplemented: ASYNCHRONOUS in procedure interface
assumed_rank_13.f90
asynchronous_3.f03
Expand Down Expand Up @@ -284,11 +306,6 @@ file(GLOB UNIMPLEMENTED_FILES CONFIGURE_DEPENDS
# unimplemented: intrinsic: co_broadcast
coarray_collectives_17.f90

# Test is not conformant as it expects different value of cmdstat and cmdmsg
# Similar test added: UnitTests/execute_command_line
execute_command_line_1.f90
execute_command_line_3.f90

# unimplemented: intrinsic: failed_images
coarray_failed_images_1.f08

Expand Down Expand Up @@ -351,6 +368,7 @@ file(GLOB UNIMPLEMENTED_FILES CONFIGURE_DEPENDS
pdt_25.f03
pdt_27.f03
pdt_28.f03
pdt_36.f03
pdt_7.f03
pdt_9.f03
pr95826.f90
Expand Down Expand Up @@ -541,6 +559,7 @@ file(GLOB SKIPPED_FILES CONFIGURE_DEPENDS

# error: No intrinsic or user-defined ASSIGNMENT(=) matches operand types
# 'TYPE 1' and 'TYPE 2'
assumed_type_18.f90
dec-comparison-complex_1.f90
dec-comparison-complex_2.f90
dec-comparison-int_1.f90
Expand Down Expand Up @@ -853,6 +872,37 @@ file(GLOB SKIPPED_FILES CONFIGURE_DEPENDS
include_19.f90
include_20.f90
include_8.f90

# ----------------------------------------------------------------------------
#
# These tests require 128-bit integer support. Since we do not process
# DejaGNU directives to conditionally disable such tests, they are always
# disabled until we can conditionally run such tests
selected_logical_kind_3.f90

# error: conflicting debug info for argument
entry_6.f90

# error: Only -std=f2018 is allowed currently.
continuation_19.f

# error: Must be a constant value
pdt_33.f03

# error: 'foo_size' is not a procedure
pr103312.f90

# error: Actual argument type '__builtin_c_ptr' is not compatible with dummy
# argument type 'c_ptr'
pr108961.f90

# error: Procedure pointer 'op' with implicit interface may not be associated
# with procedure designator 'new_t' with explicit interface that cannot be
# called via an implicit interface
pr112407a.f90

# This causes a segmentation fault at run-time.
ishftc_optional_size_1.f90
)

# These tests are disabled because they fail when they are expected to pass.
Expand Down Expand Up @@ -968,24 +1018,20 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
widechar_IO_4.f90
zero_sized_1.f90
elemental_function_2.f90
do_check_1.f90
random_3.f90

# These tests fail at runtime on AArch64 (but pass on x86). Disable them
# anyway so the test-suite passes by default on AArch64.
entry_23.f
findloc_8.f90
pr99210.f90

# These tests fail on Ubuntu because of a bug in the not utility. At least
# some of these should work once the issue with not has been fixed.
#
# https://github.com/llvm/llvm-test-suite/pull/102#issuecomment-1980674221
#
do_check_1.f90
# These tests go into an infinite loop printing "Hello World"
pointer_check_1.f90
pointer_check_2.f90
pointer_check_3.f90
pointer_check_4.f90
random_3.f90
unpack_bounds_1.f90

# ---------------------------------------------------------------------------
#
Expand All @@ -1009,6 +1055,7 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
no_unit_error_1.f90
pointer_check_10.f90
pointer_remapping_6.f08
unpack_bounds_1.f90

# ---------------------------------------------------------------------------
#
Expand Down Expand Up @@ -1367,10 +1414,6 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
directive_unroll_5.f90
# Tests "!GCC$ attributes weak :: x"
weak-3.f90
# Test is not conformant as it writes to a constant argument
# Similar test, that is conformant, added to UnitTests/assign-goto
assign_5.f90


# Probable bugs
# ["a", "ab"]
Expand Down Expand Up @@ -1438,6 +1481,9 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
# error: No explicit type declared for 'arg4'
unused_artificial_dummies_1.f90

# Invalid specification expression: reference to OPTIONAL dummy argument
allocatable_length_2.f90

# Valid errors
# Valid out-of-bounds subscript errors, are warnings in gfortran
bounds_check_3.f90
Expand Down Expand Up @@ -1730,7 +1776,7 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
bounds_check_17.f90
pr48958.f90

# These files require the __truncsfbf2 intrinsic that is not available in
# These files require the __truncsfbf2 intrinsic that is not available
# before GCC 13. Alternatively, it requires compiler-rt to be built and a
# command line option provided to instruct the compiler to use it. Currently,
# we do not support either a version check on GCC or require that compiler-rt
Expand All @@ -1748,4 +1794,53 @@ file(GLOB FAILING_FILES CONFIGURE_DEPENDS
# __trampoline_setup. This is probably an unrelated issue, but as a quick fix
# for the buildbot, this is disabled.
internal_dummy_2.f08

# The causes of failure of these tests need to be investigated
PR113061.f90
allocate_with_source_29.f90
boz_8.f90
continuation_18.f90
data_initialized_4.f90
data_pointer_3.f90
date_and_time_2.f90
interface_50.f90
interface_procedure_1.f90
iso_fortran_env_9.f90
line_length_12.f90
oldstyle_5.f
pdt_34.f03
pdt_35.f03
pr104555.f90
pr112407b.f90
pr114883.f90
pr25623-2.f90
pr25623.f90
pr43984.f90
pr88624.f90
pr99139.f90
pr99368.f90
reshape_10.f90
selected_logical_kind_2.f90
submodule_3.f08
submodule_33.f08
achar_2.f90
allocate_with_source_30.f90
allocate_with_source_31.f90
backslash_1.f90
bound_11.f90
bounds_check_fail_6.f90
bounds_check_fail_7.f90
finalize_56.f90
internal_dummy_2.f08
iso_fortran_env_8.f90
optional_absent_12.f90
pr103389.f90
pr105456-nmlr.f90
pr105473.f90
pr111022.f90
pr114304.f90
zero_sized_15.f90

# Test needs to add -pedantic to show the error
pr32601.f03
)
50 changes: 50 additions & 0 deletions Fortran/gfortran/regression/PR105658.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
! { dg-do compile }
! { dg-options "-Warray-temporaries" }
! Test fix for incorrectly passing array component to unlimited polymorphic procedure

module test_PR105658_mod
implicit none
type :: foo
integer :: member1
integer :: member2
end type foo
contains
subroutine print_poly(array)
class(*), dimension(:), intent(in) :: array
select type(array)
type is (integer)
print*, array
type is (character(*))
print *, array
end select
end subroutine print_poly

subroutine do_print(thing)
type(foo), dimension(3), intent(in) :: thing
type(foo), parameter :: y(3) = [foo(1,2),foo(3,4),foo(5,6)]
integer :: i, j, uu(5,6)

call print_poly(thing%member1) ! { dg-warning "array temporary" }
call print_poly(y%member2) ! { dg-warning "array temporary" }
call print_poly(y(1::2)%member2) ! { dg-warning "array temporary" }

! The following array sections work without temporaries
uu = reshape([(((10*i+j),i=1,5),j=1,6)],[5,6])
print *, uu(2,2::2)
call print_poly (uu(2,2::2)) ! no temp needed!
print *, uu(1::2,6)
call print_poly (uu(1::2,6)) ! no temp needed!
end subroutine do_print

subroutine do_print2(thing2)
class(foo), dimension(:), intent(in) :: thing2
call print_poly (thing2% member2) ! { dg-warning "array temporary" }
end subroutine do_print2

subroutine do_print3 ()
character(3) :: c(3) = ["abc","def","ghi"]
call print_poly (c(1::2)) ! no temp needed!
call print_poly (c(1::2)(2:3)) ! { dg-warning "array temporary" }
end subroutine do_print3

end module test_PR105658_mod
12 changes: 12 additions & 0 deletions Fortran/gfortran/regression/PR113061.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
! { dg-do compile }
! { dg-options "-fno-move-loop-invariants -Oz" }
module module_foo
use iso_c_binding
contains
subroutine foo(a) bind(c)
type(c_ptr) a(..)
select rank(a)
end select
call bar
end
end
2 changes: 1 addition & 1 deletion Fortran/gfortran/regression/allocatable_function_1.f90
Original file line number Diff line number Diff line change
Expand Up @@ -107,4 +107,4 @@ function bar (n) result(b)
end function bar

end program alloc_fun
! { dg-final { scan-tree-dump-times "free" 10 "original" } }
! { dg-final { scan-tree-dump-times "__builtin_free " 10 "original" } }
Loading

0 comments on commit bd3728b

Please sign in to comment.