Skip to content
Prev Previous commit
Next Next commit
linalg-qr: gcc-15 test fix
  • Loading branch information
perazz committed Jun 28, 2025
commit 47aed22898ff6d116b1e249bbb67c48acd071dda
22 changes: 21 additions & 1 deletion test/linalg/test_linalg_qr.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module test_linalg_qr
allocate(tests(0))

#:for rk,rt,ri in RC_KINDS_TYPES
tests = [tests,new_unittest("qr_random_${ri}$",test_qr_random_${ri}$)]
call add_test(tests,new_unittest("qr_random_${ri}$",test_qr_random_${ri}$))
#:endfor

end subroutine test_qr_factorization
Expand Down Expand Up @@ -110,6 +110,26 @@ module test_linalg_qr

#: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_qr

Expand Down