@@ -251,11 +251,9 @@ module stdlib_linalg
251251 !! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
252252 !!
253253 !!@note The solution is based on LAPACK's generic LU decomposition based solvers `*GESV`.
254- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
255254 !!
256255 #:for nd,ndsuf,nde in ALL_RHS
257256 #:for rk,rt,ri in RC_KINDS_TYPES
258- #:if rk!="xdp"
259257 module function stdlib_linalg_${ri}$_solve_${ndsuf}$(a,b,overwrite_a,err) result(x)
260258 !> Input matrix a[n,n]
261259 ${rt}$, intent(inout), target :: a(:,:)
@@ -276,7 +274,6 @@ module stdlib_linalg
276274 !> Result array/matrix x[n] or x[n,nrhs]
277275 ${rt}$, allocatable, target :: x${nd}$
278276 end function stdlib_linalg_${ri}$_pure_solve_${ndsuf}$
279- #:endif
280277 #:endfor
281278 #:endfor
282279 end interface solve
@@ -302,11 +299,9 @@ module stdlib_linalg
302299 !! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
303300 !!
304301 !!@note The solution is based on LAPACK's generic LU decomposition based solvers `*GESV`.
305- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
306302 !!
307303 #:for nd,ndsuf,nde in ALL_RHS
308304 #:for rk,rt,ri in RC_KINDS_TYPES
309- #:if rk!="xdp"
310305 pure module subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$(a,b,x,pivot,overwrite_a,err)
311306 !> Input matrix a[n,n]
312307 ${rt}$, intent(inout), target :: a(:,:)
@@ -321,7 +316,6 @@ module stdlib_linalg
321316 !> [optional] state return flag. On error if not requested, the code will stop
322317 type(linalg_state_type), optional, intent(out) :: err
323318 end subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$
324- #:endif
325319 #:endfor
326320 #:endfor
327321 end interface solve_lu
@@ -342,11 +336,9 @@ module stdlib_linalg
342336 !! Supported data types include `real` and `complex`.
343337 !!
344338 !!@note The solution is based on LAPACK's singular value decomposition `*GELSD` methods.
345- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
346339 !!
347340 #:for nd,ndsuf,nde in ALL_RHS
348341 #:for rk,rt,ri in RC_KINDS_TYPES
349- #:if rk!="xdp"
350342 module function stdlib_linalg_${ri}$_lstsq_${ndsuf}$(a,b,cond,overwrite_a,rank,err) result(x)
351343 !> Input matrix a[n,n]
352344 ${rt}$, intent(inout), target :: a(:,:)
@@ -363,7 +355,6 @@ module stdlib_linalg
363355 !> Result array/matrix x[n] or x[n,nrhs]
364356 ${rt}$, allocatable, target :: x${nd}$
365357 end function stdlib_linalg_${ri}$_lstsq_${ndsuf}$
366- #:endif
367358 #:endfor
368359 #:endfor
369360 end interface lstsq
@@ -385,11 +376,9 @@ module stdlib_linalg
385376 !! are provided, no internal memory allocations take place when using this interface.
386377 !!
387378 !!@note The solution is based on LAPACK's singular value decomposition `*GELSD` methods.
388- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
389379 !!
390380 #:for nd,ndsuf,nde in ALL_RHS
391381 #:for rk,rt,ri in RC_KINDS_TYPES
392- #:if rk!="xdp"
393382 module subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$(a,b,x,real_storage,int_storage,&
394383 #{if rt.startswith('c')}#cmpl_storage,#{endif}#cond,singvals,overwrite_a,rank,err)
395384 !> Input matrix a[n,n]
@@ -417,7 +406,6 @@ module stdlib_linalg
417406 !> [optional] state return flag. On error if not requested, the code will stop
418407 type(linalg_state_type), optional, intent(out) :: err
419408 end subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$
420- #:endif
421409 #:endfor
422410 #:endfor
423411 end interface solve_lstsq
@@ -438,7 +426,6 @@ module stdlib_linalg
438426 !!
439427 #:for nd,ndsuf,nde in ALL_RHS
440428 #:for rk,rt,ri in RC_KINDS_TYPES
441- #:if rk!="xdp"
442429 pure module subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$(a,b,lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#)
443430 !> Input matrix a[m,n]
444431 ${rt}$, intent(in), target :: a(:,:)
@@ -447,7 +434,6 @@ module stdlib_linalg
447434 !> Size of the working space arrays
448435 integer(ilp), intent(out) :: lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#
449436 end subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$
450- #:endif
451437 #:endfor
452438 #:endfor
453439 end interface lstsq_space
@@ -573,7 +559,6 @@ module stdlib_linalg
573559 !! It is possible to use partial storage [m,k] and [k,n], `k=min(m,n)`, choosing `full_matrices=.false.`.
574560 !!
575561 !!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
576- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
577562 !!
578563 !!### Example
579564 !!
@@ -586,7 +571,6 @@ module stdlib_linalg
586571 !!```
587572 !!
588573 #:for rk,rt,ri in RC_KINDS_TYPES
589- #:if rk!="xdp"
590574 module subroutine stdlib_linalg_svd_${ri}$(a,s,u,vt,overwrite_a,full_matrices,err)
591575 !!### Summary
592576 !! Compute singular value decomposition of a matrix \( A = U \cdot S \cdot \V^T \)
@@ -622,7 +606,6 @@ module stdlib_linalg
622606 !> [optional] state return flag. On error if not requested, the code will stop
623607 type(linalg_state_type), optional, intent(out) :: err
624608 end subroutine stdlib_linalg_svd_${ri}$
625- #:endif
626609 #:endfor
627610 end interface svd
628611
@@ -645,7 +628,6 @@ module stdlib_linalg
645628 !! singular values, with size [min(m,n)].
646629 !!
647630 !!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
648- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
649631 !!
650632 !!### Example
651633 !!
@@ -658,7 +640,6 @@ module stdlib_linalg
658640 !!```
659641 !!
660642 #:for rk,rt,ri in RC_KINDS_TYPES
661- #:if rk!="xdp"
662643 module function stdlib_linalg_svdvals_${ri}$(a,err) result(s)
663644 !!### Summary
664645 !! Compute singular values \(S \) from the singular-value decomposition of a matrix \( A = U \cdot S \cdot \V^T \).
@@ -682,7 +663,6 @@ module stdlib_linalg
682663 !> Array of singular values
683664 real(${rk}$), allocatable :: s(:)
684665 end function stdlib_linalg_svdvals_${ri}$
685- #:endif
686666 #:endfor
687667 end interface svdvals
688668
0 commit comments