Skip to content

Commit bb3f7e4

Browse files
committed
remove xdp restriction
1 parent 35efbe8 commit bb3f7e4

File tree

4 files changed

+2
-18
lines changed

4 files changed

+2
-18
lines changed

doc/specs/stdlib_linalg.md

+2-1
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,8 @@ end interface axpy
104104
Note that the 128-bit functions are only provided by `stdlib` and always point to the internal implementation.
105105
Because 128-bit precision is identified as [stdlib_kinds(module):qp], initials for 128-bit procedures were
106106
labelled as `q` (quadruple-precision reals) and `w` ("wide" or quadruple-precision complex numbers).
107-
Extended precision ([stdlib_kinds(module):xdp]) calculations are currently not supported.
107+
Extended precision ([stdlib_kinds(module):xdp]) calculations are labelled as `x` (extended-precision reals).
108+
and `y` (extended-precision complex numbers).
108109

109110
### Example
110111

src/stdlib_linalg.fypp

-9
Original file line numberDiff line numberDiff line change
@@ -567,10 +567,8 @@ module stdlib_linalg
567567
!! the state flag `err` is not provided.
568568
!!
569569
!!@note The provided functions are intended for square matrices.
570-
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
571570
!!
572571
#:for rk,rt,ri in RC_KINDS_TYPES
573-
#:if rk!="xdp"
574572
module function stdlib_linalg_inverse_${ri}$(a,err) result(inva)
575573
!> Input matrix a[n,n]
576574
${rt}$, intent(in) :: a(:,:)
@@ -579,7 +577,6 @@ module stdlib_linalg
579577
!> [optional] state return flag. On error if not requested, the code will stop
580578
type(linalg_state_type), optional, intent(out) :: err
581579
end function stdlib_linalg_inverse_${ri}$
582-
#:endif
583580
#:endfor
584581
end interface inv
585582

@@ -605,10 +602,8 @@ module stdlib_linalg
605602
!! work spaces are provided, no internal memory allocations take place when using this interface.
606603
!!
607604
!!@note The provided subroutines are intended for square matrices.
608-
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
609605
!!
610606
#:for rk,rt,ri in RC_KINDS_TYPES
611-
#:if rk!="xdp"
612607
module subroutine stdlib_linalg_invert_inplace_${ri}$(a,pivot,err)
613608
!> Input matrix a[n,n]
614609
${rt}$, intent(inout) :: a(:,:)
@@ -628,7 +623,6 @@ module stdlib_linalg
628623
!> [optional] state return flag. On error if not requested, the code will stop
629624
type(linalg_state_type), optional, intent(out) :: err
630625
end subroutine stdlib_linalg_invert_split_${ri}$
631-
#:endif
632626
#:endfor
633627
end interface invert
634628

@@ -649,17 +643,14 @@ module stdlib_linalg
649643
!! NaNs will be returned.
650644
!!
651645
!!@note The provided functions are intended for square matrices.
652-
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
653646
!!
654647
#:for rk,rt,ri in RC_KINDS_TYPES
655-
#:if rk!="xdp"
656648
module function stdlib_linalg_inverse_${ri}$_operator(a) result(inva)
657649
!> Input matrix a[n,n]
658650
${rt}$, intent(in) :: a(:,:)
659651
!> Result matrix
660652
${rt}$, allocatable :: inva(:,:)
661653
end function stdlib_linalg_inverse_${ri}$_operator
662-
#:endif
663654
#:endfor
664655
end interface operator(.inv.)
665656

src/stdlib_linalg_inverse.fypp

-2
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,6 @@ submodule (stdlib_linalg) stdlib_linalg_inverse
3333
end subroutine handle_getri_info
3434

3535
#:for rk,rt,ri in RC_KINDS_TYPES
36-
#:if rk!="xdp"
3736
! Compute the in-place square matrix inverse of a
3837
module subroutine stdlib_linalg_invert_inplace_${ri}$(a,pivot,err)
3938
!> Input matrix a[n,n]. On return, A is destroyed and replaced by the inverse
@@ -175,7 +174,6 @@ submodule (stdlib_linalg) stdlib_linalg_inverse
175174

176175
end function stdlib_linalg_inverse_${ri}$_operator
177176

178-
#:endif
179177
#:endfor
180178

181179
end submodule stdlib_linalg_inverse

test/linalg/test_linalg_inverse.fypp

-6
Original file line numberDiff line numberDiff line change
@@ -22,17 +22,14 @@ module test_linalg_inverse
2222
allocate(tests(0))
2323

2424
#:for rk,rt,ri in RC_KINDS_TYPES
25-
#:if rk!="xdp"
2625
tests = [tests,new_unittest("${ri}$_eye_inverse",test_${ri}$_eye_inverse), &
2726
new_unittest("${ri}$_singular_inverse",test_${ri}$_singular_inverse), &
2827
new_unittest("${ri}$_random_spd_inverse",test_${ri}$_random_spd_inverse)]
29-
#:endif
3028
#:endfor
3129

3230
end subroutine test_inverse_matrix
3331

3432
#:for rk,rt,ri in REAL_KINDS_TYPES
35-
#:if rk!="xdp"
3633
!> Invert real identity matrix
3734
subroutine test_${ri}$_eye_inverse(error)
3835
type(error_type), allocatable, intent(out) :: error
@@ -139,12 +136,10 @@ module test_linalg_inverse
139136

140137
end subroutine test_${ri}$_random_spd_inverse
141138

142-
#:endif
143139
#:endfor
144140

145141
!> Invert complex identity matrix
146142
#:for ck,ct,ci in CMPLX_KINDS_TYPES
147-
#:if ck!="xdp"
148143
subroutine test_${ci}$_eye_inverse(error)
149144
type(error_type), allocatable, intent(out) :: error
150145

@@ -295,7 +290,6 @@ module test_linalg_inverse
295290

296291
end subroutine test_${ci}$_singular_inverse
297292

298-
#:endif
299293
#:endfor
300294

301295
end module test_linalg_inverse

0 commit comments

Comments
 (0)