LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zlarot ( logical  LROWS,
logical  LLEFT,
logical  LRIGHT,
integer  NL,
complex*16  C,
complex*16  S,
complex*16, dimension( * )  A,
integer  LDA,
complex*16  XLEFT,
complex*16  XRIGHT 
)

ZLAROT

Purpose:
    ZLAROT applies a (Givens) rotation to two adjacent rows or
    columns, where one element of the first and/or last column/row
    for use on matrices stored in some format other than GE, so
    that elements of the matrix may be used or modified for which
    no array element is provided.

    One example is a symmetric matrix in SB format (bandwidth=4), for
    which UPLO='L':  Two adjacent rows will have the format:

    row j:     C> C> C> C> C> .  .  .  .
    row j+1:      C> C> C> C> C> .  .  .  .

    '*' indicates elements for which storage is provided,
    '.' indicates elements for which no storage is provided, but
    are not necessarily zero; their values are determined by
    symmetry.  ' ' indicates elements which are necessarily zero,
     and have no storage provided.

    Those columns which have two '*'s can be handled by DROT.
    Those columns which have no '*'s can be ignored, since as long
    as the Givens rotations are carefully applied to preserve
    symmetry, their values are determined.
    Those columns which have one '*' have to be handled separately,
    by using separate variables "p" and "q":

    row j:     C> C> C> C> C> p  .  .  .
    row j+1:   q  C> C> C> C> C> .  .  .  .

    The element p would have to be set correctly, then that column
    is rotated, setting p to its new value.  The next call to
    ZLAROT would rotate columns j and j+1, using p, and restore
    symmetry.  The element q would start out being zero, and be
    made non-zero by the rotation.  Later, rotations would presumably
    be chosen to zero q out.

    Typical Calling Sequences: rotating the i-th and (i+1)-st rows.
    ------- ------- ---------

      General dense matrix:

              CALL ZLAROT(.TRUE.,.FALSE.,.FALSE., N, C,S,
                      A(i,1),LDA, DUMMY, DUMMY)

      General banded matrix in GB format:

              j = MAX(1, i-KL )
              NL = MIN( N, i+KU+1 ) + 1-j
              CALL ZLAROT( .TRUE., i-KL.GE.1, i+KU.LT.N, NL, C,S,
                      A(KU+i+1-j,j),LDA-1, XLEFT, XRIGHT )

              [ note that i+1-j is just MIN(i,KL+1) ]

      Symmetric banded matrix in SY format, bandwidth K,
      lower triangle only:

              j = MAX(1, i-K )
              NL = MIN( K+1, i ) + 1
              CALL ZLAROT( .TRUE., i-K.GE.1, .TRUE., NL, C,S,
                      A(i,j), LDA, XLEFT, XRIGHT )

      Same, but upper triangle only:

              NL = MIN( K+1, N-i ) + 1
              CALL ZLAROT( .TRUE., .TRUE., i+K.LT.N, NL, C,S,
                      A(i,i), LDA, XLEFT, XRIGHT )

      Symmetric banded matrix in SB format, bandwidth K,
      lower triangle only:

              [ same as for SY, except:]
                  . . . .
                      A(i+1-j,j), LDA-1, XLEFT, XRIGHT )

              [ note that i+1-j is just MIN(i,K+1) ]

      Same, but upper triangle only:
                  . . .
                      A(K+1,i), LDA-1, XLEFT, XRIGHT )

      Rotating columns is just the transpose of rotating rows, except
      for GB and SB: (rotating columns i and i+1)

      GB:
              j = MAX(1, i-KU )
              NL = MIN( N, i+KL+1 ) + 1-j
              CALL ZLAROT( .TRUE., i-KU.GE.1, i+KL.LT.N, NL, C,S,
                      A(KU+j+1-i,i),LDA-1, XTOP, XBOTTM )

              [note that KU+j+1-i is just MAX(1,KU+2-i)]

      SB: (upper triangle)

                   . . . . . .
                      A(K+j+1-i,i),LDA-1, XTOP, XBOTTM )

      SB: (lower triangle)

                   . . . . . .
                      A(1,i),LDA-1, XTOP, XBOTTM )
  LROWS  - LOGICAL
           If .TRUE., then ZLAROT will rotate two rows.  If .FALSE.,
           then it will rotate two columns.
           Not modified.

  LLEFT  - LOGICAL
           If .TRUE., then XLEFT will be used instead of the
           corresponding element of A for the first element in the
           second row (if LROWS=.FALSE.) or column (if LROWS=.TRUE.)
           If .FALSE., then the corresponding element of A will be
           used.
           Not modified.

  LRIGHT - LOGICAL
           If .TRUE., then XRIGHT will be used instead of the
           corresponding element of A for the last element in the
           first row (if LROWS=.FALSE.) or column (if LROWS=.TRUE.) If
           .FALSE., then the corresponding element of A will be used.
           Not modified.

  NL     - INTEGER
           The length of the rows (if LROWS=.TRUE.) or columns (if
           LROWS=.FALSE.) to be rotated.  If XLEFT and/or XRIGHT are
           used, the columns/rows they are in should be included in
           NL, e.g., if LLEFT = LRIGHT = .TRUE., then NL must be at
           least 2.  The number of rows/columns to be rotated
           exclusive of those involving XLEFT and/or XRIGHT may
           not be negative, i.e., NL minus how many of LLEFT and
           LRIGHT are .TRUE. must be at least zero; if not, XERBLA
           will be called.
           Not modified.

  C, S   - COMPLEX*16
           Specify the Givens rotation to be applied.  If LROWS is
           true, then the matrix ( c  s )
                                 ( _  _ )
                                 (-s  c )  is applied from the left;
           if false, then the transpose (not conjugated) thereof is
           applied from the right.  Note that in contrast to the
           output of ZROTG or to most versions of ZROT, both C and S
           are complex.  For a Givens rotation, |C|**2 + |S|**2 should
           be 1, but this is not checked.
           Not modified.

  A      - COMPLEX*16 array.
           The array containing the rows/columns to be rotated.  The
           first element of A should be the upper left element to
           be rotated.
           Read and modified.

  LDA    - INTEGER
           The "effective" leading dimension of A.  If A contains
           a matrix stored in GE, HE, or SY format, then this is just
           the leading dimension of A as dimensioned in the calling
           routine.  If A contains a matrix stored in band (GB, HB, or
           SB) format, then this should be *one less* than the leading
           dimension used in the calling routine.  Thus, if A were
           dimensioned A(LDA,*) in ZLAROT, then A(1,j) would be the
           j-th element in the first of the two rows to be rotated,
           and A(2,j) would be the j-th in the second, regardless of
           how the array may be stored in the calling routine.  [A
           cannot, however, actually be dimensioned thus, since for
           band format, the row number may exceed LDA, which is not
           legal FORTRAN.]
           If LROWS=.TRUE., then LDA must be at least 1, otherwise
           it must be at least NL minus the number of .TRUE. values
           in XLEFT and XRIGHT.
           Not modified.

  XLEFT  - COMPLEX*16
           If LLEFT is .TRUE., then XLEFT will be used and modified
           instead of A(2,1) (if LROWS=.TRUE.) or A(1,2)
           (if LROWS=.FALSE.).
           Read and modified.

  XRIGHT - COMPLEX*16
           If LRIGHT is .TRUE., then XRIGHT will be used and modified
           instead of A(1,NL) (if LROWS=.TRUE.) or A(NL,1)
           (if LROWS=.FALSE.).
           Read and modified.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 231 of file zlarot.f.

