@@ -258,11 +258,9 @@ module stdlib_linalg
258258 !! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
259259 !!
260260 !!@note The solution is based on LAPACK's generic LU decomposition based solvers `*GESV`.
261- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
262261 !!
263262 #:for nd,ndsuf,nde in ALL_RHS
264263 #:for rk,rt,ri in RC_KINDS_TYPES
265- #:if rk!="xdp"
266264 module function stdlib_linalg_${ri}$_solve_${ndsuf}$(a,b,overwrite_a,err) result(x)
267265 !> Input matrix a[n,n]
268266 ${rt}$, intent(inout), target :: a(:,:)
@@ -283,7 +281,6 @@ module stdlib_linalg
283281 !> Result array/matrix x[n] or x[n,nrhs]
284282 ${rt}$, allocatable, target :: x${nd}$
285283 end function stdlib_linalg_${ri}$_pure_solve_${ndsuf}$
286- #:endif
287284 #:endfor
288285 #:endfor
289286 end interface solve
@@ -309,11 +306,9 @@ module stdlib_linalg
309306 !! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
310307 !!
311308 !!@note The solution is based on LAPACK's generic LU decomposition based solvers `*GESV`.
312- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
313309 !!
314310 #:for nd,ndsuf,nde in ALL_RHS
315311 #:for rk,rt,ri in RC_KINDS_TYPES
316- #:if rk!="xdp"
317312 pure module subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$(a,b,x,pivot,overwrite_a,err)
318313 !> Input matrix a[n,n]
319314 ${rt}$, intent(inout), target :: a(:,:)
@@ -328,7 +323,6 @@ module stdlib_linalg
328323 !> [optional] state return flag. On error if not requested, the code will stop
329324 type(linalg_state_type), optional, intent(out) :: err
330325 end subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$
331- #:endif
332326 #:endfor
333327 #:endfor
334328 end interface solve_lu
@@ -349,11 +343,9 @@ module stdlib_linalg
349343 !! Supported data types include `real` and `complex`.
350344 !!
351345 !!@note The solution is based on LAPACK's singular value decomposition `*GELSD` methods.
352- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
353346 !!
354347 #:for nd,ndsuf,nde in ALL_RHS
355348 #:for rk,rt,ri in RC_KINDS_TYPES
356- #:if rk!="xdp"
357349 module function stdlib_linalg_${ri}$_lstsq_${ndsuf}$(a,b,cond,overwrite_a,rank,err) result(x)
358350 !> Input matrix a[n,n]
359351 ${rt}$, intent(inout), target :: a(:,:)
@@ -370,7 +362,6 @@ module stdlib_linalg
370362 !> Result array/matrix x[n] or x[n,nrhs]
371363 ${rt}$, allocatable, target :: x${nd}$
372364 end function stdlib_linalg_${ri}$_lstsq_${ndsuf}$
373- #:endif
374365 #:endfor
375366 #:endfor
376367 end interface lstsq
@@ -392,11 +383,9 @@ module stdlib_linalg
392383 !! are provided, no internal memory allocations take place when using this interface.
393384 !!
394385 !!@note The solution is based on LAPACK's singular value decomposition `*GELSD` methods.
395- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
396386 !!
397387 #:for nd,ndsuf,nde in ALL_RHS
398388 #:for rk,rt,ri in RC_KINDS_TYPES
399- #:if rk!="xdp"
400389 module subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$(a,b,x,real_storage,int_storage,&
401390 #{if rt.startswith('c')}#cmpl_storage,#{endif}#cond,singvals,overwrite_a,rank,err)
402391 !> Input matrix a[n,n]
@@ -424,7 +413,6 @@ module stdlib_linalg
424413 !> [optional] state return flag. On error if not requested, the code will stop
425414 type(linalg_state_type), optional, intent(out) :: err
426415 end subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$
427- #:endif
428416 #:endfor
429417 #:endfor
430418 end interface solve_lstsq
@@ -445,7 +433,6 @@ module stdlib_linalg
445433 !!
446434 #:for nd,ndsuf,nde in ALL_RHS
447435 #:for rk,rt,ri in RC_KINDS_TYPES
448- #:if rk!="xdp"
449436 pure module subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$(a,b,lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#)
450437 !> Input matrix a[m,n]
451438 ${rt}$, intent(in), target :: a(:,:)
@@ -454,7 +441,6 @@ module stdlib_linalg
454441 !> Size of the working space arrays
455442 integer(ilp), intent(out) :: lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#
456443 end subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$
457- #:endif
458444 #:endfor
459445 #:endfor
460446 end interface lstsq_space
@@ -900,7 +886,6 @@ module stdlib_linalg
900886 !! It is possible to use partial storage [m,k] and [k,n], `k=min(m,n)`, choosing `full_matrices=.false.`.
901887 !!
902888 !!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
903- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
904889 !!
905890 !!### Example
906891 !!
@@ -913,7 +898,6 @@ module stdlib_linalg
913898 !!```
914899 !!
915900 #:for rk,rt,ri in RC_KINDS_TYPES
916- #:if rk!="xdp"
917901 module subroutine stdlib_linalg_svd_${ri}$(a,s,u,vt,overwrite_a,full_matrices,err)
918902 !!### Summary
919903 !! Compute singular value decomposition of a matrix \( A = U \cdot S \cdot \V^T \)
@@ -949,7 +933,6 @@ module stdlib_linalg
949933 !> [optional] state return flag. On error if not requested, the code will stop
950934 type(linalg_state_type), optional, intent(out) :: err
951935 end subroutine stdlib_linalg_svd_${ri}$
952- #:endif
953936 #:endfor
954937 end interface svd
955938
@@ -972,7 +955,6 @@ module stdlib_linalg
972955 !! singular values, with size [min(m,n)].
973956 !!
974957 !!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
975- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
976958 !!
977959 !!### Example
978960 !!
@@ -985,7 +967,6 @@ module stdlib_linalg
985967 !!```
986968 !!
987969 #:for rk,rt,ri in RC_KINDS_TYPES
988- #:if rk!="xdp"
989970 module function stdlib_linalg_svdvals_${ri}$(a,err) result(s)
990971 !!### Summary
991972 !! Compute singular values \(S \) from the singular-value decomposition of a matrix \( A = U \cdot S \cdot \V^T \).
@@ -1009,7 +990,6 @@ module stdlib_linalg
1009990 !> Array of singular values
1010991 real(${rk}$), allocatable :: s(:)
1011992 end function stdlib_linalg_svdvals_${ri}$
1012- #:endif
1013993 #:endfor
1014994 end interface svdvals
1015995
0 commit comments