@@ -478,9 +478,6 @@ module stdlib_linalg_lapack_d
478478 public :: stdlib_dtrttp
479479 public :: stdlib_dtzrzf
480480 public :: stdlib_dzsum1
481- #:if WITH_QP
482- public :: stdlib_dlag2q
483- #:endif
484481
485482 ! 64-bit real constants
486483 real(dp), parameter, private :: negone = -1.00_dp
@@ -24146,38 +24143,6 @@ module stdlib_linalg_lapack_d
2414624143 return
2414724144 end function stdlib_dzsum1
2414824145
24149- #:if WITH_QP
24150-
24151- pure subroutine stdlib_dlag2q( m, n, sa, ldsa, a, lda, info )
24152- !! DLAG2Q converts a SINGLE PRECISION matrix, SA, to a DOUBLE
24153- !! PRECISION matrix, A.
24154- !! Note that while it is possible to overflow while converting
24155- !! from double to single, it is not possible to overflow when
24156- !! converting from single to double.
24157- !! This is an auxiliary routine so there is no argument checking.
24158- ! -- lapack auxiliary routine --
24159- ! -- lapack is a software package provided by univ. of tennessee, --
24160- ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
24161- ! Scalar Arguments
24162- integer(ilp), intent(out) :: info
24163- integer(ilp), intent(in) :: lda, ldsa, m, n
24164- ! Array Arguments
24165- real(dp), intent(in) :: sa(ldsa,*)
24166- real(qp), intent(out) :: a(lda,*)
24167- ! =====================================================================
24168- ! Local Scalars
24169- integer(ilp) :: i, j
24170- ! Executable Statements
24171- info = 0
24172- do j = 1, n
24173- do i = 1, m
24174- a( i, j ) = sa( i, j )
24175- end do
24176- end do
24177- return
24178- end subroutine stdlib_dlag2q
24179- #:endif
24180-
2418124146 pure subroutine stdlib_dbbcsd( jobu1, jobu2, jobv1t, jobv2t, trans, m, p, q,theta, phi, u1, &
2418224147 !! DBBCSD computes the CS decomposition of an orthogonal matrix in
2418324148 !! bidiagonal-block form,
0 commit comments