231 *
232 * -- LAPACK auxiliary routine (version 3.4.0) --
233 * -- LAPACK is a software package provided by Univ. of Tennessee, --
234 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
235 * November 2011
236 *
237 * .. Scalar Arguments ..
238  LOGICAL lleft, lright, lrows
239  INTEGER lda, nl
240  COMPLEX*16 c, s, xleft, xright
241 * ..
242 * .. Array Arguments ..
243  COMPLEX*16 a( * )
244 * ..
245 *
246 * =====================================================================
247 *
248 * .. Local Scalars ..
249  INTEGER iinc, inext, ix, iy, iyt, j, nt
250  COMPLEX*16 tempx
251 * ..
252 * .. Local Arrays ..
253  COMPLEX*16 xt( 2 ), yt( 2 )
254 * ..
255 * .. External Subroutines ..
256  EXTERNAL xerbla
257 * ..
258 * .. Intrinsic Functions ..
259  INTRINSIC dconjg
260 * ..
261 * .. Executable Statements ..
262 *
263 * Set up indices, arrays for ends
264 *
265  IF( lrows ) THEN
266  iinc = lda
267  inext = 1
268  ELSE
269  iinc = 1
270  inext = lda
271  END IF
272 *
273  IF( lleft ) THEN
274  nt = 1
275  ix = 1 + iinc
276  iy = 2 + lda
277  xt( 1 ) = a( 1 )
278  yt( 1 ) = xleft
279  ELSE
280  nt = 0
281  ix = 1
282  iy = 1 + inext
283  END IF
284 *
285  IF( lright ) THEN
286  iyt = 1 + inext + ( nl-1 )*iinc
287  nt = nt + 1
288  xt( nt ) = xright
289  yt( nt ) = a( iyt )
290  END IF
291 *
292 * Check for errors
293 *
294  IF( nl.LT.nt ) THEN
295  CALL xerbla( 'ZLAROT', 4 )
296  RETURN
297  END IF
298  IF( lda.LE.0 .OR. ( .NOT.lrows .AND. lda.LT.nl-nt ) ) THEN
299  CALL xerbla( 'ZLAROT', 8 )
300  RETURN
301  END IF
302 *
303 * Rotate
304 *
305 * ZROT( NL-NT, A(IX),IINC, A(IY),IINC, C, S ) with complex C, S
306 *
307  DO 10 j = 0, nl - nt - 1
308  tempx = c*a( ix+j*iinc ) + s*a( iy+j*iinc )
309  a( iy+j*iinc ) = -dconjg( s )*a( ix+j*iinc ) +
310  $ dconjg( c )*a( iy+j*iinc )
311  a( ix+j*iinc ) = tempx
312  10 CONTINUE
313 *
314 * ZROT( NT, XT,1, YT,1, C, S ) with complex C, S
315 *
316  DO 20 j = 1, nt
317  tempx = c*xt( j ) + s*yt( j )
318  yt( j ) = -dconjg( s )*xt( j ) + dconjg( c )*yt( j )
319  xt( j ) = tempx
320  20 CONTINUE
321 *
322 * Stuff values back into XLEFT, XRIGHT, etc.
323 *
324  IF( lleft ) THEN
325  a( 1 ) = xt( 1 )
326  xleft = yt( 1 )
327  END IF
328 *
329  IF( lright ) THEN
330  xright = xt( nt )
331  a( iyt ) = yt( nt )
332  END IF
333 *
334  RETURN
335 *
336 * End of ZLAROT
337 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62

Here is the call graph for this function:

Here is the caller graph for this function: