Skip to content
Merged
Show file tree
Hide file tree
Changes from 1 commit
Commits
File filter

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Prev Previous commit
Next Next commit
edits
  • Loading branch information
jalvesz committed Dec 30, 2024
commit 8e63891d69dcc1b5eb4ccf18ceefe700b722612f
30 changes: 15 additions & 15 deletions legacy/stdlib_linalg_lapack_c.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -41273,7 +41273,7 @@ module stdlib_linalg_lapack_c
end subroutine stdlib${ii}$_clalsd


real(sp) function stdlib${ii}$_clangb( norm, n, kl, ku, ab, ldab,work )
real(sp) function stdlib${ii}$_clangb( norm, n, kl, ku, ab, ldab,work )
!! CLANGB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n band matrix A, with kl sub-diagonals and ku super-diagonals.
Expand Down Expand Up @@ -41348,7 +41348,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clangb


real(sp) function stdlib${ii}$_clange( norm, m, n, a, lda, work )
real(sp) function stdlib${ii}$_clange( norm, m, n, a, lda, work )
!! CLANGE returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex matrix A.
Expand Down Expand Up @@ -41420,7 +41420,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clange


pure real(sp) function stdlib${ii}$_clangt( norm, n, dl, d, du )
pure real(sp) function stdlib${ii}$_clangt( norm, n, dl, d, du )
!! CLANGT returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex tridiagonal matrix A.
Expand Down Expand Up @@ -41496,7 +41496,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clangt


real(sp) function stdlib${ii}$_clanhb( norm, uplo, n, k, ab, ldab,work )
real(sp) function stdlib${ii}$_clanhb( norm, uplo, n, k, ab, ldab,work )
!! CLANHB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n hermitian band matrix A, with k super-diagonals.
Expand Down Expand Up @@ -41615,7 +41615,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clanhb


real(sp) function stdlib${ii}$_clanhe( norm, uplo, n, a, lda, work )
real(sp) function stdlib${ii}$_clanhe( norm, uplo, n, a, lda, work )
!! CLANHE returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex hermitian matrix A.
Expand Down Expand Up @@ -42945,7 +42945,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clanhf


real(sp) function stdlib${ii}$_clanhp( norm, uplo, n, ap, work )
real(sp) function stdlib${ii}$_clanhp( norm, uplo, n, ap, work )
!! CLANHP returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex hermitian matrix A, supplied in packed form.
Expand Down Expand Up @@ -43073,7 +43073,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clanhp


real(sp) function stdlib${ii}$_clanhs( norm, n, a, lda, work )
real(sp) function stdlib${ii}$_clanhs( norm, n, a, lda, work )
!! CLANHS returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! Hessenberg matrix A.
Expand Down Expand Up @@ -43145,7 +43145,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clanhs


pure real(sp) function stdlib${ii}$_clanht( norm, n, d, e )
pure real(sp) function stdlib${ii}$_clanht( norm, n, d, e )
!! CLANHT returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex Hermitian tridiagonal matrix A.
Expand Down Expand Up @@ -43208,7 +43208,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clanht


real(sp) function stdlib${ii}$_clansb( norm, uplo, n, k, ab, ldab,work )
real(sp) function stdlib${ii}$_clansb( norm, uplo, n, k, ab, ldab,work )
!! CLANSB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n symmetric band matrix A, with k super-diagonals.
Expand Down Expand Up @@ -43313,7 +43313,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clansb


real(sp) function stdlib${ii}$_clansp( norm, uplo, n, ap, work )
real(sp) function stdlib${ii}$_clansp( norm, uplo, n, ap, work )
!! CLANSP returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex symmetric matrix A, supplied in packed form.
Expand Down Expand Up @@ -43446,7 +43446,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clansp


real(sp) function stdlib${ii}$_clansy( norm, uplo, n, a, lda, work )
real(sp) function stdlib${ii}$_clansy( norm, uplo, n, a, lda, work )
!! CLANSY returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! complex symmetric matrix A.
Expand Down Expand Up @@ -43542,7 +43542,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clansy


