exciting-0.9.218
[exciting.git] / src / LAPACK / zlarf.f
blobd5233c8c9c54ba28a932863f0f2badb0de22f814
1 SUBROUTINE ZLARF( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
3 * -- LAPACK auxiliary routine (version 3.1) --
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * November 2006
7 * .. Scalar Arguments ..
8 CHARACTER SIDE
9 INTEGER INCV, LDC, M, N
10 COMPLEX*16 TAU
11 * ..
12 * .. Array Arguments ..
13 COMPLEX*16 C( LDC, * ), V( * ), WORK( * )
14 * ..
16 * Purpose
17 * =======
19 * ZLARF applies a complex elementary reflector H to a complex M-by-N
20 * matrix C, from either the left or the right. H is represented in the
21 * form
23 * H = I - tau * v * v'
25 * where tau is a complex scalar and v is a complex vector.
27 * If tau = 0, then H is taken to be the unit matrix.
29 * To apply H' (the conjugate transpose of H), supply conjg(tau) instead
30 * tau.
32 * Arguments
33 * =========
35 * SIDE (input) CHARACTER*1
36 * = 'L': form H * C
37 * = 'R': form C * H
39 * M (input) INTEGER
40 * The number of rows of the matrix C.
42 * N (input) INTEGER
43 * The number of columns of the matrix C.
45 * V (input) COMPLEX*16 array, dimension
46 * (1 + (M-1)*abs(INCV)) if SIDE = 'L'
47 * or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
48 * The vector v in the representation of H. V is not used if
49 * TAU = 0.
51 * INCV (input) INTEGER
52 * The increment between elements of v. INCV <> 0.
54 * TAU (input) COMPLEX*16
55 * The value tau in the representation of H.
57 * C (input/output) COMPLEX*16 array, dimension (LDC,N)
58 * On entry, the M-by-N matrix C.
59 * On exit, C is overwritten by the matrix H * C if SIDE = 'L',
60 * or C * H if SIDE = 'R'.
62 * LDC (input) INTEGER
63 * The leading dimension of the array C. LDC >= max(1,M).
65 * WORK (workspace) COMPLEX*16 array, dimension
66 * (N) if SIDE = 'L'
67 * or (M) if SIDE = 'R'
69 * =====================================================================
71 * .. Parameters ..
72 COMPLEX*16 ONE, ZERO
73 PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ),
74 $ ZERO = ( 0.0D+0, 0.0D+0 ) )
75 * ..
76 * .. External Subroutines ..
77 EXTERNAL ZGEMV, ZGERC
78 * ..
79 * .. External Functions ..
80 LOGICAL LSAME
81 EXTERNAL LSAME
82 * ..
83 * .. Executable Statements ..
85 IF( LSAME( SIDE, 'L' ) ) THEN
87 * Form H * C
89 IF( TAU.NE.ZERO ) THEN
91 * w := C' * v
93 CALL ZGEMV( 'Conjugate transpose', M, N, ONE, C, LDC, V,
94 $ INCV, ZERO, WORK, 1 )
96 * C := C - v * w'
98 CALL ZGERC( M, N, -TAU, V, INCV, WORK, 1, C, LDC )
99 END IF
100 ELSE
102 * Form C * H
104 IF( TAU.NE.ZERO ) THEN
106 * w := C * v
108 CALL ZGEMV( 'No transpose', M, N, ONE, C, LDC, V, INCV,
109 $ ZERO, WORK, 1 )
111 * C := C - w * v'
113 CALL ZGERC( M, N, -TAU, WORK, 1, V, INCV, C, LDC )
114 END IF
115 END IF
116 RETURN
118 * End of ZLARF