LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ db1nrm2()

subroutine db1nrm2 ( integer  n,
integer  incx,
double precision  thresh 
)

Definition at line 1137 of file dblat1.f.

1138* Compare NRM2 with a reference computation using combinations
1139* of the following values:
1140*
1141* 0, very small, small, ulp, 1, 1/ulp, big, very big, infinity, NaN
1142*
1143* one of these values is used to initialize x(1) and x(2:N) is
1144* filled with random values from [-1,1] scaled by another of
1145* these values.
1146*
1147* This routine is adapted from the test suite provided by
1148* Anderson E. (2017)
1149* Algorithm 978: Safe Scaling in the Level 1 BLAS
1150* ACM Trans Math Softw 44:1--28
1151* https://doi.org/10.1145/3061665
1152*
1153* .. Scalar Arguments ..
1154 INTEGER INCX, N
1155 DOUBLE PRECISION THRESH
1156*
1157* =====================================================================
1158* .. Parameters ..
1159 INTEGER NMAX, NOUT, NV
1160 parameter(nmax=20, nout=6, nv=10)
1161 DOUBLE PRECISION HALF, ONE, TWO, ZERO
1162 parameter(half=0.5d+0, one=1.0d+0, two= 2.0d+0,
1163 & zero=0.0d+0)
1164* .. External Functions ..
1165 DOUBLE PRECISION DNRM2
1166 EXTERNAL dnrm2
1167* .. Intrinsic Functions ..
1168 INTRINSIC abs, dble, max, min, sqrt
1169* .. Model parameters ..
1170 DOUBLE PRECISION BIGNUM, SAFMAX, SAFMIN, SMLNUM, ULP
1171 parameter(bignum=0.99792015476735990583d+292,
1172 & safmax=0.44942328371557897693d+308,
1173 & safmin=0.22250738585072013831d-307,
1174 & smlnum=0.10020841800044863890d-291,
1175 & ulp=0.22204460492503130808d-015)
1176* .. Local Scalars ..
1177 DOUBLE PRECISION ROGUE, SNRM, TRAT, V0, V1, WORKSSQ, Y1, Y2,
1178 & YMAX, YMIN, YNRM, ZNRM
1179 INTEGER I, IV, IW, IX
1180 LOGICAL FIRST
1181* .. Local Arrays ..
1182 DOUBLE PRECISION VALUES(NV), WORK(NMAX), X(NMAX), Z(NMAX)
1183* .. Executable Statements ..
1184 values(1) = zero
1185 values(2) = two*safmin
1186 values(3) = smlnum
1187 values(4) = ulp
1188 values(5) = one
1189 values(6) = one / ulp
1190 values(7) = bignum
1191 values(8) = safmax
1192 values(9) = dxvals(v0,2)
1193 values(10) = dxvals(v0,3)
1194 rogue = -1234.5678d+0
1195 first = .true.
1196*
1197* Check that the arrays are large enough
1198*
1199 IF (n*abs(incx).GT.nmax) THEN
1200 WRITE (nout,99) "DNRM2", nmax, incx, n, n*abs(incx)
1201 RETURN
1202 END IF
1203*
1204* Zero-sized inputs are tested in STEST1.
1205 IF (n.LE.0) THEN
1206 RETURN
1207 END IF
1208*
1209* Generate (N-1) values in (-1,1).
1210*
1211 DO i = 2, n
1212 CALL random_number(work(i))
1213 work(i) = one - two*work(i)
1214 END DO
1215*
1216* Compute the sum of squares of the random values
1217* by an unscaled algorithm.
1218*
1219 workssq = zero
1220 DO i = 2, n
1221 workssq = workssq + work(i)*work(i)
1222 END DO
1223*
1224* Construct the test vector with one known value
1225* and the rest from the random work array multiplied
1226* by a scaling factor.
1227*
1228 DO iv = 1, nv
1229 v0 = values(iv)
1230 IF (abs(v0).GT.one) THEN
1231 v0 = v0*half
1232 END IF
1233 z(1) = v0
1234 DO iw = 1, nv
1235 v1 = values(iw)
1236 IF (abs(v1).GT.one) THEN
1237 v1 = (v1*half) / sqrt(dble(n))
1238 END IF
1239 DO i = 2, n
1240 z(i) = v1*work(i)
1241 END DO
1242*
1243* Compute the expected value of the 2-norm
1244*
1245 y1 = abs(v0)
1246 IF (n.GT.1) THEN
1247 y2 = abs(v1)*sqrt(workssq)
1248 ELSE
1249 y2 = zero
1250 END IF
1251 ymin = min(y1, y2)
1252 ymax = max(y1, y2)
1253*
1254* Expected value is NaN if either is NaN. The test
1255* for YMIN == YMAX avoids further computation if both
1256* are infinity.
1257*
1258 IF ((y1.NE.y1).OR.(y2.NE.y2)) THEN
1259* Add to propagate NaN
1260 ynrm = y1 + y2
1261 ELSE IF (ymax == zero) THEN
1262 ynrm = zero
1263 ELSE IF (ymin == ymax) THEN
1264 ynrm = sqrt(two)*ymax
1265 ELSE
1266 ynrm = ymax*sqrt(one + (ymin / ymax)**2)
1267 END IF
1268*
1269* Fill the input array to DNRM2 with steps of incx
1270*
1271 DO i = 1, n
1272 x(i) = rogue
1273 END DO
1274 ix = 1
1275 IF (incx.LT.0) ix = 1 - (n-1)*incx
1276 DO i = 1, n
1277 x(ix) = z(i)
1278 ix = ix + incx
1279 END DO
1280*
1281* Call DNRM2 to compute the 2-norm
1282*
1283 snrm = dnrm2(n,x,incx)
1284*
1285* Compare SNRM and ZNRM. Roundoff error grows like O(n)
1286* in this implementation so we scale the test ratio accordingly.
1287*
1288 IF (incx.EQ.0) THEN
1289 znrm = sqrt(dble(n))*abs(x(1))
1290 ELSE
1291 znrm = ynrm
1292 END IF
1293*
1294* The tests for NaN rely on the compiler not being overly
1295* aggressive and removing the statements altogether.
1296 IF ((snrm.NE.snrm).OR.(znrm.NE.znrm)) THEN
1297 IF ((snrm.NE.snrm).NEQV.(znrm.NE.znrm)) THEN
1298 trat = one / ulp
1299 ELSE
1300 trat = zero
1301 END IF
1302 ELSE IF (snrm == znrm) THEN
1303 trat = zero
1304 ELSE IF (znrm == zero) THEN
1305 trat = snrm / ulp
1306 ELSE
1307 trat = (abs(snrm-znrm) / znrm) / (dble(n)*ulp)
1308 END IF
1309 IF ((trat.NE.trat).OR.(trat.GE.thresh)) THEN
1310 IF (first) THEN
1311 first = .false.
1312 WRITE(nout,99999)
1313 END IF
1314 WRITE (nout,98) "DNRM2", n, incx, iv, iw, trat
1315 END IF
1316 END DO
1317 END DO
131899999 FORMAT (' FAIL')
1319 99 FORMAT ( ' Not enough space to test ', a6, ': NMAX = ',i6,
1320 + ', INCX = ',i6,/,' N = ',i6,', must be at least ',i6 )
1321 98 FORMAT( 1x, a6, ': N=', i6,', INCX=', i4, ', IV=', i2, ', IW=',
1322 + i2, ', test=', e15.8 )
1323 RETURN
1324 CONTAINS
1325 DOUBLE PRECISION FUNCTION dxvals(XX,K)
1326* .. Scalar Arguments ..
1327 DOUBLE PRECISION XX
1328 INTEGER K
1329* .. Local Scalars ..
1330 DOUBLE PRECISION X, Y, YY, Z
1331* .. Intrinsic Functions ..
1332 INTRINSIC huge
1333* .. Executable Statements ..
1334 y = huge(xx)
1335 z = yy
1336 IF (k.EQ.1) THEN
1337 x = -z
1338 ELSE IF (k.EQ.2) THEN
1339 x = z
1340 ELSE IF (k.EQ.3) THEN
1341 x = z / z
1342 END IF
1343 dxvals = x
1344 RETURN
1345 END
real(wp) function dnrm2(n, x, incx)
DNRM2
Definition dnrm2.f90:89
Here is the caller graph for this function: