@@ -64,10 +64,8 @@ module stdlib_linalg
6464 !! Supported data types include `real` and `complex`.
6565 !!
6666 !!@note The solution is based on LAPACK's `*POTRF` methods.
67- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
6867 !!
6968 #:for rk,rt,ri in RC_KINDS_TYPES
70- #:if rk!="xdp"
7169 pure module function stdlib_linalg_${ri}$_cholesky_fun(a,lower,other_zeroed) result(c)
7270 !> Input matrix a[m,n]
7371 ${rt}$, intent(in) :: a(:,:)
@@ -78,7 +76,6 @@ module stdlib_linalg
7876 !> Output matrix with Cholesky factors c[n,n]
7977 ${rt}$, allocatable :: c(:,:)
8078 end function stdlib_linalg_${ri}$_cholesky_fun
81- #:endif
8279 #:endfor
8380 end interface chol
8481
@@ -102,10 +99,8 @@ module stdlib_linalg
10299 !! part of the triangular matrix should be filled with zeroes.
103100 !!
104101 !!@note The solution is based on LAPACK's `*POTRF` methods.
105- !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
106102 !!
107103 #:for rk,rt,ri in RC_KINDS_TYPES
108- #:if rk!="xdp"
109104 pure module subroutine stdlib_linalg_${ri}$_cholesky_inplace(a,lower,other_zeroed,err)
110105 !> Input matrix a[m,n]
111106 ${rt}$, intent(inout), target :: a(:,:)
@@ -129,7 +124,6 @@ module stdlib_linalg
129124 !> [optional] state return flag. On error if not requested, the code will stop
130125 type(linalg_state_type), optional, intent(out) :: err
131126 end subroutine stdlib_linalg_${ri}$_cholesky
132- #:endif
133127 #:endfor
134128 end interface cholesky
135129
0 commit comments