@@ -255,11 +255,9 @@ module stdlib_linalg
255
255
!! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
256
256
!!
257
257
!!@note The solution is based on LAPACK's generic LU decomposition based solvers `*GESV`.
258
- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
259
258
!!
260
259
#:for nd,ndsuf,nde in ALL_RHS
261
260
#:for rk,rt,ri in RC_KINDS_TYPES
262
- #:if rk!="xdp"
263
261
module function stdlib_linalg_${ri}$_solve_${ndsuf}$(a,b,overwrite_a,err) result(x)
264
262
!> Input matrix a[n,n]
265
263
${rt}$, intent(inout), target :: a(:,:)
@@ -280,7 +278,6 @@ module stdlib_linalg
280
278
!> Result array/matrix x[n] or x[n,nrhs]
281
279
${rt}$, allocatable, target :: x${nd}$
282
280
end function stdlib_linalg_${ri}$_pure_solve_${ndsuf}$
283
- #:endif
284
281
#:endfor
285
282
#:endfor
286
283
end interface solve
@@ -306,11 +303,9 @@ module stdlib_linalg
306
303
!! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
307
304
!!
308
305
!!@note The solution is based on LAPACK's generic LU decomposition based solvers `*GESV`.
309
- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
310
306
!!
311
307
#:for nd,ndsuf,nde in ALL_RHS
312
308
#:for rk,rt,ri in RC_KINDS_TYPES
313
- #:if rk!="xdp"
314
309
pure module subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$(a,b,x,pivot,overwrite_a,err)
315
310
!> Input matrix a[n,n]
316
311
${rt}$, intent(inout), target :: a(:,:)
@@ -325,7 +320,6 @@ module stdlib_linalg
325
320
!> [optional] state return flag. On error if not requested, the code will stop
326
321
type(linalg_state_type), optional, intent(out) :: err
327
322
end subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$
328
- #:endif
329
323
#:endfor
330
324
#:endfor
331
325
end interface solve_lu
@@ -346,11 +340,9 @@ module stdlib_linalg
346
340
!! Supported data types include `real` and `complex`.
347
341
!!
348
342
!!@note The solution is based on LAPACK's singular value decomposition `*GELSD` methods.
349
- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
350
343
!!
351
344
#:for nd,ndsuf,nde in ALL_RHS
352
345
#:for rk,rt,ri in RC_KINDS_TYPES
353
- #:if rk!="xdp"
354
346
module function stdlib_linalg_${ri}$_lstsq_${ndsuf}$(a,b,cond,overwrite_a,rank,err) result(x)
355
347
!> Input matrix a[n,n]
356
348
${rt}$, intent(inout), target :: a(:,:)
@@ -367,7 +359,6 @@ module stdlib_linalg
367
359
!> Result array/matrix x[n] or x[n,nrhs]
368
360
${rt}$, allocatable, target :: x${nd}$
369
361
end function stdlib_linalg_${ri}$_lstsq_${ndsuf}$
370
- #:endif
371
362
#:endfor
372
363
#:endfor
373
364
end interface lstsq
@@ -389,11 +380,9 @@ module stdlib_linalg
389
380
!! are provided, no internal memory allocations take place when using this interface.
390
381
!!
391
382
!!@note The solution is based on LAPACK's singular value decomposition `*GELSD` methods.
392
- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
393
383
!!
394
384
#:for nd,ndsuf,nde in ALL_RHS
395
385
#:for rk,rt,ri in RC_KINDS_TYPES
396
- #:if rk!="xdp"
397
386
module subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$(a,b,x,real_storage,int_storage,&
398
387
#{if rt.startswith('c')}#cmpl_storage,#{endif}#cond,singvals,overwrite_a,rank,err)
399
388
!> Input matrix a[n,n]
@@ -421,7 +410,6 @@ module stdlib_linalg
421
410
!> [optional] state return flag. On error if not requested, the code will stop
422
411
type(linalg_state_type), optional, intent(out) :: err
423
412
end subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$
424
- #:endif
425
413
#:endfor
426
414
#:endfor
427
415
end interface solve_lstsq
@@ -442,7 +430,6 @@ module stdlib_linalg
442
430
!!
443
431
#:for nd,ndsuf,nde in ALL_RHS
444
432
#:for rk,rt,ri in RC_KINDS_TYPES
445
- #:if rk!="xdp"
446
433
pure module subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$(a,b,lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#)
447
434
!> Input matrix a[m,n]
448
435
${rt}$, intent(in), target :: a(:,:)
@@ -451,7 +438,6 @@ module stdlib_linalg
451
438
!> Size of the working space arrays
452
439
integer(ilp), intent(out) :: lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#
453
440
end subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$
454
- #:endif
455
441
#:endfor
456
442
#:endfor
457
443
end interface lstsq_space
@@ -781,7 +767,6 @@ module stdlib_linalg
781
767
!! It is possible to use partial storage [m,k] and [k,n], `k=min(m,n)`, choosing `full_matrices=.false.`.
782
768
!!
783
769
!!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
784
- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
785
770
!!
786
771
!!### Example
787
772
!!
@@ -794,7 +779,6 @@ module stdlib_linalg
794
779
!!```
795
780
!!
796
781
#:for rk,rt,ri in RC_KINDS_TYPES
797
- #:if rk!="xdp"
798
782
module subroutine stdlib_linalg_svd_${ri}$(a,s,u,vt,overwrite_a,full_matrices,err)
799
783
!!### Summary
800
784
!! Compute singular value decomposition of a matrix \( A = U \cdot S \cdot \V^T \)
@@ -830,7 +814,6 @@ module stdlib_linalg
830
814
!> [optional] state return flag. On error if not requested, the code will stop
831
815
type(linalg_state_type), optional, intent(out) :: err
832
816
end subroutine stdlib_linalg_svd_${ri}$
833
- #:endif
834
817
#:endfor
835
818
end interface svd
836
819
@@ -853,7 +836,6 @@ module stdlib_linalg
853
836
!! singular values, with size [min(m,n)].
854
837
!!
855
838
!!@note The solution is based on LAPACK's singular value decomposition `*GESDD` methods.
856
- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
857
839
!!
858
840
!!### Example
859
841
!!
@@ -866,7 +848,6 @@ module stdlib_linalg
866
848
!!```
867
849
!!
868
850
#:for rk,rt,ri in RC_KINDS_TYPES
869
- #:if rk!="xdp"
870
851
module function stdlib_linalg_svdvals_${ri}$(a,err) result(s)
871
852
!!### Summary
872
853
!! Compute singular values \(S \) from the singular-value decomposition of a matrix \( A = U \cdot S \cdot \V^T \).
@@ -890,7 +871,6 @@ module stdlib_linalg
890
871
!> Array of singular values
891
872
real(${rk}$), allocatable :: s(:)
892
873
end function stdlib_linalg_svdvals_${ri}$
893
- #:endif
894
874
#:endfor
895
875
end interface svdvals
896
876
0 commit comments