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

◆ zpftrs()

subroutine zpftrs ( character transr,
character uplo,
integer n,
integer nrhs,
complex*16, dimension( 0: * ) a,
complex*16, dimension( ldb, * ) b,
integer ldb,
integer info )

ZPFTRS

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

Purpose:
!>
!> ZPFTRS solves a system of linear equations A*X = B with a Hermitian
!> positive definite matrix A using the Cholesky factorization
!> A = U**H*U or A = L*L**H computed by ZPFTRF.
!> 
Parameters
[in]TRANSR
!>          TRANSR is CHARACTER*1
!>          = 'N':  The Normal TRANSR of RFP A is stored;
!>          = 'C':  The Conjugate-transpose TRANSR of RFP A is stored.
!> 
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  Upper triangle of RFP A is stored;
!>          = 'L':  Lower triangle of RFP A is stored.
!> 
[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 matrix B.  NRHS >= 0.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension ( N*(N+1)/2 );
!>          The triangular factor U or L from the Cholesky factorization
!>          of RFP A = U**H*U or RFP A = L*L**H, as computed by ZPFTRF.
!>          See note below for more details about RFP A.
!> 
[in,out]B
!>          B is COMPLEX*16 array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, the solution matrix X.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>  We first consider Standard Packed Format when N is even.
!>  We give an example where N = 6.
!>
!>      AP is Upper             AP is Lower
!>
!>   00 01 02 03 04 05       00
!>      11 12 13 14 15       10 11
!>         22 23 24 25       20 21 22
!>            33 34 35       30 31 32 33
!>               44 45       40 41 42 43 44
!>                  55       50 51 52 53 54 55
!>
!>
!>  Let TRANSR = 'N'. RFP holds AP as follows:
!>  For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
!>  three columns of AP upper. The lower triangle A(4:6,0:2) consists of
!>  conjugate-transpose of the first three columns of AP upper.
!>  For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
!>  three columns of AP lower. The upper triangle A(0:2,0:2) consists of
!>  conjugate-transpose of the last three columns of AP lower.
!>  To denote conjugate we place -- above the element. This covers the
!>  case N even and TRANSR = 'N'.
!>
!>         RFP A                   RFP A
!>
!>                                -- -- --
!>        03 04 05                33 43 53
!>                                   -- --
!>        13 14 15                00 44 54
!>                                      --
!>        23 24 25                10 11 55
!>
!>        33 34 35                20 21 22
!>        --
!>        00 44 45                30 31 32
!>        -- --
!>        01 11 55                40 41 42
!>        -- -- --
!>        02 12 22                50 51 52
!>
!>  Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
!>  transpose of RFP A above. One therefore gets:
!>
!>
!>           RFP A                   RFP A
!>
!>     -- -- -- --                -- -- -- -- -- --
!>     03 13 23 33 00 01 02    33 00 10 20 30 40 50
!>     -- -- -- -- --                -- -- -- -- --
!>     04 14 24 34 44 11 12    43 44 11 21 31 41 51
!>     -- -- -- -- -- --                -- -- -- --
!>     05 15 25 35 45 55 22    53 54 55 22 32 42 52
!>
!>
!>  We next  consider Standard Packed Format when N is odd.
!>  We give an example where N = 5.
!>
!>     AP is Upper                 AP is Lower
!>
!>   00 01 02 03 04              00
!>      11 12 13 14              10 11
!>         22 23 24              20 21 22
!>            33 34              30 31 32 33
!>               44              40 41 42 43 44
!>
!>
!>  Let TRANSR = 'N'. RFP holds AP as follows:
!>  For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
!>  three columns of AP upper. The lower triangle A(3:4,0:1) consists of
!>  conjugate-transpose of the first two   columns of AP upper.
!>  For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
!>  three columns of AP lower. The upper triangle A(0:1,1:2) consists of
!>  conjugate-transpose of the last two   columns of AP lower.
!>  To denote conjugate we place -- above the element. This covers the
!>  case N odd  and TRANSR = 'N'.
!>
!>         RFP A                   RFP A
!>
!>                                   -- --
!>        02 03 04                00 33 43
!>                                      --
!>        12 13 14                10 11 44
!>
!>        22 23 24                20 21 22
!>        --
!>        00 33 34                30 31 32
!>        -- --
!>        01 11 44                40 41 42
!>
!>  Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
!>  transpose of RFP A above. One therefore gets:
!>
!>
!>           RFP A                   RFP A
!>
!>     -- -- --                   -- -- -- -- -- --
!>     02 12 22 00 01             00 10 20 30 40 50
!>     -- -- -- --                   -- -- -- -- --
!>     03 13 23 33 11             33 11 21 31 41 51
!>     -- -- -- -- --                   -- -- -- --
!>     04 14 24 34 44             43 44 22 32 42 52
!> 

Definition at line 217 of file zpftrs.f.

218*
219* -- LAPACK computational routine --
220* -- LAPACK is a software package provided by Univ. of Tennessee, --
221* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
222*
223* .. Scalar Arguments ..
224 CHARACTER TRANSR, UPLO
225 INTEGER INFO, LDB, N, NRHS
226* ..
227* .. Array Arguments ..
228 COMPLEX*16 A( 0: * ), B( LDB, * )
229* ..
230*
231* =====================================================================
232*
233* .. Parameters ..
234 COMPLEX*16 CONE
235 parameter( cone = ( 1.0d+0, 0.0d+0 ) )
236* ..
237* .. Local Scalars ..
238 LOGICAL LOWER, NORMALTRANSR
239* ..
240* .. External Functions ..
241 LOGICAL LSAME
242 EXTERNAL lsame
243* ..
244* .. External Subroutines ..
245 EXTERNAL xerbla, ztfsm
246* ..
247* .. Intrinsic Functions ..
248 INTRINSIC max
249* ..
250* .. Executable Statements ..
251*
252* Test the input parameters.
253*
254 info = 0
255 normaltransr = lsame( transr, 'N' )
256 lower = lsame( uplo, 'L' )
257 IF( .NOT.normaltransr .AND. .NOT.lsame( transr, 'C' ) ) THEN
258 info = -1
259 ELSE IF( .NOT.lower .AND. .NOT.lsame( uplo, 'U' ) ) THEN
260 info = -2
261 ELSE IF( n.LT.0 ) THEN
262 info = -3
263 ELSE IF( nrhs.LT.0 ) THEN
264 info = -4
265 ELSE IF( ldb.LT.max( 1, n ) ) THEN
266 info = -7
267 END IF
268 IF( info.NE.0 ) THEN
269 CALL xerbla( 'ZPFTRS', -info )
270 RETURN
271 END IF
272*
273* Quick return if possible
274*
275 IF( n.EQ.0 .OR. nrhs.EQ.0 )
276 $ RETURN
277*
278* start execution: there are two triangular solves
279*
280 IF( lower ) THEN
281 CALL ztfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, cone, a,
282 $ b,
283 $ ldb )
284 CALL ztfsm( transr, 'L', uplo, 'C', 'N', n, nrhs, cone, a,
285 $ b,
286 $ ldb )
287 ELSE
288 CALL ztfsm( transr, 'L', uplo, 'C', 'N', n, nrhs, cone, a,
289 $ b,
290 $ ldb )
291 CALL ztfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, cone, a,
292 $ b,
293 $ ldb )
294 END IF
295*
296 RETURN
297*
298* End of ZPFTRS
299*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ztfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)
ZTFSM solves a matrix equation (one operand is a triangular matrix in RFP format).
Definition ztfsm.f:298
Here is the call graph for this function:
Here is the caller graph for this function: