Skip to content
Prev Previous commit
Next Next commit
linalg-solve: gcc-15 test fix
  • Loading branch information
perazz committed Jun 28, 2025
commit 3a53c6ba9cf51354ba9dc2675ceee3d45549f8f6
31 changes: 26 additions & 5 deletions test/linalg/test_linalg_solve.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,13 @@ module test_linalg_solve
allocate(tests(0))

#:for rk,rt,ri in REAL_KINDS_TYPES
tests = [tests,new_unittest("solve_${ri}$",test_${ri}$_solve), &
new_unittest("solve_${ri}$_multiple",test_${ri}$_solve_multiple)]
call add_test(tests,new_unittest("solve_${ri}$",test_${ri}$_solve))
call add_test(tests,new_unittest("solve_${ri}$_multiple",test_${ri}$_solve_multiple))
#:endfor

#:for ck,ct,ci in CMPLX_KINDS_TYPES
tests = [tests,new_unittest("solve_complex_${ci}$",test_${ci}$_solve), &
new_unittest("solve_2x2_complex_${ci}$",test_2x2_${ci}$_solve)]
call add_test(tests,new_unittest("solve_complex_${ci}$",test_${ci}$_solve))
call add_test(tests,new_unittest("solve_2x2_complex_${ci}$",test_2x2_${ci}$_solve))
#:endfor

end subroutine test_linear_systems
Expand Down Expand Up @@ -150,7 +150,28 @@ module test_linalg_solve

end subroutine test_2x2_${ri}$_solve
#:endfor


! gcc-15 bugfix utility
pure subroutine add_test(tests,new_test)
type(unittest_type), allocatable, intent(inout) :: tests(:)
type(unittest_type), intent(in) :: new_test

integer :: n
type(unittest_type), allocatable :: new_tests(:)

if (allocated(tests)) then
n = size(tests)
else
n = 0
end if

allocate(new_tests(n+1))
if (n>0) new_tests(1:n) = tests(1:n)
new_tests(1+n) = new_test
call move_alloc(from=new_tests,to=tests)

end subroutine add_test

end module test_linalg_solve

program test_solve
Expand Down