real(sp) function stdlib${ii}$_clantb( norm, uplo, diag, n, k, ab,ldab, work )
real(sp) function stdlib${ii}$_clantb( norm, uplo, diag, n, k, ab,ldab, work )
!! CLANTB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n triangular band matrix A, with ( k + 1 ) diagonals.
Expand Down Expand Up @@ -43735,7 +43735,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clantb


real(sp) function stdlib${ii}$_clantp( norm, uplo, diag, n, ap, work )
real(sp) function stdlib${ii}$_clantp( norm, uplo, diag, n, ap, work )
!! CLANTP returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! triangular matrix A, supplied in packed form.
Expand Down Expand Up @@ -43941,7 +43941,7 @@ module stdlib_linalg_lapack_c
end function stdlib${ii}$_clantp


real(sp) function stdlib${ii}$_clantr( norm, uplo, diag, m, n, a, lda,work )
real(sp) function stdlib${ii}$_clantr( norm, uplo, diag, m, n, a, lda,work )
!! CLANTR returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! trapezoidal or triangular matrix A.
Expand Down Expand Up @@ -79708,7 +79708,7 @@ module stdlib_linalg_lapack_c
alpha( * ), beta( * ), work( * )
real(sp), intent( out ) :: rwork( * )


! ================================================================
! local scalars
real(sp) :: smlnum, ulp, safmin, safmax, c1, tempr
complex(sp) :: eshift, s1, temp
Expand Down
12 changes: 3 additions & 9 deletions legacy/stdlib_linalg_lapack_d.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -2717,17 +2717,11 @@ module stdlib_linalg_lapack_d
! =====================================================================

! Local Scalars
real(dp) :: rnd, eps, sfmin, small, rmach
real(dp) :: sfmin, small, rmach
! Intrinsic Functions
intrinsic :: digits,epsilon,huge,maxexponent,minexponent,radix,tiny
! Executable Statements
! assume rounding, not chopping. always.
rnd = one
if( one==rnd ) then
eps = epsilon(zero) * 0.5
else
eps = epsilon(zero)
end if
if( stdlib_lsame( cmach, 'E' ) ) then
rmach = eps
else if( stdlib_lsame( cmach, 'S' ) ) then
Expand All @@ -2746,7 +2740,7 @@ module stdlib_linalg_lapack_d
else if( stdlib_lsame( cmach, 'N' ) ) then
rmach = digits(zero)
else if( stdlib_lsame( cmach, 'R' ) ) then
rmach = rnd
rmach = one
else if( stdlib_lsame( cmach, 'M' ) ) then
rmach = minexponent(zero)
else if( stdlib_lsame( cmach, 'U' ) ) then
Expand Down Expand Up @@ -32077,7 +32071,7 @@ module stdlib_linalg_lapack_d
integer(${ik}$), intent( in ) :: lda, ldb
real(dp), intent( in ) :: a( lda, * ), b( ldb, * ), sr1,sr2, si, beta1, beta2
real(dp), intent( out ) :: v( * )

! ================================================================
! local scalars
real(dp) :: w(2_${ik}$), safmin, safmax, scale1, scale2
safmin = stdlib${ii}$_dlamch( 'SAFE MINIMUM' )
Expand Down
10 changes: 2 additions & 8 deletions legacy/stdlib_linalg_lapack_q.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -30827,17 +30827,11 @@ module stdlib_linalg_lapack_${ri}$
! =====================================================================

! Local Scalars
real(${rk}$) :: rnd, eps, sfmin, small, rmach
real(${rk}$) :: sfmin, small, rmach
! Intrinsic Functions
intrinsic :: digits,epsilon,huge,maxexponent,minexponent,radix,tiny
! Executable Statements
! assume rounding, not chopping. always.
rnd = one
if( one==rnd ) then
eps = epsilon(zero) * 0.5
else
eps = epsilon(zero)
end if
if( stdlib_lsame( cmach, 'E' ) ) then
rmach = eps
else if( stdlib_lsame( cmach, 'S' ) ) then
Expand All @@ -30856,7 +30850,7 @@ module stdlib_linalg_lapack_${ri}$
else if( stdlib_lsame( cmach, 'N' ) ) then
rmach = digits(zero)
else if( stdlib_lsame( cmach, 'R' ) ) then
rmach = rnd
rmach = one
else if( stdlib_lsame( cmach, 'M' ) ) then
rmach = minexponent(zero)
else if( stdlib_lsame( cmach, 'U' ) ) then
Expand Down
43 changes: 19 additions & 24 deletions legacy/stdlib_linalg_lapack_s.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -2737,7 +2737,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slaisnan


