@@ -156,7 +156,7 @@ module stdlib_linalg_svd
156156
157157 if (.not.size(s,kind=ilp)>=k) then
158158 err0 = linalg_state_type(this,LINALG_VALUE_ERROR,'singular value array has insufficient size:',&
159- ' s=[',size (s,kind=ilp),'] , k=',k)
159+ ' s=',shape (s,kind=ilp),', k=',k)
160160 goto 1
161161 endif
162162
@@ -193,31 +193,37 @@ module stdlib_linalg_svd
193193
194194 ! U, VT storage
195195 if (present(u)) then
196+ ! User input
196197 umat => u
197198 alloc_u = .false.
198199 elseif ((copy_a .and. m>=n) .or. .not.compute_uv) then
199200 ! U not wanted, and A can be overwritten: do not allocate
200201 umat => u_dummy
201202 alloc_u = .false.
202203 elseif (.not.full_storage) then
204+ ! Allocate with minimum size
203205 allocate(umat(m,k))
204206 alloc_u = .true.
205207 else
208+ ! Allocate with regular size
206209 allocate(umat(m,m))
207210 alloc_u = .true.
208211 end if
209212
210213 if (present(vt)) then
214+ ! User input
211215 vtmat => vt
212216 alloc_vt = .false.
213217 elseif ((copy_a .and. m<n) .or. .not.compute_uv) then
214218 ! amat can be overwritten, VT not wanted: VT is returned upon A
215219 vtmat => vt_dummy
216220 alloc_vt = .false.
217221 elseif (.not.full_storage) then
222+ ! Allocate with minimum size
218223 allocate(vtmat(k,n))
219224 alloc_vt = .true.
220225 else
226+ ! Allocate with regular size
221227 allocate(vtmat(n,n))
222228 alloc_vt = .true.
223229 end if
@@ -245,10 +251,12 @@ module stdlib_linalg_svd
245251 lrwork = max(1,5*k*(k+1),2*k*(k+max(m,n))+k)
246252 endif
247253 allocate(rwork(lrwork))
254+ #:else
255+ lrwork = -1_ilp ! not needed
248256 #:endif
249257
258+ ! First call: request working storage space
250259 lwork = -1_ilp
251-
252260 call gesdd(task,m,n,amat,lda,s,umat,ldu,vtmat,ldvt,&
253261 work_dummy,lwork,#{if rt.startswith('complex')}#rwork,#{endif}#iwork,info)
254262 call handle_gesdd_info(err0,info,m,n)
@@ -262,7 +270,7 @@ module stdlib_linalg_svd
262270
263271 !> Compute SVD
264272 call gesdd(task,m,n,amat,lda,s,umat,ldu,vtmat,ldvt,&
265- work,lwork,#{if rt.startswith('comp ')}#rwork,#{endif}#iwork,info)
273+ work,lwork,#{if rt.startswith('complex ')}#rwork,#{endif}#iwork,info)
266274 call handle_gesdd_info(err0,info,m,n)
267275
268276 endif
0 commit comments