Skip to content

Commit 347021d

Browse files
committed
edits
1 parent fa3e02c commit 347021d

12 files changed

+101
-95
lines changed

legacy/stdlib_linalg_blas_c.fypp

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2557,6 +2557,7 @@ module stdlib_linalg_blas_c
25572557
complex(sp), intent(inout) :: a
25582558
complex(sp), intent(in) :: b
25592559
complex(sp), intent(out) :: s
2560+
! =====================================================================
25602561
! Local Scalars
25612562
real(sp) :: d, f1, f2, g1, g2, h2, p, u, uu, v, vv, w
25622563
complex(sp) :: f, fs, g, gs, r, t

legacy/stdlib_linalg_blas_d.fypp

Lines changed: 14 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -840,22 +840,22 @@ module stdlib_linalg_blas_d
840840
end subroutine stdlib${ii}$_dger
841841

842842

843-
pure function stdlib${ii}$_dnrm2( n, x, incx )
843+
pure real(dp) function stdlib${ii}$_dnrm2( n, x, incx )
844844
!! DNRM2 returns the euclidean norm of a vector via the function
845845
!! name, so that
846846
!! DNRM2 := sqrt( x'*x )
847-
real(dp) :: stdlib${ii}$_dnrm2
848847
! -- reference blas level1 routine (version 3.9.1_dp) --
849848
! -- reference blas is a software package provided by univ. of tennessee, --
850849
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
851850
! march 2021
852-
! Constants
853-
real(dp), parameter :: maxn = huge(0.0_dp)
854-
! .. blue's scaling constants ..
855851
! Scalar Arguments
856-
integer(${ik}$), intent(in) :: incx, n
852+
integer(${ik}$), intent(in) :: incx, n
857853
! Array Arguments
858854
real(dp), intent(in) :: x(*)
855+
! =====================================================================
856+
! Constants
857+
real(dp), parameter :: maxn = huge(0.0_dp)
858+
! .. blue's scaling constants ..
859859
! Local Scalars
860860
integer(${ik}$) :: i, ix
861861
logical(lk) :: notbig
@@ -990,6 +990,7 @@ module stdlib_linalg_blas_d
990990
! Scalar Arguments
991991
real(dp), intent(inout) :: a, b
992992
real(dp), intent(out) :: c, s
993+
! =====================================================================
993994
! Local Scalars
994995
real(dp) :: anorm, bnorm, scl, sigma, r, z
995996
anorm = abs(a)
@@ -1049,11 +1050,9 @@ module stdlib_linalg_blas_d
10491050
real(dp), intent(inout) :: dx(*), dy(*)
10501051
! =====================================================================
10511052
! Local Scalars
1052-
real(dp) :: dflag, dh11, dh12, dh21, dh22, two, w, z, zero
1053+
real(dp) :: dflag, dh11, dh12, dh21, dh22, w, z
10531054
integer(${ik}$) :: i, kx, ky, nsteps
10541055
! Data Statements
1055-
zero = 0.0_dp
1056-
two = 2.0_dp
10571056
dflag = dparam(1)
10581057
if (n<=0 .or. (dflag+two==zero)) return
10591058
if (incx==incy.and.incx>0) then
@@ -1158,13 +1157,10 @@ module stdlib_linalg_blas_d
11581157
! =====================================================================
11591158
! Local Scalars
11601159
real(dp) :: dflag, dh11, dh12, dh21, dh22, dp1, dp2, dq1, dq2, dtemp, du, gam, gamsq, &
1161-
one, rgamsq, two, zero
1160+
rgamsq
11621161
! Intrinsic Functions
11631162
intrinsic :: abs
11641163
! Data Statements
1165-
zero = 0.0_dp
1166-
one = 1.0_dp
1167-
two = 2.0_dp
11681164
gam = 4096.0_dp
11691165
gamsq = 16777216.0_dp
11701166
rgamsq = 5.9604645e-8_dp
@@ -4411,22 +4407,22 @@ module stdlib_linalg_blas_d
44114407
end function stdlib${ii}$_dzasum
44124408

44134409

4414-
pure function stdlib${ii}$_dznrm2( n, x, incx )
4410+
pure real(dp) function stdlib${ii}$_dznrm2( n, x, incx )
44154411
!! DZNRM2 returns the euclidean norm of a vector via the function
44164412
!! name, so that
44174413
!! DZNRM2 := sqrt( x**H*x )
4418-
real(dp) :: stdlib${ii}$_dznrm2
44194414
! -- reference blas level1 routine (version 3.9.1_dp) --
44204415
! -- reference blas is a software package provided by univ. of tennessee, --
44214416
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
44224417
! march 2021
4423-
! Constants
4424-
real(dp), parameter :: maxn = huge(0.0_dp)
4425-
! .. blue's scaling constants ..
44264418
! Scalar Arguments
44274419
integer(${ik}$), intent(in) :: incx, n
44284420
! Array Arguments
44294421
complex(dp), intent(in) :: x(*)
4422+
! =====================================================================
4423+
! Constants
4424+
real(dp), parameter :: maxn = huge(0.0_dp)
4425+
! .. blue's scaling constants ..
44304426
! Local Scalars
44314427
integer(${ik}$) :: i, ix
44324428
logical(lk) :: notbig

legacy/stdlib_linalg_blas_q.fypp

Lines changed: 14 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -844,22 +844,22 @@ module stdlib_linalg_blas_${ri}$
844844
end subroutine stdlib${ii}$_${ri}$ger
845845

846846

847-
pure function stdlib${ii}$_${ri}$nrm2( n, x, incx )
847+
pure real(${rk}$) function stdlib${ii}$_${ri}$nrm2( n, x, incx )
848848
!! DNRM2: returns the euclidean norm of a vector via the function
849849
!! name, so that
850850
!! DNRM2 := sqrt( x'*x )
851-
real(${rk}$) :: stdlib${ii}$_${ri}$nrm2
852851
! -- reference blas level1 routine (version 3.9.1_${rk}$) --
853852
! -- reference blas is a software package provided by univ. of tennessee, --
854853
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
855854
! march 2021
856-
! Constants
857-
real(${rk}$), parameter :: maxn = huge(0.0_${rk}$)
858-
! .. blue's scaling constants ..
859855
! Scalar Arguments
860-
integer(${ik}$), intent(in) :: incx, n
856+
integer(${ik}$), intent(in) :: incx, n
861857
! Array Arguments
862858
real(${rk}$), intent(in) :: x(*)
859+
! =====================================================================
860+
! Constants
861+
real(${rk}$), parameter :: maxn = huge(0.0_${rk}$)
862+
! .. blue's scaling constants ..
863863
! Local Scalars
864864
integer(${ik}$) :: i, ix
865865
logical(lk) :: notbig
@@ -994,6 +994,7 @@ module stdlib_linalg_blas_${ri}$
994994
! Scalar Arguments
995995
real(${rk}$), intent(inout) :: a, b
996996
real(${rk}$), intent(out) :: c, s
997+
! =====================================================================
997998
! Local Scalars
998999
real(${rk}$) :: anorm, bnorm, scl, sigma, r, z
9991000
anorm = abs(a)
@@ -1053,11 +1054,9 @@ module stdlib_linalg_blas_${ri}$
10531054
real(${rk}$), intent(inout) :: dx(*), dy(*)
10541055
! =====================================================================
10551056
! Local Scalars
1056-
real(${rk}$) :: dflag, dh11, dh12, dh21, dh22, two, w, z, zero
1057+
real(${rk}$) :: dflag, dh11, dh12, dh21, dh22, w, z
10571058
integer(${ik}$) :: i, kx, ky, nsteps
10581059
! Data Statements
1059-
zero = 0.0_${rk}$
1060-
two = 2.0_${rk}$
10611060
dflag = dparam(1)
10621061
if (n<=0 .or. (dflag+two==zero)) return
10631062
if (incx==incy.and.incx>0) then
@@ -1162,13 +1161,10 @@ module stdlib_linalg_blas_${ri}$
11621161
! =====================================================================
11631162
! Local Scalars
11641163
real(${rk}$) :: dflag, dh11, dh12, dh21, dh22, dp1, dp2, dq1, dq2, dtemp, du, gam, gamsq, &
1165-
one, rgamsq, two, zero
1164+
rgamsq
11661165
! Intrinsic Functions
11671166
intrinsic :: abs
11681167
! Data Statements
1169-
zero = 0.0_${rk}$
1170-
one = 1.0_${rk}$
1171-
two = 2.0_${rk}$
11721168
gam = 4096.0_${rk}$
11731169
gamsq = 16777216.0_${rk}$
11741170
rgamsq = 5.9604645e-8_${rk}$
@@ -4415,22 +4411,22 @@ module stdlib_linalg_blas_${ri}$
44154411
end function stdlib${ii}$_${ri}$zasum
44164412

44174413

4418-
pure function stdlib${ii}$_${ri}$znrm2( n, x, incx )
4414+
pure real(${rk}$) function stdlib${ii}$_${ri}$znrm2( n, x, incx )
44194415
!! DZNRM2: returns the euclidean norm of a vector via the function
44204416
!! name, so that
44214417
!! DZNRM2 := sqrt( x**H*x )
4422-
real(${rk}$) :: stdlib${ii}$_${ri}$znrm2
44234418
! -- reference blas level1 routine (version 3.9.1_${rk}$) --
44244419
! -- reference blas is a software package provided by univ. of tennessee, --
44254420
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
44264421
! march 2021
4427-
! Constants
4428-
real(${rk}$), parameter :: maxn = huge(0.0_${rk}$)
4429-
! .. blue's scaling constants ..
44304422
! Scalar Arguments
44314423
integer(${ik}$), intent(in) :: incx, n
44324424
! Array Arguments
44334425
complex(${rk}$), intent(in) :: x(*)
4426+
! =====================================================================
4427+
! Constants
4428+
real(${rk}$), parameter :: maxn = huge(0.0_${rk}$)
4429+
! .. blue's scaling constants ..
44344430
! Local Scalars
44354431
integer(${ik}$) :: i, ix
44364432
logical(lk) :: notbig

legacy/stdlib_linalg_blas_s.fypp

Lines changed: 17 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -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

legacy/stdlib_linalg_blas_w.fypp

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2643,6 +2643,7 @@ module stdlib_linalg_blas_${ci}$
26432643
complex(${ck}$), intent(inout) :: a
26442644
complex(${ck}$), intent(in) :: b
26452645
complex(${ck}$), intent(out) :: s
2646+
! =====================================================================
26462647
! Local Scalars
26472648
real(${ck}$) :: d, f1, f2, g1, g2, h2, p, u, uu, v, vv, w
26482649
complex(${ck}$) :: f, fs, g, gs, r, t

legacy/stdlib_linalg_blas_z.fypp

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2635,6 +2635,7 @@ module stdlib_linalg_blas_z
26352635
complex(dp), intent(inout) :: a
26362636
complex(dp), intent(in) :: b
26372637
complex(dp), intent(out) :: s
2638+
! =====================================================================
26382639
! Local Scalars
26392640
real(dp) :: d, f1, f2, g1, g2, h2, p, u, uu, v, vv, w
26402641
complex(dp) :: f, fs, g, gs, r, t

0 commit comments

Comments
 (0)