Skip to content

Commit

Permalink
lift xdp restriction
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Jul 6, 2024
1 parent 8d20929 commit a91103a
Show file tree
Hide file tree
Showing 3 changed files with 0 additions and 12 deletions.
6 changes: 0 additions & 6 deletions src/stdlib_linalg.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -64,10 +64,8 @@ module stdlib_linalg
!! Supported data types include `real` and `complex`.
!!
!!@note The solution is based on LAPACK's `*POTRF` methods.
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
!!
#:for rk,rt,ri in RC_KINDS_TYPES
#:if rk!="xdp"
pure module function stdlib_linalg_${ri}$_cholesky_fun(a,lower,other_zeroed) result(c)
!> Input matrix a[m,n]
${rt}$, intent(in) :: a(:,:)
Expand All @@ -78,7 +76,6 @@ module stdlib_linalg
!> Output matrix with Cholesky factors c[n,n]
${rt}$, allocatable :: c(:,:)
end function stdlib_linalg_${ri}$_cholesky_fun
#:endif
#:endfor
end interface chol
Expand All @@ -102,10 +99,8 @@ module stdlib_linalg
!! part of the triangular matrix should be filled with zeroes.
!!
!!@note The solution is based on LAPACK's `*POTRF` methods.
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
!!
#:for rk,rt,ri in RC_KINDS_TYPES
#:if rk!="xdp"
pure module subroutine stdlib_linalg_${ri}$_cholesky_inplace(a,lower,other_zeroed,err)
!> Input matrix a[m,n]
${rt}$, intent(inout), target :: a(:,:)
Expand All @@ -129,7 +124,6 @@ module stdlib_linalg
!> [optional] state return flag. On error if not requested, the code will stop
type(linalg_state_type), optional, intent(out) :: err
end subroutine stdlib_linalg_${ri}$_cholesky
#:endif
#:endfor
end interface cholesky

Expand Down
2 changes: 0 additions & 2 deletions src/stdlib_linalg_cholesky.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ submodule (stdlib_linalg) stdlib_linalg_cholesky
end subroutine handle_potrf_info

#:for rk,rt,ri in RC_KINDS_TYPES
#:if rk!="xdp"

! Compute the Cholesky factorization of a symmetric / Hermitian matrix, A = L*L^T = U^T*U.
! The factorization is returned in-place, overwriting matrix A
Expand Down Expand Up @@ -174,7 +173,6 @@ submodule (stdlib_linalg) stdlib_linalg_cholesky

end function stdlib_linalg_${ri}$_cholesky_fun

#:endif
#:endfor

end submodule stdlib_linalg_cholesky
4 changes: 0 additions & 4 deletions test/linalg/test_linalg_cholesky.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -22,16 +22,13 @@ module test_linalg_cholesky
allocate(tests(0))

#:for rk,rt,ri in RC_KINDS_TYPES
#:if rk!="xdp"
tests = [tests,new_unittest("least_cholesky_${ri}$",test_cholesky_${ri}$)]
#:endif
#:endfor

end subroutine test_cholesky_factorization

!> Cholesky factorization of a random matrix
#:for rk,rt,ri in RC_KINDS_TYPES
#:if rk!="xdp"
subroutine test_cholesky_${ri}$(error)
type(error_type), allocatable, intent(out) :: error

Expand Down Expand Up @@ -67,7 +64,6 @@ module test_linalg_cholesky

end subroutine test_cholesky_${ri}$

#:endif
#:endfor


Expand Down

0 comments on commit a91103a

Please sign in to comment.