pure real(sp) function stdlib${ii}$_slamch( cmach )
pure real(sp) function stdlib${ii}$_slamch( cmach )
!! SLAMCH determines single precision machine parameters.
! -- lapack auxiliary routine --
! -- lapack is a software package provided by univ. of tennessee, --
Expand All @@ -2747,17 +2747,11 @@ module stdlib_linalg_lapack_s
! =====================================================================

! Local Scalars
real(sp) :: rnd, eps, sfmin, small, rmach
real(sp) :: sfmin, small, rmach
! Intrinsic Functions
intrinsic :: digits,epsilon,huge,maxexponent,minexponent,radix,tiny
! Executable Statements
! assume rounding, not chopping. always.
rnd = one
if( one==rnd ) then
eps = epsilon(zero) * 0.5
else
eps = epsilon(zero)
end if
if( stdlib_lsame( cmach, 'E' ) ) then
rmach = eps
else if( stdlib_lsame( cmach, 'S' ) ) then
Expand All @@ -2776,7 +2770,7 @@ module stdlib_linalg_lapack_s
else if( stdlib_lsame( cmach, 'N' ) ) then
rmach = digits(zero)
else if( stdlib_lsame( cmach, 'R' ) ) then
rmach = rnd
rmach = one
else if( stdlib_lsame( cmach, 'M' ) ) then
rmach = minexponent(zero)
else if( stdlib_lsame( cmach, 'U' ) ) then
Expand All @@ -2793,7 +2787,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slamch


pure real(sp) function stdlib${ii}$_slamc3( a, b )
pure real(sp) function stdlib${ii}$_slamc3( a, b )
! -- lapack auxiliary routine --
! univ. of tennessee, univ. of california berkeley and nag ltd..
! Scalar Arguments
Expand Down Expand Up @@ -3135,7 +3129,7 @@ module stdlib_linalg_lapack_s
end subroutine stdlib${ii}$_slapmt


pure real(sp) function stdlib${ii}$_slapy3( x, y, z )
pure real(sp) function stdlib${ii}$_slapy3( x, y, z )
!! SLAPY3 returns sqrt(x**2+y**2+z**2), taking care not to cause
!! unnecessary overflow and unnecessary underflow.
! -- lapack auxiliary routine --
Expand Down Expand Up @@ -29907,7 +29901,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slaneg


real(sp) function stdlib${ii}$_slangb( norm, n, kl, ku, ab, ldab,work )
real(sp) function stdlib${ii}$_slangb( norm, n, kl, ku, ab, ldab,work )
!! SLANGB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n band matrix A, with kl sub-diagonals and ku super-diagonals.
Expand Down Expand Up @@ -29982,7 +29976,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slangb


real(sp) function stdlib${ii}$_slange( norm, m, n, a, lda, work )
real(sp) function stdlib${ii}$_slange( norm, m, n, a, lda, work )
!! SLANGE returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! real matrix A.
Expand Down Expand Up @@ -30054,7 +30048,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slange


pure real(sp) function stdlib${ii}$_slangt( norm, n, dl, d, du )
pure real(sp) function stdlib${ii}$_slangt( norm, n, dl, d, du )
!! SLANGT returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! real tridiagonal matrix A.
Expand Down Expand Up @@ -30130,7 +30124,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slangt


real(sp) function stdlib${ii}$_slanhs( norm, n, a, lda, work )
real(sp) function stdlib${ii}$_slanhs( norm, n, a, lda, work )
!! SLANHS returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! Hessenberg matrix A.
Expand Down Expand Up @@ -30202,7 +30196,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slanhs


real(sp) function stdlib${ii}$_slansb( norm, uplo, n, k, ab, ldab,work )
real(sp) function stdlib${ii}$_slansb( norm, uplo, n, k, ab, ldab,work )
!! SLANSB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n symmetric band matrix A, with k super-diagonals.
Expand Down Expand Up @@ -31011,7 +31005,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slansf


