Skip to content

Commit a937382

Browse files
committed
skip unsupported xdp precision
1 parent 8be6484 commit a937382

File tree

2 files changed

+9
-2
lines changed

2 files changed

+9
-2
lines changed

test/linalg/test_blas_lapack.fypp

+9-2
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,9 @@ contains
4141
!> Error handling
4242
type(error_type), allocatable, intent(out) :: error
4343

44+
#:if k1=="xdp"
45+
call skip_test(error, "Extended precision is not enabled")
46+
#:else
4447
${t1}$ :: A(3,3),x(3),y(3),ylap(3),yintr(3),alpha,beta
4548
call random_number(alpha)
4649
call random_number(beta)
@@ -54,14 +57,18 @@ contains
5457
call check(error, sum(abs(ylap - yintr)) < sptol, &
5558
"blas vs. intrinsics axpy: sum() < sptol failed")
5659
if (allocated(error)) return
57-
60+
#:endif
5861
end subroutine test_gemv${t1[0]}$${k1}$
5962

6063
! Find matrix inverse from LU decomposition
6164
subroutine test_getri${t1[0]}$${k1}$(error)
6265
!> Error handling
6366
type(error_type), allocatable, intent(out) :: error
6467

68+
#:if k1=="xdp"
69+
call skip_test(error, "Extended precision is not enabled")
70+
#:else
71+
6572
integer(ilp), parameter :: n = 3
6673
${t1}$ :: A(n,n)
6774
${t1}$,allocatable :: work(:)
@@ -89,7 +96,7 @@ contains
8996
call check(error, sum(abs(A - eye(3))) < sptol, &
9097
"lapack eye inversion: tolerance check failed")
9198
if (allocated(error)) return
92-
99+
#:endif
93100
end subroutine test_getri${t1[0]}$${k1}$
94101
#:endfor
95102

test/quadrature/.test_trapz.fypp.swp

16 KB
Binary file not shown.

0 commit comments

Comments
 (0)