@@ -207,9 +207,7 @@ contains
207
207
pure function is_square_${t1[0]}$${k1}$(A) result(res)
208
208
${t1}$, intent(in) :: A(:,:)
209
209
logical :: res
210
- integer :: A_shape(2)
211
- A_shape = shape(A)
212
- res = (A_shape(1) .eq. A_shape(2))
210
+ res = (size(A,1) .eq. size(A,2))
213
211
end function is_square_${t1[0]}$${k1}$
214
212
#:endfor
215
213
@@ -219,11 +217,10 @@ contains
219
217
${t1}$, intent(in) :: A(:,:)
220
218
logical :: res
221
219
${t1}$ :: zero
222
- integer :: A_shape(2), m, n, o, i, j
220
+ integer :: m, n, o, i, j
223
221
zero = 0 !zero of relevant type
224
- A_shape = shape(A)
225
- m = A_shape(1)
226
- n = A_shape(2)
222
+ m = size(A,1)
223
+ n = size(A,2)
227
224
do j = 1, n !loop over all columns
228
225
o = min(j-1,m) !index of row above diagonal (or last row)
229
226
do i = 1, o !loop over rows above diagonal
@@ -248,13 +245,12 @@ contains
248
245
pure function is_symmetric_${t1[0]}$${k1}$(A) result(res)
249
246
${t1}$, intent(in) :: A(:,:)
250
247
logical :: res
251
- integer :: A_shape(2), n, i, j
248
+ integer :: n, i, j
252
249
if (.not. is_square(A)) then
253
250
res = .false.
254
251
return !nonsquare matrices cannot be symmetric
255
252
end if
256
- A_shape = shape(A)
257
- n = A_shape(1) !symmetric dimension of A
253
+ n = size(A,1) !symmetric dimension of A
258
254
do j = 1, n !loop over all columns
259
255
do i = 1, j-1 !loop over all rows above diagonal
260
256
if (.not. (A(i,j) .eq. A(j,i))) then
@@ -272,13 +268,12 @@ contains
272
268
pure function is_skew_symmetric_${t1[0]}$${k1}$(A) result(res)
273
269
${t1}$, intent(in) :: A(:,:)
274
270
logical :: res
275
- integer :: A_shape(2), n, i, j
271
+ integer :: n, i, j
276
272
if (.not. is_square(A)) then
277
273
res = .false.
278
274
return !nonsquare matrices cannot be skew-symmetric
279
275
end if
280
- A_shape = shape(A)
281
- n = A_shape(1) !symmetric dimension of A
276
+ n = size(A,1) !symmetric dimension of A
282
277
do j = 1, n !loop over all columns
283
278
do i = 1, j !loop over all rows above diagonal (and diagonal)
284
279
if (.not. (A(i,j) .eq. -A(j,i))) then
@@ -296,7 +291,6 @@ contains
296
291
pure function is_hermitian_${t1[0]}$${k1}$(A) result(res)
297
292
${t1}$, intent(in) :: A(:,:)
298
293
logical :: res
299
- integer :: A_shape(2), n, i, j
300
294
if (.not. is_square(A)) then
301
295
res = .false.
302
296
return !nonsquare matrices cannot be Hermitian
@@ -308,13 +302,12 @@ contains
308
302
pure function is_hermitian_${t1[0]}$${k1}$(A) result(res)
309
303
${t1}$, intent(in) :: A(:,:)
310
304
logical :: res
311
- integer :: A_shape(2), n, i, j
305
+ integer :: n, i, j
312
306
if (.not. is_square(A)) then
313
307
res = .false.
314
308
return !nonsquare matrices cannot be Hermitian
315
309
end if
316
- A_shape = shape(A)
317
- n = A_shape(1) !symmetric dimension of A
310
+ n = size(A,1) !symmetric dimension of A
318
311
do j = 1, n !loop over all columns
319
312
do i = 1, j !loop over all rows above diagonal (and diagonal)
320
313
if (.not. (A(i,j) .eq. conjg(A(j,i)))) then
@@ -334,11 +327,10 @@ contains
334
327
character, intent(in) :: uplo
335
328
logical :: res
336
329
${t1}$ :: zero
337
- integer :: A_shape(2), m, n, o, i, j
330
+ integer :: m, n, o, i, j
338
331
zero = 0 !zero of relevant type
339
- A_shape = shape(A)
340
- m = A_shape(1)
341
- n = A_shape(2)
332
+ m = size(A,1)
333
+ n = size(A,2)
342
334
if ((uplo .eq. 'u') .or. (uplo .eq. 'U')) then !check for upper triangularity
343
335
do j = 1, n !loop over all columns
344
336
o = min(j-1,m) !index of row above diagonal (or last row)
@@ -374,11 +366,10 @@ contains
374
366
character, intent(in) :: uplo
375
367
logical :: res
376
368
${t1}$ :: zero
377
- integer :: A_shape(2), m, n, o, i, j
369
+ integer :: m, n, o, i, j
378
370
zero = 0 !zero of relevant type
379
- A_shape = shape(A)
380
- m = A_shape(1)
381
- n = A_shape(2)
371
+ m = size(A,1)
372
+ n = size(A,2)
382
373
if ((uplo .eq. 'u') .or. (uplo .eq. 'U')) then !check for upper Hessenberg
383
374
do j = 1, n !loop over all columns
384
375
o = min(j-2,m) !index of row two above diagonal (or last row)
0 commit comments