@@ -139,18 +139,18 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
139
139
module function stdlib_linalg_eigvals_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#,err) result(lambda)
140
140
!! Return an array of eigenvalues of matrix A.
141
141
!> Input matrix A[m,n]
142
- ${rt}$, intent(in), dimension(:,:), target :: a
142
+ ${rt}$, intent(in), target :: a(:,:)
143
143
#:if ei=='ggev'
144
144
!> Generalized problem matrix B[n,n]
145
- ${rt}$, intent(inout), dimension(:,:), target :: b
145
+ ${rt}$, intent(inout), target :: b(:,:)
146
146
#:endif
147
147
!> [optional] state return flag. On error if not requested, the code will stop
148
148
type(linalg_state_type), intent(out) :: err
149
149
!> Array of eigenvalues
150
150
complex(${rk}$), allocatable :: lambda(:)
151
151
152
152
!> Create
153
- ${rt}$, pointer, dimension(:,:) :: amat #{if ei=='ggev'}#, bmat #{endif}#
153
+ ${rt}$, pointer :: amat(:,:) #{if ei=='ggev'}#, bmat(:,:) #{endif}#
154
154
integer(ilp) :: m,n,k
155
155
156
156
!> Create an internal pointer so the intent of A won't affect the next call
@@ -172,16 +172,16 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
172
172
module function stdlib_linalg_eigvals_noerr_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#) result(lambda)
173
173
!! Return an array of eigenvalues of matrix A.
174
174
!> Input matrix A[m,n]
175
- ${rt}$, intent(in), dimension(:,:), target :: a
175
+ ${rt}$, intent(in), target :: a(:,:)
176
176
#:if ei=='ggev'
177
177
!> Generalized problem matrix B[n,n]
178
- ${rt}$, intent(inout), dimension(:,:), target :: b
178
+ ${rt}$, intent(inout), target :: b(:,:)
179
179
#:endif
180
180
!> Array of eigenvalues
181
181
complex(${rk}$), allocatable :: lambda(:)
182
182
183
183
!> Create
184
- ${rt}$, pointer, dimension(:,:) :: amat #{if ei=='ggev'}#, bmat #{endif}#
184
+ ${rt}$, pointer :: amat(:,:) #{if ei=='ggev'}#, bmat(:,:) #{endif}#
185
185
integer(ilp) :: m,n,k
186
186
187
187
!> Create an internal pointer so the intent of A won't affect the next call
@@ -205,10 +205,10 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
205
205
!! Eigendecomposition of matrix A returning an array `lambda` of eigenvalues,
206
206
!! and optionally right or left eigenvectors.
207
207
!> Input matrix A[m,n]
208
- ${rt}$, intent(inout), dimension(:,:), target :: a
208
+ ${rt}$, intent(inout), target :: a(:,:)
209
209
#:if ei=='ggev'
210
210
!> Generalized problem matrix B[n,n]
211
- ${rt}$, intent(inout), dimension(:,:), target :: b
211
+ ${rt}$, intent(inout), target :: b(:,:)
212
212
#:endif
213
213
!> Array of eigenvalues
214
214
complex(${rk}$), intent(out) :: lambda(:)
@@ -232,7 +232,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
232
232
character :: task_u,task_v
233
233
${rt}$, target :: work_dummy(1),u_dummy(1,1),v_dummy(1,1)
234
234
${rt}$, allocatable :: work(:)
235
- ${rt}$, dimension(:,:), pointer :: amat, umat, vmat#{if ei=='ggev'}#,bmat#{endif}#
235
+ ${rt}$, pointer :: amat(:,:), umat(:,:), vmat(:,:) #{if ei=='ggev'}#,bmat(:,:) #{endif}#
236
236
#:if rt.startswith('complex')
237
237
real(${rk}$), allocatable :: rwork(:)
238
238
#:else
@@ -353,7 +353,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
353
353
354
354
! Compute workspace size
355
355
#:if rt.startswith('complex')
356
- allocate(rwork(2*n))
356
+ allocate(rwork( #{if ei=='ggev'}# 8*n #{else}# 2*n #{endif}# ))
357
357
#:else
358
358
allocate(lreal(n),limag(n))
359
359
#:endif
0 commit comments