LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlacsg()

subroutine dlacsg ( integer  m,
integer  p,
integer  q,
double precision, dimension( * )  theta,
integer, dimension( 4 )  iseed,
double precision, dimension( ldx, * )  x,
integer  ldx,
double precision, dimension( * )  work 
)

Definition at line 350 of file dckcsd.f.

351 IMPLICIT NONE
352*
353 INTEGER LDX, M, P, Q
354 INTEGER ISEED( 4 )
355 DOUBLE PRECISION THETA( * )
356 DOUBLE PRECISION WORK( * ), X( LDX, * )
357*
358 DOUBLE PRECISION ONE, ZERO
359 parameter( one = 1.0d0, zero = 0.0d0 )
360*
361 INTEGER I, INFO, R
362*
363 r = min( p, m-p, q, m-q )
364*
365 CALL dlaset( 'Full', m, m, zero, zero, x, ldx )
366*
367 DO i = 1, min(p,q)-r
368 x(i,i) = one
369 END DO
370 DO i = 1, r
371 x(min(p,q)-r+i,min(p,q)-r+i) = cos(theta(i))
372 END DO
373 DO i = 1, min(p,m-q)-r
374 x(p-i+1,m-i+1) = -one
375 END DO
376 DO i = 1, r
377 x(p-(min(p,m-q)-r)+1-i,m-(min(p,m-q)-r)+1-i) =
378 $ -sin(theta(r-i+1))
379 END DO
380 DO i = 1, min(m-p,q)-r
381 x(m-i+1,q-i+1) = one
382 END DO
383 DO i = 1, r
384 x(m-(min(m-p,q)-r)+1-i,q-(min(m-p,q)-r)+1-i) =
385 $ sin(theta(r-i+1))
386 END DO
387 DO i = 1, min(m-p,m-q)-r
388 x(p+i,q+i) = one
389 END DO
390 DO i = 1, r
391 x(p+(min(m-p,m-q)-r)+i,q+(min(m-p,m-q)-r)+i) =
392 $ cos(theta(i))
393 END DO
394 CALL dlaror( 'Left', 'No init', p, m, x, ldx, iseed, work, info )
395 CALL dlaror( 'Left', 'No init', m-p, m, x(p+1,1), ldx,
396 $ iseed, work, info )
397 CALL dlaror( 'Right', 'No init', m, q, x, ldx, iseed,
398 $ work, info )
399 CALL dlaror( 'Right', 'No init', m, m-q,
400 $ x(1,q+1), ldx, iseed, work, info )
401*
subroutine dlaror(side, init, m, n, a, lda, iseed, x, info)
DLAROR
Definition dlaror.f:146
subroutine dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition dlaset.f:110
Here is the call graph for this function:
Here is the caller graph for this function: