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

◆ dlarot()

subroutine dlarot ( logical lrows,
logical lleft,
logical lright,
integer nl,
double precision c,
double precision s,
double precision, dimension( * ) a,
integer lda,
double precision xleft,
double precision xright )

DLAROT

Purpose:
!>
!>    DLAROT 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  and :
!>
!>    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
!>    DLAROT 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 DLAROT(.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 DLAROT( .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 DLAROT( .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 DLAROT( .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 DLAROT( .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 DLAROT 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   - DOUBLE PRECISION
!>           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 thereof is applied from the
!>           right.  For a Givens rotation, C**2 + S**2 should be 1,
!>           but this is not checked.
!>           Not modified.
!>
!>  A      - DOUBLE PRECISION 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  leading dimension of A.  If A contains
!>           a matrix stored in GE 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 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 DLAROT, 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  - DOUBLE PRECISION
!>           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 - DOUBLE PRECISION
!>           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.

Definition at line 224 of file dlarot.f.

227*
228* -- LAPACK auxiliary routine --
229* -- LAPACK is a software package provided by Univ. of Tennessee, --
230* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
231*
232* .. Scalar Arguments ..
233 LOGICAL LLEFT, LRIGHT, LROWS
234 INTEGER LDA, NL
235 DOUBLE PRECISION C, S, XLEFT, XRIGHT
236* ..
237* .. Array Arguments ..
238 DOUBLE PRECISION A( * )
239* ..
240*
241* =====================================================================
242*
243* .. Local Scalars ..
244 INTEGER IINC, INEXT, IX, IY, IYT, NT
245* ..
246* .. Local Arrays ..
247 DOUBLE PRECISION XT( 2 ), YT( 2 )
248* ..
249* .. External Subroutines ..
250 EXTERNAL drot, xerbla
251* ..
252* .. Executable Statements ..
253*
254* Set up indices, arrays for ends
255*
256 IF( lrows ) THEN
257 iinc = lda
258 inext = 1
259 ELSE
260 iinc = 1
261 inext = lda
262 END IF
263*
264 IF( lleft ) THEN
265 nt = 1
266 ix = 1 + iinc
267 iy = 2 + lda
268 xt( 1 ) = a( 1 )
269 yt( 1 ) = xleft
270 ELSE
271 nt = 0
272 ix = 1
273 iy = 1 + inext
274 END IF
275*
276 IF( lright ) THEN
277 iyt = 1 + inext + ( nl-1 )*iinc
278 nt = nt + 1
279 xt( nt ) = xright
280 yt( nt ) = a( iyt )
281 END IF
282*
283* Check for errors
284*
285 IF( nl.LT.nt ) THEN
286 CALL xerbla( 'DLAROT', 4 )
287 RETURN
288 END IF
289 IF( lda.LE.0 .OR. ( .NOT.lrows .AND. lda.LT.nl-nt ) ) THEN
290 CALL xerbla( 'DLAROT', 8 )
291 RETURN
292 END IF
293*
294* Rotate
295*
296 CALL drot( nl-nt, a( ix ), iinc, a( iy ), iinc, c, s )
297 CALL drot( nt, xt, 1, yt, 1, c, s )
298*
299* Stuff values back into XLEFT, XRIGHT, etc.
300*
301 IF( lleft ) THEN
302 a( 1 ) = xt( 1 )
303 xleft = yt( 1 )
304 END IF
305*
306 IF( lright ) THEN
307 xright = xt( nt )
308 a( iyt ) = yt( nt )
309 END IF
310*
311 RETURN
312*
313* End of DLAROT
314*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine drot(n, dx, incx, dy, incy, c, s)
DROT
Definition drot.f:92
Here is the call graph for this function:
Here is the caller graph for this function: