@@ -2737,7 +2737,7 @@ module stdlib_linalg_lapack_s
27372737 end function stdlib${ii}$_slaisnan
27382738
27392739
2740- pure real(sp) function stdlib${ii}$_slamch( cmach )
2740+ pure real(sp) function stdlib${ii}$_slamch( cmach )
27412741 !! SLAMCH determines single precision machine parameters.
27422742 ! -- lapack auxiliary routine --
27432743 ! -- lapack is a software package provided by univ. of tennessee, --
@@ -2747,17 +2747,11 @@ module stdlib_linalg_lapack_s
27472747 ! =====================================================================
27482748
27492749 ! Local Scalars
2750- real(sp) :: rnd, eps, sfmin, small, rmach
2750+ real(sp) :: sfmin, small, rmach
27512751 ! Intrinsic Functions
27522752 intrinsic :: digits,epsilon,huge,maxexponent,minexponent,radix,tiny
27532753 ! Executable Statements
27542754 ! assume rounding, not chopping. always.
2755- rnd = one
2756- if( one==rnd ) then
2757- eps = epsilon(zero) * 0.5
2758- else
2759- eps = epsilon(zero)
2760- end if
27612755 if( stdlib_lsame( cmach, 'E' ) ) then
27622756 rmach = eps
27632757 else if( stdlib_lsame( cmach, 'S' ) ) then
@@ -2776,7 +2770,7 @@ module stdlib_linalg_lapack_s
27762770 else if( stdlib_lsame( cmach, 'N' ) ) then
27772771 rmach = digits(zero)
27782772 else if( stdlib_lsame( cmach, 'R' ) ) then
2779- rmach = rnd
2773+ rmach = one
27802774 else if( stdlib_lsame( cmach, 'M' ) ) then
27812775 rmach = minexponent(zero)
27822776 else if( stdlib_lsame( cmach, 'U' ) ) then
@@ -2793,7 +2787,7 @@ module stdlib_linalg_lapack_s
27932787 end function stdlib${ii}$_slamch
27942788
27952789
2796- pure real(sp) function stdlib${ii}$_slamc3( a, b )
2790+ pure real(sp) function stdlib${ii}$_slamc3( a, b )
27972791 ! -- lapack auxiliary routine --
27982792 ! univ. of tennessee, univ. of california berkeley and nag ltd..
27992793 ! Scalar Arguments
@@ -3135,7 +3129,7 @@ module stdlib_linalg_lapack_s
31353129 end subroutine stdlib${ii}$_slapmt
31363130
31373131
3138- pure real(sp) function stdlib${ii}$_slapy3( x, y, z )
3132+ pure real(sp) function stdlib${ii}$_slapy3( x, y, z )
31393133 !! SLAPY3 returns sqrt(x**2+y**2+z**2), taking care not to cause
31403134 !! unnecessary overflow and unnecessary underflow.
31413135 ! -- lapack auxiliary routine --
@@ -29907,7 +29901,7 @@ module stdlib_linalg_lapack_s
2990729901 end function stdlib${ii}$_slaneg
2990829902
2990929903
29910- real(sp) function stdlib${ii}$_slangb( norm, n, kl, ku, ab, ldab,work )
29904+ real(sp) function stdlib${ii}$_slangb( norm, n, kl, ku, ab, ldab,work )
2991129905 !! SLANGB returns the value of the one norm, or the Frobenius norm, or
2991229906 !! the infinity norm, or the element of largest absolute value of an
2991329907 !! n by n band matrix A, with kl sub-diagonals and ku super-diagonals.
@@ -29982,7 +29976,7 @@ module stdlib_linalg_lapack_s
2998229976 end function stdlib${ii}$_slangb
2998329977
2998429978
29985- real(sp) function stdlib${ii}$_slange( norm, m, n, a, lda, work )
29979+ real(sp) function stdlib${ii}$_slange( norm, m, n, a, lda, work )
2998629980 !! SLANGE returns the value of the one norm, or the Frobenius norm, or
2998729981 !! the infinity norm, or the element of largest absolute value of a
2998829982 !! real matrix A.
@@ -30054,7 +30048,7 @@ module stdlib_linalg_lapack_s
3005430048 end function stdlib${ii}$_slange
3005530049
3005630050
30057- pure real(sp) function stdlib${ii}$_slangt( norm, n, dl, d, du )
30051+ pure real(sp) function stdlib${ii}$_slangt( norm, n, dl, d, du )
3005830052 !! SLANGT returns the value of the one norm, or the Frobenius norm, or
3005930053 !! the infinity norm, or the element of largest absolute value of a
3006030054 !! real tridiagonal matrix A.
@@ -30130,7 +30124,7 @@ module stdlib_linalg_lapack_s
3013030124 end function stdlib${ii}$_slangt
3013130125
3013230126
30133- real(sp) function stdlib${ii}$_slanhs( norm, n, a, lda, work )
30127+ real(sp) function stdlib${ii}$_slanhs( norm, n, a, lda, work )
3013430128 !! SLANHS returns the value of the one norm, or the Frobenius norm, or
3013530129 !! the infinity norm, or the element of largest absolute value of a
3013630130 !! Hessenberg matrix A.
@@ -30202,7 +30196,7 @@ module stdlib_linalg_lapack_s
3020230196 end function stdlib${ii}$_slanhs
3020330197
3020430198
30205- real(sp) function stdlib${ii}$_slansb( norm, uplo, n, k, ab, ldab,work )
30199+ real(sp) function stdlib${ii}$_slansb( norm, uplo, n, k, ab, ldab,work )
3020630200 !! SLANSB returns the value of the one norm, or the Frobenius norm, or
3020730201 !! the infinity norm, or the element of largest absolute value of an
3020830202 !! n by n symmetric band matrix A, with k super-diagonals.
@@ -31011,7 +31005,7 @@ module stdlib_linalg_lapack_s
3101131005 end function stdlib${ii}$_slansf
3101231006
3101331007
31014- real(sp) function stdlib${ii}$_slansp( norm, uplo, n, ap, work )
31008+ real(sp) function stdlib${ii}$_slansp( norm, uplo, n, ap, work )
3101531009 !! SLANSP returns the value of the one norm, or the Frobenius norm, or
3101631010 !! the infinity norm, or the element of largest absolute value of a
3101731011 !! real symmetric matrix A, supplied in packed form.
@@ -31135,7 +31129,7 @@ module stdlib_linalg_lapack_s
3113531129 end function stdlib${ii}$_slansp
3113631130
3113731131
31138- pure real(sp) function stdlib${ii}$_slanst( norm, n, d, e )
31132+ pure real(sp) function stdlib${ii}$_slanst( norm, n, d, e )
3113931133 !! SLANST returns the value of the one norm, or the Frobenius norm, or
3114031134 !! the infinity norm, or the element of largest absolute value of a
3114131135 !! real symmetric tridiagonal matrix A.
@@ -31197,7 +31191,7 @@ module stdlib_linalg_lapack_s
3119731191 end function stdlib${ii}$_slanst
3119831192
3119931193
31200- real(sp) function stdlib${ii}$_slansy( norm, uplo, n, a, lda, work )
31194+ real(sp) function stdlib${ii}$_slansy( norm, uplo, n, a, lda, work )
3120131195 !! SLANSY returns the value of the one norm, or the Frobenius norm, or
3120231196 !! the infinity norm, or the element of largest absolute value of a
3120331197 !! real symmetric matrix A.
@@ -31293,7 +31287,7 @@ module stdlib_linalg_lapack_s
3129331287 end function stdlib${ii}$_slansy
3129431288
3129531289
31296- real(sp) function stdlib${ii}$_slantb( norm, uplo, diag, n, k, ab,ldab, work )
31290+ real(sp) function stdlib${ii}$_slantb( norm, uplo, diag, n, k, ab,ldab, work )
3129731291 !! SLANTB returns the value of the one norm, or the Frobenius norm, or
3129831292 !! the infinity norm, or the element of largest absolute value of an
3129931293 !! n by n triangular band matrix A, with ( k + 1 ) diagonals.
@@ -31486,7 +31480,7 @@ module stdlib_linalg_lapack_s
3148631480 end function stdlib${ii}$_slantb
3148731481
3148831482
31489- real(sp) function stdlib${ii}$_slantp( norm, uplo, diag, n, ap, work )
31483+ real(sp) function stdlib${ii}$_slantp( norm, uplo, diag, n, ap, work )
3149031484 !! SLANTP returns the value of the one norm, or the Frobenius norm, or
3149131485 !! the infinity norm, or the element of largest absolute value of a
3149231486 !! triangular matrix A, supplied in packed form.
@@ -31692,7 +31686,7 @@ module stdlib_linalg_lapack_s
3169231686 end function stdlib${ii}$_slantp
3169331687
3169431688
31695- real(sp) function stdlib${ii}$_slantr( norm, uplo, diag, m, n, a, lda,work )
31689+ real(sp) function stdlib${ii}$_slantr( norm, uplo, diag, m, n, a, lda,work )
3169631690 !! SLANTR returns the value of the one norm, or the Frobenius norm, or
3169731691 !! the infinity norm, or the element of largest absolute value of a
3169831692 !! trapezoidal or triangular matrix A.
@@ -31972,7 +31966,7 @@ module stdlib_linalg_lapack_s
3197231966 end subroutine stdlib${ii}$_slaorhr_col_getrfnp
3197331967
3197431968
31975- pure real(sp) function stdlib${ii}$_slapy2( x, y )
31969+ pure real(sp) function stdlib${ii}$_slapy2( x, y )
3197631970 !! SLAPY2 returns sqrt(x**2+y**2), taking care not to cause unnecessary
3197731971 !! overflow and unnecessary underflow.
3197831972 ! -- lapack auxiliary routine --
@@ -81042,7 +81036,7 @@ module stdlib_linalg_lapack_s
8104281036 integer(${ik}$), intent( out ) :: info
8104381037 real(sp), intent( inout ) :: a( lda, * ), b( ldb, * ), q( ldq, * ),z( ldz, * ), alphar(&
8104481038 * ), alphai( * ), beta( * ), work( * )
81045-
81039+ ! ================================================================
8104681040 ! local scalars
8104781041 real(sp) :: smlnum, ulp, eshift, safmin, safmax, c1, s1, temp, swap
8104881042 integer(${ik}$) :: istart, istop, iiter, maxit, istart2, k, ld, nshifts, nblock, nw, nmin,&
@@ -81392,6 +81386,7 @@ module stdlib_linalg_lapack_s
8139281386 real(sp), intent(inout) :: qc(ldqc,*), zc(ldzc,*)
8139381387 real(sp), intent(out) :: work(*)
8139481388
81389+ ! ================================================================
8139581390 ! local scalars
8139681391 logical(lk) :: bulge
8139781392 integer(${ik}$) :: jw, kwtop, kwbot, istopm, istartm, k, k2, stgexc_info, ifst, ilst, &
0 commit comments