Skip to content

Commit fd8fcf1

Browse files
committed
Replace A_shape with size() calls
1 parent 55e0dd0 commit fd8fcf1

File tree

1 file changed

+16
-25
lines changed

1 file changed

+16
-25
lines changed

src/stdlib_linalg.fypp

Lines changed: 16 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -207,9 +207,7 @@ contains
207207
pure function is_square_${t1[0]}$${k1}$(A) result(res)
208208
${t1}$, intent(in) :: A(:,:)
209209
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))
213211
end function is_square_${t1[0]}$${k1}$
214212
#:endfor
215213

@@ -219,11 +217,10 @@ contains
219217
${t1}$, intent(in) :: A(:,:)
220218
logical :: res
221219
${t1}$ :: zero
222-
integer :: A_shape(2), m, n, o, i, j
220+
integer :: m, n, o, i, j
223221
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)
227224
do j = 1, n !loop over all columns
228225
o = min(j-1,m) !index of row above diagonal (or last row)
229226
do i = 1, o !loop over rows above diagonal
@@ -248,13 +245,12 @@ contains
248245
pure function is_symmetric_${t1[0]}$${k1}$(A) result(res)
249246
${t1}$, intent(in) :: A(:,:)
250247
logical :: res
251-
integer :: A_shape(2), n, i, j
248+
integer :: n, i, j
252249
if (.not. is_square(A)) then
253250
res = .false.
254251
return !nonsquare matrices cannot be symmetric
255252
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
258254
do j = 1, n !loop over all columns
259255
do i = 1, j-1 !loop over all rows above diagonal
260256
if (.not. (A(i,j) .eq. A(j,i))) then
@@ -272,13 +268,12 @@ contains
272268
pure function is_skew_symmetric_${t1[0]}$${k1}$(A) result(res)
273269
${t1}$, intent(in) :: A(:,:)
274270
logical :: res
275-
integer :: A_shape(2), n, i, j
271+
integer :: n, i, j
276272
if (.not. is_square(A)) then
277273
res = .false.
278274
return !nonsquare matrices cannot be skew-symmetric
279275
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
282277
do j = 1, n !loop over all columns
283278
do i = 1, j !loop over all rows above diagonal (and diagonal)
284279
if (.not. (A(i,j) .eq. -A(j,i))) then
@@ -296,7 +291,6 @@ contains
296291
pure function is_hermitian_${t1[0]}$${k1}$(A) result(res)
297292
${t1}$, intent(in) :: A(:,:)
298293
logical :: res
299-
integer :: A_shape(2), n, i, j
300294
if (.not. is_square(A)) then
301295
res = .false.
302296
return !nonsquare matrices cannot be Hermitian
@@ -308,13 +302,12 @@ contains
308302
pure function is_hermitian_${t1[0]}$${k1}$(A) result(res)
309303
${t1}$, intent(in) :: A(:,:)
310304
logical :: res
311-
integer :: A_shape(2), n, i, j
305+
integer :: n, i, j
312306
if (.not. is_square(A)) then
313307
res = .false.
314308
return !nonsquare matrices cannot be Hermitian
315309
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
318311
do j = 1, n !loop over all columns
319312
do i = 1, j !loop over all rows above diagonal (and diagonal)
320313
if (.not. (A(i,j) .eq. conjg(A(j,i)))) then
@@ -334,11 +327,10 @@ contains
334327
character, intent(in) :: uplo
335328
logical :: res
336329
${t1}$ :: zero
337-
integer :: A_shape(2), m, n, o, i, j
330+
integer :: m, n, o, i, j
338331
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)
342334
if ((uplo .eq. 'u') .or. (uplo .eq. 'U')) then !check for upper triangularity
343335
do j = 1, n !loop over all columns
344336
o = min(j-1,m) !index of row above diagonal (or last row)
@@ -374,11 +366,10 @@ contains
374366
character, intent(in) :: uplo
375367
logical :: res
376368
${t1}$ :: zero
377-
integer :: A_shape(2), m, n, o, i, j
369+
integer :: m, n, o, i, j
378370
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)
382373
if ((uplo .eq. 'u') .or. (uplo .eq. 'U')) then !check for upper Hessenberg
383374
do j = 1, n !loop over all columns
384375
o = min(j-2,m) !index of row two above diagonal (or last row)

0 commit comments

Comments
 (0)