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

◆ dlaqz1()

subroutine dlaqz1 ( double precision, dimension( lda, * ), intent(in)  a,
integer, intent(in)  lda,
double precision, dimension( ldb, * ), intent(in)  b,
integer, intent(in)  ldb,
double precision, intent(in)  sr1,
double precision, intent(in)  sr2,
double precision, intent(in)  si,
double precision, intent(in)  beta1,
double precision, intent(in)  beta2,
double precision, dimension( * ), intent(out)  v 
)

DLAQZ1

Download DLAQZ1 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
      Given a 3-by-3 matrix pencil (A,B), DLAQZ1 sets v to a
      scalar multiple of the first column of the product

      (*)  K = (A - (beta2*sr2 - i*si)*B)*B^(-1)*(beta1*A - (sr2 + i*si2)*B)*B^(-1).

      It is assumed that either

              1) sr1 = sr2
          or
              2) si = 0.

      This is useful for starting double implicit shift bulges
      in the QZ algorithm.
Parameters
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
              The 3-by-3 matrix A in (*).
[in]LDA
          LDA is INTEGER
              The leading dimension of A as declared in
              the calling procedure.
[in]B
          B is DOUBLE PRECISION array, dimension (LDB,N)
              The 3-by-3 matrix B in (*).
[in]LDB
          LDB is INTEGER
              The leading dimension of B as declared in
              the calling procedure.
[in]SR1
          SR1 is DOUBLE PRECISION
[in]SR2
          SR2 is DOUBLE PRECISION
[in]SI
          SI is DOUBLE PRECISION
[in]BETA1
          BETA1 is DOUBLE PRECISION
[in]BETA2
          BETA2 is DOUBLE PRECISION
[out]V
          V is DOUBLE PRECISION array, dimension (N)
              A scalar multiple of the first column of the
              matrix K in (*).
Author
Thijs Steel, KU Leuven
Date
May 2020

Definition at line 125 of file dlaqz1.f.

127 IMPLICIT NONE
128*
129* Arguments
130 INTEGER, INTENT( IN ) :: LDA, LDB
131 DOUBLE PRECISION, INTENT( IN ) :: A( LDA, * ), B( LDB, * ), SR1,
132 $ SR2, SI, BETA1, BETA2
133 DOUBLE PRECISION, INTENT( OUT ) :: V( * )
134*
135* Parameters
136 DOUBLE PRECISION :: ZERO, ONE, HALF
137 parameter( zero = 0.0d0, one = 1.0d0, half = 0.5d0 )
138*
139* Local scalars
140 DOUBLE PRECISION :: W( 2 ), SAFMIN, SAFMAX, SCALE1, SCALE2
141*
142* External Functions
143 DOUBLE PRECISION, EXTERNAL :: DLAMCH
144 LOGICAL, EXTERNAL :: DISNAN
145*
146 safmin = dlamch( 'SAFE MINIMUM' )
147 safmax = one/safmin
148*
149* Calculate first shifted vector
150*
151 w( 1 ) = beta1*a( 1, 1 )-sr1*b( 1, 1 )
152 w( 2 ) = beta1*a( 2, 1 )-sr1*b( 2, 1 )
153 scale1 = sqrt( abs( w( 1 ) ) ) * sqrt( abs( w( 2 ) ) )
154 IF( scale1 .GE. safmin .AND. scale1 .LE. safmax ) THEN
155 w( 1 ) = w( 1 )/scale1
156 w( 2 ) = w( 2 )/scale1
157 END IF
158*
159* Solve linear system
160*
161 w( 2 ) = w( 2 )/b( 2, 2 )
162 w( 1 ) = ( w( 1 )-b( 1, 2 )*w( 2 ) )/b( 1, 1 )
163 scale2 = sqrt( abs( w( 1 ) ) ) * sqrt( abs( w( 2 ) ) )
164 IF( scale2 .GE. safmin .AND. scale2 .LE. safmax ) THEN
165 w( 1 ) = w( 1 )/scale2
166 w( 2 ) = w( 2 )/scale2
167 END IF
168*
169* Apply second shift
170*
171 v( 1 ) = beta2*( a( 1, 1 )*w( 1 )+a( 1, 2 )*w( 2 ) )-sr2*( b( 1,
172 $ 1 )*w( 1 )+b( 1, 2 )*w( 2 ) )
173 v( 2 ) = beta2*( a( 2, 1 )*w( 1 )+a( 2, 2 )*w( 2 ) )-sr2*( b( 2,
174 $ 1 )*w( 1 )+b( 2, 2 )*w( 2 ) )
175 v( 3 ) = beta2*( a( 3, 1 )*w( 1 )+a( 3, 2 )*w( 2 ) )-sr2*( b( 3,
176 $ 1 )*w( 1 )+b( 3, 2 )*w( 2 ) )
177*
178* Account for imaginary part
179*
180 v( 1 ) = v( 1 )+si*si*b( 1, 1 )/scale1/scale2
181*
182* Check for overflow
183*
184 IF( abs( v( 1 ) ).GT.safmax .OR. abs( v( 2 ) ) .GT. safmax .OR.
185 $ abs( v( 3 ) ).GT.safmax .OR. disnan( v( 1 ) ) .OR.
186 $ disnan( v( 2 ) ) .OR. disnan( v( 3 ) ) ) THEN
187 v( 1 ) = zero
188 v( 2 ) = zero
189 v( 3 ) = zero
190 END IF
191*
192* End of DLAQZ1
193*
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
Here is the caller graph for this function: