@@ -139,18 +139,18 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
139139 module function stdlib_linalg_eigvals_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#,err) result(lambda)
140140 !! Return an array of eigenvalues of matrix A.
141141 !> Input matrix A[m,n]
142- ${rt}$, intent(in), dimension(:,:), target :: a
142+ ${rt}$, intent(in), target :: a(:,:)
143143 #:if ei=='ggev'
144144 !> Generalized problem matrix B[n,n]
145- ${rt}$, intent(inout), dimension(:,:), target :: b
145+ ${rt}$, intent(inout), target :: b(:,:)
146146 #:endif
147147 !> [optional] state return flag. On error if not requested, the code will stop
148148 type(linalg_state_type), intent(out) :: err
149149 !> Array of eigenvalues
150150 complex(${rk}$), allocatable :: lambda(:)
151151
152152 !> Create
153- ${rt}$, pointer, dimension(:,:) :: amat #{if ei=='ggev'}#, bmat #{endif}#
153+ ${rt}$, pointer :: amat(:,:) #{if ei=='ggev'}#, bmat(:,:) #{endif}#
154154 integer(ilp) :: m,n,k
155155
156156 !> 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
172172 module function stdlib_linalg_eigvals_noerr_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#) result(lambda)
173173 !! Return an array of eigenvalues of matrix A.
174174 !> Input matrix A[m,n]
175- ${rt}$, intent(in), dimension(:,:), target :: a
175+ ${rt}$, intent(in), target :: a(:,:)
176176 #:if ei=='ggev'
177177 !> Generalized problem matrix B[n,n]
178- ${rt}$, intent(inout), dimension(:,:), target :: b
178+ ${rt}$, intent(inout), target :: b(:,:)
179179 #:endif
180180 !> Array of eigenvalues
181181 complex(${rk}$), allocatable :: lambda(:)
182182
183183 !> Create
184- ${rt}$, pointer, dimension(:,:) :: amat #{if ei=='ggev'}#, bmat #{endif}#
184+ ${rt}$, pointer :: amat(:,:) #{if ei=='ggev'}#, bmat(:,:) #{endif}#
185185 integer(ilp) :: m,n,k
186186
187187 !> 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
205205 !! Eigendecomposition of matrix A returning an array `lambda` of eigenvalues,
206206 !! and optionally right or left eigenvectors.
207207 !> Input matrix A[m,n]
208- ${rt}$, intent(inout), dimension(:,:), target :: a
208+ ${rt}$, intent(inout), target :: a(:,:)
209209 #:if ei=='ggev'
210210 !> Generalized problem matrix B[n,n]
211- ${rt}$, intent(inout), dimension(:,:), target :: b
211+ ${rt}$, intent(inout), target :: b(:,:)
212212 #:endif
213213 !> Array of eigenvalues
214214 complex(${rk}$), intent(out) :: lambda(:)
@@ -232,7 +232,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
232232 character :: task_u,task_v
233233 ${rt}$, target :: work_dummy(1),u_dummy(1,1),v_dummy(1,1)
234234 ${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}#
236236 #:if rt.startswith('complex')
237237 real(${rk}$), allocatable :: rwork(:)
238238 #:else
0 commit comments