LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zlaptm ( character  UPLO,
integer  N,
integer  NRHS,
double precision  ALPHA,
double precision, dimension( * )  D,
complex*16, dimension( * )  E,
complex*16, dimension( ldx, * )  X,
integer  LDX,
double precision  BETA,
complex*16, dimension( ldb, * )  B,
integer  LDB 
)

ZLAPTM

Purpose:
 ZLAPTM multiplies an N by NRHS matrix X by a Hermitian tridiagonal
 matrix A and stores the result in a matrix B.  The operation has the
 form

    B := alpha * A * X + beta * B

 where alpha may be either 1. or -1. and beta may be 0., 1., or -1.
Parameters
[in]UPLO
          UPLO is CHARACTER
          Specifies whether the superdiagonal or the subdiagonal of the
          tridiagonal matrix A is stored.
          = 'U':  Upper, E is the superdiagonal of A.
          = 'L':  Lower, E is the subdiagonal of A.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of right hand sides, i.e., the number of columns
          of the matrices X and B.
[in]ALPHA
          ALPHA is DOUBLE PRECISION
          The scalar alpha.  ALPHA must be 1. or -1.; otherwise,
          it is assumed to be 0.
[in]D
          D is DOUBLE PRECISION array, dimension (N)
          The n diagonal elements of the tridiagonal matrix A.
[in]E
          E is COMPLEX*16 array, dimension (N-1)
          The (n-1) subdiagonal or superdiagonal elements of A.
[in]X
          X is COMPLEX*16 array, dimension (LDX,NRHS)
          The N by NRHS matrix X.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= max(N,1).
[in]BETA
          BETA is DOUBLE PRECISION
          The scalar beta.  BETA must be 0., 1., or -1.; otherwise,
          it is assumed to be 1.
[in,out]B
          B is COMPLEX*16 array, dimension (LDB,NRHS)
          On entry, the N by NRHS matrix B.
          On exit, B is overwritten by the matrix expression
          B := alpha * A * X + beta * B.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(N,1).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 131 of file zlaptm.f.

131 *
132 * -- LAPACK test routine (version 3.4.0) --
133 * -- LAPACK is a software package provided by Univ. of Tennessee, --
134 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
135 * November 2011
136 *
137 * .. Scalar Arguments ..
138  CHARACTER uplo
139  INTEGER ldb, ldx, n, nrhs
140  DOUBLE PRECISION alpha, beta
141 * ..
142 * .. Array Arguments ..
143  DOUBLE PRECISION d( * )
144  COMPLEX*16 b( ldb, * ), e( * ), x( ldx, * )
145 * ..
146 *
147 * =====================================================================
148 *
149 * .. Parameters ..
150  DOUBLE PRECISION one, zero
151  parameter ( one = 1.0d+0, zero = 0.0d+0 )
152 * ..
153 * .. Local Scalars ..
154  INTEGER i, j
155 * ..
156 * .. External Functions ..
157  LOGICAL lsame
158  EXTERNAL lsame
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC dconjg
162 * ..
163 * .. Executable Statements ..
164 *
165  IF( n.EQ.0 )
166  $ RETURN
167 *
168  IF( beta.EQ.zero ) THEN
169  DO 20 j = 1, nrhs
170  DO 10 i = 1, n
171  b( i, j ) = zero
172  10 CONTINUE
173  20 CONTINUE
174  ELSE IF( beta.EQ.-one ) THEN
175  DO 40 j = 1, nrhs
176  DO 30 i = 1, n
177  b( i, j ) = -b( i, j )
178  30 CONTINUE
179  40 CONTINUE
180  END IF
181 *
182  IF( alpha.EQ.one ) THEN
183  IF( lsame( uplo, 'U' ) ) THEN
184 *
185 * Compute B := B + A*X, where E is the superdiagonal of A.
186 *
187  DO 60 j = 1, nrhs
188  IF( n.EQ.1 ) THEN
189  b( 1, j ) = b( 1, j ) + d( 1 )*x( 1, j )
190  ELSE
191  b( 1, j ) = b( 1, j ) + d( 1 )*x( 1, j ) +
192  $ e( 1 )*x( 2, j )
193  b( n, j ) = b( n, j ) + dconjg( e( n-1 ) )*
194  $ x( n-1, j ) + d( n )*x( n, j )
195  DO 50 i = 2, n - 1
196  b( i, j ) = b( i, j ) + dconjg( e( i-1 ) )*
197  $ x( i-1, j ) + d( i )*x( i, j ) +
198  $ e( i )*x( i+1, j )
199  50 CONTINUE
200  END IF
201  60 CONTINUE
202  ELSE
203 *
204 * Compute B := B + A*X, where E is the subdiagonal of A.
205 *
206  DO 80 j = 1, nrhs
207  IF( n.EQ.1 ) THEN
208  b( 1, j ) = b( 1, j ) + d( 1 )*x( 1, j )
209  ELSE
210  b( 1, j ) = b( 1, j ) + d( 1 )*x( 1, j ) +
211  $ dconjg( e( 1 ) )*x( 2, j )
212  b( n, j ) = b( n, j ) + e( n-1 )*x( n-1, j ) +
213  $ d( n )*x( n, j )
214  DO 70 i = 2, n - 1
215  b( i, j ) = b( i, j ) + e( i-1 )*x( i-1, j ) +
216  $ d( i )*x( i, j ) +
217  $ dconjg( e( i ) )*x( i+1, j )
218  70 CONTINUE
219  END IF
220  80 CONTINUE
221  END IF
222  ELSE IF( alpha.EQ.-one ) THEN
223  IF( lsame( uplo, 'U' ) ) THEN
224 *
225 * Compute B := B - A*X, where E is the superdiagonal of A.
226 *
227  DO 100 j = 1, nrhs
228  IF( n.EQ.1 ) THEN
229  b( 1, j ) = b( 1, j ) - d( 1 )*x( 1, j )
230  ELSE
231  b( 1, j ) = b( 1, j ) - d( 1 )*x( 1, j ) -
232  $ e( 1 )*x( 2, j )
233  b( n, j ) = b( n, j ) - dconjg( e( n-1 ) )*
234  $ x( n-1, j ) - d( n )*x( n, j )
235  DO 90 i = 2, n - 1
236  b( i, j ) = b( i, j ) - dconjg( e( i-1 ) )*
237  $ x( i-1, j ) - d( i )*x( i, j ) -
238  $ e( i )*x( i+1, j )
239  90 CONTINUE
240  END IF
241  100 CONTINUE
242  ELSE
243 *
244 * Compute B := B - A*X, where E is the subdiagonal of A.
245 *
246  DO 120 j = 1, nrhs
247  IF( n.EQ.1 ) THEN
248  b( 1, j ) = b( 1, j ) - d( 1 )*x( 1, j )
249  ELSE
250  b( 1, j ) = b( 1, j ) - d( 1 )*x( 1, j ) -
251  $ dconjg( e( 1 ) )*x( 2, j )
252  b( n, j ) = b( n, j ) - e( n-1 )*x( n-1, j ) -
253  $ d( n )*x( n, j )
254  DO 110 i = 2, n - 1
255  b( i, j ) = b( i, j ) - e( i-1 )*x( i-1, j ) -
256  $ d( i )*x( i, j ) -
257  $ dconjg( e( i ) )*x( i+1, j )
258  110 CONTINUE
259  END IF
260  120 CONTINUE
261  END IF
262  END IF
263  RETURN
264 *
265 * End of ZLAPTM
266 *
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the caller graph for this function: