@@ -225,22 +225,22 @@ module stdlib_linalg_blas_s
225225 end function stdlib${ii}$_scasum
226226
227227
228- pure function stdlib${ii}$_scnrm2( n, x, incx )
228+ pure real(sp) function stdlib${ii}$_scnrm2( n, x, incx )
229229 !! SCNRM2 returns the euclidean norm of a vector via the function
230230 !! name, so that
231231 !! SCNRM2 := sqrt( x**H*x )
232- real(sp) :: stdlib${ii}$_scnrm2
233232 ! -- reference blas level1 routine (version 3.9.1_sp) --
234233 ! -- reference blas is a software package provided by univ. of tennessee, --
235234 ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
236235 ! march 2021
237- ! Constants
238- real(sp), parameter :: maxn = huge(0.0_sp)
239- ! .. blue's scaling constants ..
240236 ! Scalar Arguments
241- integer(${ik}$), intent(in) :: incx, n
237+ integer(${ik}$), intent(in) :: incx, n
242238 ! Array Arguments
243239 complex(sp), intent(in) :: x(*)
240+ ! =====================================================================
241+ ! Constants
242+ real(sp), parameter :: maxn = huge(0.0_sp)
243+ ! .. blue's scaling constants ..
244244 ! Local Scalars
245245 integer(${ik}$) :: i, ix
246246 logical(lk) :: notbig
@@ -445,6 +445,7 @@ module stdlib_linalg_blas_s
445445 integer(${ik}$), intent(in) :: incx, incy, n
446446 ! Array Arguments
447447 real(sp), intent(in) :: sx(*), sy(*)
448+ ! =====================================================================
448449 ! Local Scalars
449450 real(dp) :: dsdot
450451 integer(${ik}$) :: i, kx, ky, ns
@@ -1019,22 +1020,22 @@ module stdlib_linalg_blas_s
10191020 end subroutine stdlib${ii}$_sger
10201021
10211022
1022- pure function stdlib${ii}$_snrm2( n, x, incx )
1023+ pure real(sp) function stdlib${ii}$_snrm2( n, x, incx )
10231024 !! SNRM2 returns the euclidean norm of a vector via the function
10241025 !! name, so that
10251026 !! SNRM2 := sqrt( x'*x ).
1026- real(sp) :: stdlib${ii}$_snrm2
10271027 ! -- reference blas level1 routine (version 3.9.1_sp) --
10281028 ! -- reference blas is a software package provided by univ. of tennessee, --
10291029 ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
10301030 ! march 2021
1031- ! Constants
1032- real(sp), parameter :: maxn = huge(0.0_sp)
1033- ! .. blue's scaling constants ..
10341031 ! Scalar Arguments
1035- integer(${ik}$), intent(in) :: incx, n
1032+ integer(${ik}$), intent(in) :: incx, n
10361033 ! Array Arguments
10371034 real(sp), intent(in) :: x(*)
1035+ ! =====================================================================
1036+ ! Constants
1037+ real(sp), parameter :: maxn = huge(0.0_sp)
1038+ ! .. blue's scaling constants ..
10381039 ! Local Scalars
10391040 integer(${ik}$) :: i, ix
10401041 logical(lk) :: notbig
@@ -1170,6 +1171,7 @@ module stdlib_linalg_blas_s
11701171 ! Scalar Arguments
11711172 real(sp), intent(inout) :: a, b
11721173 real(sp), intent(out) :: c, s
1174+ ! =====================================================================
11731175 ! Local Scalars
11741176 real(sp) :: anorm, bnorm, scl, sigma, r, z
11751177 anorm = abs(a)
@@ -1229,11 +1231,9 @@ module stdlib_linalg_blas_s
12291231 real(sp), intent(inout) :: sx(*), sy(*)
12301232 ! =====================================================================
12311233 ! Local Scalars
1232- real(sp) :: sflag, sh11, sh12, sh21, sh22, two, w, z, zero
1234+ real(sp) :: sflag, sh11, sh12, sh21, sh22, w, z
12331235 integer(${ik}$) :: i, kx, ky, nsteps
12341236 ! Data Statements
1235- zero = 0.0_sp
1236- two = 2.0_sp
12371237 sflag = sparam(1)
12381238 if (n<=0 .or. (sflag+two==zero)) return
12391239 if (incx==incy.and.incx>0) then
@@ -1337,14 +1337,11 @@ module stdlib_linalg_blas_s
13371337 real(sp), intent(out) :: sparam(5)
13381338 ! =====================================================================
13391339 ! Local Scalars
1340- real(sp) :: gam, gamsq, one, rgamsq, sflag, sh11, sh12, sh21, sh22, sp1, sp2, sq1, sq2,&
1341- stemp, su, two, zero
1340+ real(sp) :: gam, gamsq, rgamsq, sflag, sh11, sh12, sh21, sh22, sp1, sp2, sq1, sq2,&
1341+ stemp, su
13421342 ! Intrinsic Functions
13431343 intrinsic :: abs
13441344 ! Data Statements
1345- zero = 0.0_sp
1346- one = 1.0_sp
1347- two = 2.0_sp
13481345 gam = 4096.0_sp
13491346 gamsq = 1.67772e7_sp
13501347 rgamsq = 5.96046e-8_sp
0 commit comments