@@ -30,7 +30,9 @@ contains
30
30
new_unittest("test_gemv${t1[0]}$${k1}$", test_gemv${t1[0]}$${k1}$), &
31
31
new_unittest("test_getri${t1[0]}$${k1}$", test_getri${t1[0]}$${k1}$), &
32
32
#: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) &
34
36
]
35
37
36
38
end subroutine collect_blas_lapack
@@ -117,6 +119,75 @@ contains
117
119
118
120
end subroutine test_idamax
119
121
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
+
120
191
end module test_blas_lapack
121
192
122
193
0 commit comments