Skip to content

Commit 6862209

Browse files
committed
add tests
1 parent 6e36e6b commit 6862209

File tree

3 files changed

+91
-4
lines changed

3 files changed

+91
-4
lines changed

Diff for: test/CMakeLists.txt

+10-1
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,15 @@ macro(ADDTEST name)
1010
WORKING_DIRECTORY ${CMAKE_CURRENT_SOURCE_DIR})
1111
endmacro(ADDTEST)
1212

13+
macro(ADDTESTPP name)
14+
add_executable(test_${name} test_${name}.F90)
15+
target_link_libraries(test_${name} "${PROJECT_NAME}" "test-drive::test-drive")
16+
add_test(NAME ${name}
17+
COMMAND $<TARGET_FILE:test_${name}> ${CMAKE_CURRENT_BINARY_DIR}
18+
WORKING_DIRECTORY ${CMAKE_CURRENT_SOURCE_DIR})
19+
endmacro(ADDTESTPP)
20+
21+
1322
add_subdirectory(array)
1423
add_subdirectory(ascii)
1524
add_subdirectory(bitsets)
@@ -30,4 +39,4 @@ add_subdirectory(system)
3039
add_subdirectory(quadrature)
3140
add_subdirectory(math)
3241
add_subdirectory(stringlist)
33-
add_subdirectory(terminal)
42+
add_subdirectory(terminal)

Diff for: test/linalg/CMakeLists.txt

+9-2
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,22 @@
11
set(
22
fppFiles
33
"test_linalg.fypp"
4-
"test_blas_lapack.fypp"
54
"test_linalg_eigenvalues.fypp"
65
"test_linalg_solve.fypp"
76
"test_linalg_lstsq.fypp"
87
"test_linalg_determinant.fypp"
98
"test_linalg_svd.fypp"
109
"test_linalg_matrix_property_checks.fypp"
1110
)
11+
12+
# Preprocessed files to contain preprocessor directives -> .F90
13+
set(
14+
cppFiles
15+
"test_blas_lapack.fypp"
16+
)
17+
1218
fypp_f90("${fyppFlags}" "${fppFiles}" outFiles)
19+
fypp_f90pp("${fyppFlags}" "${cppFiles}" outPreprocFiles)
1320

1421
ADDTEST(linalg)
1522
ADDTEST(linalg_determinant)
@@ -18,4 +25,4 @@ ADDTEST(linalg_matrix_property_checks)
1825
ADDTEST(linalg_solve)
1926
ADDTEST(linalg_lstsq)
2027
ADDTEST(linalg_svd)
21-
ADDTEST(blas_lapack)
28+
ADDTESTPP(blas_lapack)

Diff for: test/linalg/test_blas_lapack.fypp

+72-1
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,9 @@ contains
3030
new_unittest("test_gemv${t1[0]}$${k1}$", test_gemv${t1[0]}$${k1}$), &
3131
new_unittest("test_getri${t1[0]}$${k1}$", test_getri${t1[0]}$${k1}$), &
3232
#:endfor
33-
new_unittest("test_idamax", test_idamax) &
33+
new_unittest("test_idamax", test_idamax), &
34+
new_unittest("test_external_blas",external_blas_test), &
35+
new_unittest("test_external_lapack",external_lapack_test) &
3436
]
3537

3638
end subroutine collect_blas_lapack
@@ -117,6 +119,75 @@ contains
117119

118120
end subroutine test_idamax
119121

122+
!> Test availability of the external BLAS interface
123+
subroutine external_blas_test(error)
124+
!> Error handling
125+
type(error_type), allocatable, intent(out) :: error
126+
127+
#ifdef STDLIB_EXTERNAL_BLAS
128+
interface
129+
subroutine saxpy(n,sa,sx,incx,sy,incy)
130+
import sp,ilp
131+
implicit none(type,external)
132+
real(sp), intent(in) :: sa,sx(*)
133+
integer(ilp), intent(in) :: incx,incy,n
134+
real(sp), intent(inout) :: sy(*)
135+
end subroutine saxpy
136+
end interface
137+
138+
integer(ilp), parameter :: n = 5, inc=1
139+
real(sp) :: a,x(n),y(n)
140+
141+
x = 1.0_sp
142+
y = 2.0_sp
143+
a = 3.0_sp
144+
145+
call saxpy(n,a,x,inc,y,inc)
146+
call check(error, all(abs(y-5.0_sp)<sqrt(epsilon(0.0_sp))), "saxpy: check result")
147+
if (allocated(error)) return
148+
149+
#else
150+
call skip_test(error, "Not using an external BLAS")
151+
#endif
152+
153+
end subroutine external_blas_test
154+
155+
!> Test availability of the external BLAS interface
156+
subroutine external_lapack_test(error)
157+
!> Error handling
158+
type(error_type), allocatable, intent(out) :: error
159+
160+
#ifdef STDLIB_EXTERNAL_LAPACK
161+
interface
162+
subroutine dgetrf( m, n, a, lda, ipiv, info )
163+
import dp,ilp
164+
implicit none(type,external)
165+
integer(ilp), intent(out) :: info,ipiv(*)
166+
integer(ilp), intent(in) :: lda,m,n
167+
real(dp), intent(inout) :: a(lda,*)
168+
end subroutine dgetrf
169+
end interface
170+
171+
integer(ilp), parameter :: n = 3
172+
real(dp) :: A(n,n)
173+
integer(ilp) :: ipiv(n),info
174+
175+
176+
A = eye(n)
177+
info = 123
178+
179+
! Factorize matrix
180+
call dgetrf(n,n,A,n,ipiv,info)
181+
182+
call check(error, info==0, "dgetrf: check result")
183+
if (allocated(error)) return
184+
185+
#else
186+
call skip_test(error, "Not using an external LAPACK")
187+
#endif
188+
189+
end subroutine external_lapack_test
190+
120191
end module test_blas_lapack
121192

122193

0 commit comments

Comments
 (0)