Skip to content

Commit 1a9ddb3

Browse files
committed
Switch to modern relational operators
1 parent 0da0d7d commit 1a9ddb3

File tree

1 file changed

+14
-14
lines changed

1 file changed

+14
-14
lines changed

src/stdlib_linalg.fypp

+14-14
Original file line numberDiff line numberDiff line change
@@ -207,7 +207,7 @@ contains
207207
pure function is_square_${t1[0]}$${k1}$(A) result(res)
208208
${t1}$, intent(in) :: A(:,:)
209209
logical :: res
210-
res = (size(A,1) .eq. size(A,2))
210+
res = (size(A,1) == size(A,2))
211211
end function is_square_${t1[0]}$${k1}$
212212
#:endfor
213213

@@ -224,13 +224,13 @@ contains
224224
do j = 1, n !loop over all columns
225225
o = min(j-1,m) !index of row above diagonal (or last row)
226226
do i = 1, o !loop over rows above diagonal
227-
if (A(i,j) .ne. zero) then
227+
if (A(i,j) /= zero) then
228228
res = .false.
229229
return
230230
end if
231231
end do
232232
do i = o+2, m !loop over rows below diagonal
233-
if (A(i,j) .ne. zero) then
233+
if (A(i,j) /= zero) then
234234
res = .false.
235235
return
236236
end if
@@ -253,7 +253,7 @@ contains
253253
n = size(A,1) !symmetric dimension of A
254254
do j = 1, n !loop over all columns
255255
do i = 1, j-1 !loop over all rows above diagonal
256-
if (A(i,j) .ne. A(j,i)) then
256+
if (A(i,j) /= A(j,i)) then
257257
res = .false.
258258
return
259259
end if
@@ -276,7 +276,7 @@ contains
276276
n = size(A,1) !symmetric dimension of A
277277
do j = 1, n !loop over all columns
278278
do i = 1, j !loop over all rows above diagonal (and diagonal)
279-
if (A(i,j) .ne. -A(j,i)) then
279+
if (A(i,j) /= -A(j,i)) then
280280
res = .false.
281281
return
282282
end if
@@ -310,7 +310,7 @@ contains
310310
n = size(A,1) !symmetric dimension of A
311311
do j = 1, n !loop over all columns
312312
do i = 1, j !loop over all rows above diagonal (and diagonal)
313-
if (A(i,j) .ne. conjg(A(j,i))) then
313+
if (A(i,j) /= conjg(A(j,i))) then
314314
res = .false.
315315
return
316316
end if
@@ -331,21 +331,21 @@ contains
331331
zero = 0 !zero of relevant type
332332
m = size(A,1)
333333
n = size(A,2)
334-
if ((uplo .eq. 'u') .or. (uplo .eq. 'U')) then !check for upper triangularity
334+
if ((uplo == 'u') .or. (uplo == 'U')) then !check for upper triangularity
335335
do j = 1, n !loop over all columns
336336
o = min(j-1,m) !index of row above diagonal (or last row)
337337
do i = o+2, m !loop over rows below diagonal
338-
if (A(i,j) .ne. zero) then
338+
if (A(i,j) /= zero) then
339339
res = .false.
340340
return
341341
end if
342342
end do
343343
end do
344-
else if ((uplo .eq. 'l') .or. (uplo .eq. 'L')) then !check for lower triangularity
344+
else if ((uplo == 'l') .or. (uplo == 'L')) then !check for lower triangularity
345345
do j=1,n !loop over all columns
346346
o = min(j-1,m) !index of row above diagonal (or last row)
347347
do i=1,o !loop over rows above diagonal
348-
if (A(i,j) .ne. zero) then
348+
if (A(i,j) /= zero) then
349349
res = .false.
350350
return
351351
end if
@@ -370,21 +370,21 @@ contains
370370
zero = 0 !zero of relevant type
371371
m = size(A,1)
372372
n = size(A,2)
373-
if ((uplo .eq. 'u') .or. (uplo .eq. 'U')) then !check for upper Hessenberg
373+
if ((uplo == 'u') .or. (uplo == 'U')) then !check for upper Hessenberg
374374
do j = 1, n !loop over all columns
375375
o = min(j-2,m) !index of row two above diagonal (or last row)
376376
do i = o+4, m !loop over rows two or more below main diagonal
377-
if (A(i,j) .ne. zero) then
377+
if (A(i,j) /= zero) then
378378
res = .false.
379379
return
380380
end if
381381
end do
382382
end do
383-
else if ((uplo .eq. 'l') .or. (uplo .eq. 'L')) then !check for lower Hessenberg
383+
else if ((uplo == 'l') .or. (uplo == 'L')) then !check for lower Hessenberg
384384
do j = 1, n !loop over all columns
385385
o = min(j-2,m) !index of row two above diagonal (or last row)
386386
do i = 1, o !loop over rows one or more above main diagonal
387-
if (A(i,j) .ne. zero) then
387+
if (A(i,j) /= zero) then
388388
res = .false.
389389
return
390390
end if

0 commit comments

Comments
 (0)