Skip to content

Commit 4859081

Browse files
authored
linalg: enable 80-bit extended precision for whole library, xdp (#839)
2 parents 6d9d7fd + 12a6640 commit 4859081

22 files changed

+25332
-23752
lines changed

Diff for: include/common.fypp

+13
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,19 @@
6060
#:set CMPLX_INIT = CMPLX_INIT + ["w"]
6161
#:endif
6262

63+
#! BLAS/LAPACK complex->real kind initial conversion
64+
#! Converts a BLAS/LAPACK complex kind initial to a real kind initial
65+
#!
66+
#! Args:
67+
#! ci (character): Complex kind initial in ["c","z","y","w"]
68+
#!
69+
#! Returns:
70+
#! Real kind initial in ["s","d","x","q"] or an empty string on invalid input
71+
#!
72+
#:def c2ri(cmplx)
73+
$:"s" if cmplx=="c" else "d" if cmplx=="z" else "x" if cmplx=="y" else "q" if cmplx=="w" else "ERROR"
74+
#:enddef
75+
6376
#! Complex types to be considered during templating
6477
#:set CMPLX_TYPES = ["complex({})".format(k) for k in CMPLX_KINDS]
6578

Diff for: src/stdlib_linalg.fypp

-20
Original file line numberDiff line numberDiff line change
@@ -255,11 +255,9 @@ module stdlib_linalg
255255
!! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
256256
!!
257257
!!@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``).
259258
!!
260259
#:for nd,ndsuf,nde in ALL_RHS
261260
#:for rk,rt,ri in RC_KINDS_TYPES
262-
#:if rk!="xdp"
263261
module function stdlib_linalg_${ri}$_solve_${ndsuf}$(a,b,overwrite_a,err) result(x)
264262
!> Input matrix a[n,n]
265263
${rt}$, intent(inout), target :: a(:,:)
@@ -280,7 +278,6 @@ module stdlib_linalg
280278
!> Result array/matrix x[n] or x[n,nrhs]
281279
${rt}$, allocatable, target :: x${nd}$
282280
end function stdlib_linalg_${ri}$_pure_solve_${ndsuf}$
283-
#:endif
284281
#:endfor
285282
#:endfor
286283
end interface solve
@@ -306,11 +303,9 @@ module stdlib_linalg
306303
!! or several (from a 2-d right-hand-side vector `b(:,:)`) systems.
307304
!!
308305
!!@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``).
310306
!!
311307
#:for nd,ndsuf,nde in ALL_RHS
312308
#:for rk,rt,ri in RC_KINDS_TYPES
313-
#:if rk!="xdp"
314309
pure module subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$(a,b,x,pivot,overwrite_a,err)
315310
!> Input matrix a[n,n]
316311
${rt}$, intent(inout), target :: a(:,:)
@@ -325,7 +320,6 @@ module stdlib_linalg
325320
!> [optional] state return flag. On error if not requested, the code will stop
326321
type(linalg_state_type), optional, intent(out) :: err
327322
end subroutine stdlib_linalg_${ri}$_solve_lu_${ndsuf}$
328-
#:endif
329323
#:endfor
330324
#:endfor
331325
end interface solve_lu
@@ -346,11 +340,9 @@ module stdlib_linalg
346340
!! Supported data types include `real` and `complex`.
347341
!!
348342
!!@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``).
350343
!!
351344
#:for nd,ndsuf,nde in ALL_RHS
352345
#:for rk,rt,ri in RC_KINDS_TYPES
353-
#:if rk!="xdp"
354346
module function stdlib_linalg_${ri}$_lstsq_${ndsuf}$(a,b,cond,overwrite_a,rank,err) result(x)
355347
!> Input matrix a[n,n]
356348
${rt}$, intent(inout), target :: a(:,:)
@@ -367,7 +359,6 @@ module stdlib_linalg
367359
!> Result array/matrix x[n] or x[n,nrhs]
368360
${rt}$, allocatable, target :: x${nd}$
369361
end function stdlib_linalg_${ri}$_lstsq_${ndsuf}$
370-
#:endif
371362
#:endfor
372363
#:endfor
373364
end interface lstsq
@@ -389,11 +380,9 @@ module stdlib_linalg
389380
!! are provided, no internal memory allocations take place when using this interface.
390381
!!
391382
!!@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``).
393383
!!
394384
#:for nd,ndsuf,nde in ALL_RHS
395385
#:for rk,rt,ri in RC_KINDS_TYPES
396-
#:if rk!="xdp"
397386
module subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$(a,b,x,real_storage,int_storage,&
398387
#{if rt.startswith('c')}#cmpl_storage,#{endif}#cond,singvals,overwrite_a,rank,err)
399388
!> Input matrix a[n,n]
@@ -421,7 +410,6 @@ module stdlib_linalg
421410
!> [optional] state return flag. On error if not requested, the code will stop
422411
type(linalg_state_type), optional, intent(out) :: err
423412
end subroutine stdlib_linalg_${ri}$_solve_lstsq_${ndsuf}$
424-
#:endif
425413
#:endfor
426414
#:endfor
427415
end interface solve_lstsq
@@ -442,7 +430,6 @@ module stdlib_linalg
442430
!!
443431
#:for nd,ndsuf,nde in ALL_RHS
444432
#:for rk,rt,ri in RC_KINDS_TYPES
445-
#:if rk!="xdp"
446433
pure module subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$(a,b,lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#)
447434
!> Input matrix a[m,n]
448435
${rt}$, intent(in), target :: a(:,:)
@@ -451,7 +438,6 @@ module stdlib_linalg
451438
!> Size of the working space arrays
452439
integer(ilp), intent(out) :: lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#
453440
end subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$
454-
#:endif
455441
#:endfor
456442
#:endfor
457443
end interface lstsq_space
@@ -781,7 +767,6 @@ module stdlib_linalg
781767
!! It is possible to use partial storage [m,k] and [k,n], `k=min(m,n)`, choosing `full_matrices=.false.`.
782768
!!
783769
!!@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``).
785770
!!
786771
!!### Example
787772
!!
@@ -794,7 +779,6 @@ module stdlib_linalg
794779
!!```
795780
!!
796781
#:for rk,rt,ri in RC_KINDS_TYPES
797-
#:if rk!="xdp"
798782
module subroutine stdlib_linalg_svd_${ri}$(a,s,u,vt,overwrite_a,full_matrices,err)
799783
!!### Summary
800784
!! Compute singular value decomposition of a matrix \( A = U \cdot S \cdot \V^T \)
@@ -830,7 +814,6 @@ module stdlib_linalg
830814
!> [optional] state return flag. On error if not requested, the code will stop
831815
type(linalg_state_type), optional, intent(out) :: err
832816
end subroutine stdlib_linalg_svd_${ri}$
833-
#:endif
834817
#:endfor
835818
end interface svd
836819

@@ -853,7 +836,6 @@ module stdlib_linalg
853836
!! singular values, with size [min(m,n)].
854837
!!
855838
!!@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``).
857839
!!
858840
!!### Example
859841
!!
@@ -866,7 +848,6 @@ module stdlib_linalg
866848
!!```
867849
!!
868850
#:for rk,rt,ri in RC_KINDS_TYPES
869-
#:if rk!="xdp"
870851
module function stdlib_linalg_svdvals_${ri}$(a,err) result(s)
871852
!!### Summary
872853
!! 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
890871
!> Array of singular values
891872
real(${rk}$), allocatable :: s(:)
892873
end function stdlib_linalg_svdvals_${ri}$
893-
#:endif
894874
#:endfor
895875
end interface svdvals
896876

0 commit comments

Comments
 (0)