real(sp) function stdlib${ii}$_slansp( norm, uplo, n, ap, work )
real(sp) function stdlib${ii}$_slansp( norm, uplo, n, ap, work )
!! SLANSP returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! real symmetric matrix A, supplied in packed form.
Expand Down Expand Up @@ -31135,7 +31129,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slansp


pure real(sp) function stdlib${ii}$_slanst( norm, n, d, e )
pure real(sp) function stdlib${ii}$_slanst( norm, n, d, e )
!! SLANST returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! real symmetric tridiagonal matrix A.
Expand Down Expand Up @@ -31197,7 +31191,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slanst


real(sp) function stdlib${ii}$_slansy( norm, uplo, n, a, lda, work )
real(sp) function stdlib${ii}$_slansy( norm, uplo, n, a, lda, work )
!! SLANSY returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! real symmetric matrix A.
Expand Down Expand Up @@ -31293,7 +31287,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slansy


real(sp) function stdlib${ii}$_slantb( norm, uplo, diag, n, k, ab,ldab, work )
real(sp) function stdlib${ii}$_slantb( norm, uplo, diag, n, k, ab,ldab, work )
!! SLANTB returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of an
!! n by n triangular band matrix A, with ( k + 1 ) diagonals.
Expand Down Expand Up @@ -31486,7 +31480,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slantb


real(sp) function stdlib${ii}$_slantp( norm, uplo, diag, n, ap, work )
real(sp) function stdlib${ii}$_slantp( norm, uplo, diag, n, ap, work )
!! SLANTP returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! triangular matrix A, supplied in packed form.
Expand Down Expand Up @@ -31692,7 +31686,7 @@ module stdlib_linalg_lapack_s
end function stdlib${ii}$_slantp


real(sp) function stdlib${ii}$_slantr( norm, uplo, diag, m, n, a, lda,work )
real(sp) function stdlib${ii}$_slantr( norm, uplo, diag, m, n, a, lda,work )
!! SLANTR returns the value of the one norm, or the Frobenius norm, or
!! the infinity norm, or the element of largest absolute value of a
!! trapezoidal or triangular matrix A.
Expand Down Expand Up @@ -31972,7 +31966,7 @@ module stdlib_linalg_lapack_s
end subroutine stdlib${ii}$_slaorhr_col_getrfnp


pure real(sp) function stdlib${ii}$_slapy2( x, y )
pure real(sp) function stdlib${ii}$_slapy2( x, y )
!! SLAPY2 returns sqrt(x**2+y**2), taking care not to cause unnecessary
!! overflow and unnecessary underflow.
! -- lapack auxiliary routine --
Expand Down Expand Up @@ -81042,7 +81036,7 @@ module stdlib_linalg_lapack_s
integer(${ik}$), intent( out ) :: info
real(sp), intent( inout ) :: a( lda, * ), b( ldb, * ), q( ldq, * ),z( ldz, * ), alphar(&
* ), alphai( * ), beta( * ), work( * )

! ================================================================
! local scalars
real(sp) :: smlnum, ulp, eshift, safmin, safmax, c1, s1, temp, swap
integer(${ik}$) :: istart, istop, iiter, maxit, istart2, k, ld, nshifts, nblock, nw, nmin,&
Expand Down Expand Up @@ -81392,6 +81386,7 @@ module stdlib_linalg_lapack_s
real(sp), intent(inout) :: qc(ldqc,*), zc(ldzc,*)
real(sp), intent(out) :: work(*)

! ================================================================
! local scalars
logical(lk) :: bulge
integer(${ik}$) :: jw, kwtop, kwbot, istopm, istartm, k, k2, stgexc_info, ifst, ilst, &
Expand Down
2 changes: 1 addition & 1 deletion legacy/stdlib_linalg_lapack_w.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -47990,7 +47990,7 @@ module stdlib_linalg_lapack_${ci}$
integer(${ik}$), intent( in ) :: k, lda, ldb, ldq, ldz, istartm, istopm,nq, nz, qstart, &
zstart, ihi
complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*), q(ldq,*), z(ldz,*)

! ================================================================
! local variables
real(${ck}$) :: c
complex(${ck}$) :: s, temp
Expand Down